Skip to content

Commit

Permalink
Take type-function arity into account
Browse files Browse the repository at this point in the history
...when computing the size of a call on the RHS of a type
instance declaration.

This came up in Trac #11581.  The change is in
   TcType.tcTyFamInsts
which now trims the type arguments in a call.  See the
comments with that function definition.
  • Loading branch information
Simon Peyton Jones committed Feb 18, 2016
1 parent 4d031cf commit a008ead
Show file tree
Hide file tree
Showing 3 changed files with 21 additions and 2 deletions.
14 changes: 12 additions & 2 deletions compiler/typecheck/TcType.hs
Original file line number Diff line number Diff line change
Expand Up @@ -693,13 +693,23 @@ isSigMaybe _ = Nothing
-}

-- | Finds outermost type-family applications occuring in a type,
-- after expanding synonyms.
-- after expanding synonyms. In the list (F, tys) that is returned
-- we guarantee that tys matches F's arity. For example, given
-- type family F a :: * -> * (arity 1)
-- calling tcTyFamInsts on (Maybe (F Int Bool) will return
-- (F, [Int]), not (F, [Int,Bool])
--
-- This is important for its use in deciding termination of type
-- instances (see Trac #11581). E.g.
-- type instance G [Int] = ...(F Int <big type>)...
-- we don't need to take <big type> into account when asking if
-- the calls on the RHS are smaller than the LHS
tcTyFamInsts :: Type -> [(TyCon, [Type])]
tcTyFamInsts ty
| Just exp_ty <- coreView ty = tcTyFamInsts exp_ty
tcTyFamInsts (TyVarTy _) = []
tcTyFamInsts (TyConApp tc tys)
| isTypeFamilyTyCon tc = [(tc, tys)]
| isTypeFamilyTyCon tc = [(tc, take (tyConArity tc) tys)]
| otherwise = concat (map tcTyFamInsts tys)
tcTyFamInsts (LitTy {}) = []
tcTyFamInsts (ForAllTy bndr ty) = tcTyFamInsts (binderType bndr)
Expand Down
8 changes: 8 additions & 0 deletions testsuite/tests/indexed-types/should_compile/T11581.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,8 @@
{-# LANGUAGE TypeFamilies #-}

module T11581 where

type family F a :: * -> *
type family G a

type instance G [a] = F a (Int,Bool)
1 change: 1 addition & 0 deletions testsuite/tests/indexed-types/should_compile/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -274,3 +274,4 @@ test('T11408', normal, compile, [''])
test('T11361', normal, compile, ['-dunique-increment=-1'])
# -dunique-increment=-1 doesn't work inside the file
test('T11361a', normal, compile_fail, [''])
test('T11581', normal, compile, [''])

0 comments on commit a008ead

Please sign in to comment.