X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Ftypes%2FTyCon.lhs;h=d91effeada8da392126742bd68afd40d621c53e5;hb=b00b5bc04ff36a551552470060064f0b7d84ca30;hp=5ded0a8c7ca05da795113f7506adff9935a68fb6;hpb=909d2dd885f5eebaf7c12cf15d5ac153d646566e;p=ghc-hetmet.git diff --git a/compiler/types/TyCon.lhs b/compiler/types/TyCon.lhs index 5ded0a8..d91effe 100644 --- a/compiler/types/TyCon.lhs +++ b/compiler/types/TyCon.lhs @@ -10,16 +10,20 @@ module TyCon( PrimRep(..), tyConPrimRep, - AlgTyConRhs(..), visibleDataCons, AlgTyConParent(..), + AlgTyConRhs(..), visibleDataCons, + AlgTyConParent(..), hasParent, SynTyConRhs(..), isFunTyCon, isUnLiftedTyCon, isProductTyCon, - isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isPrimTyCon, + isAlgTyCon, isDataTyCon, isSynTyCon, isNewTyCon, isClosedNewTyCon, + isPrimTyCon, isEnumerationTyCon, isGadtSyntaxTyCon, isOpenTyCon, + assocTyConArgPoss_maybe, isTyConAssoc, setTyConArgPoss, isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity, - isRecursiveTyCon, newTyConRep, newTyConRhs, newTyConCo, + isRecursiveTyCon, newTyConRep, newTyConRhs, newTyConCo_maybe, isHiBootTyCon, isSuperKindTyCon, isCoercionTyCon_maybe, isCoercionTyCon, + isImplicitTyCon, tcExpandTyCon_maybe, coreExpandTyCon_maybe, @@ -59,7 +63,7 @@ module TyCon( #include "HsVersions.h" -import {-# SOURCE #-} TypeRep ( Kind, Type, Coercion, PredType ) +import {-# SOURCE #-} TypeRep ( Kind, Type, PredType ) import {-# SOURCE #-} DataCon ( DataCon, isVanillaDataCon ) import Var ( TyVar, Id ) @@ -67,6 +71,7 @@ import Class ( Class ) import BasicTypes ( Arity, RecFlag(..), Boxity(..), isBoxed ) import Name ( Name, nameUnique, NamedThing(getName) ) import PrelNames ( Unique, Uniquable(..) ) +import Maybe ( isJust ) import Maybes ( orElse ) import Outputable import FastString @@ -94,11 +99,21 @@ data TyCon tyConName :: Name, tyConKind :: Kind, tyConArity :: Arity, - + tyConTyVars :: [TyVar], -- Scopes over (a) the algTcStupidTheta -- (b) the cached types in -- algTyConRhs.NewTyCon + -- (c) the family instance + -- types if present -- But not over the data constructors + + tyConArgPoss :: Maybe [Int], -- for associated families: for each + -- tyvar in the AT decl, gives the + -- position of that tyvar in the class + -- argument list (starting from 0). + -- NB: Length is less than tyConArity + -- if higher kind signature. + algTcSelIds :: [Id], -- Its record selectors (empty if none) algTcGadtSyntax :: Bool, -- True <=> the data type was declared using GADT syntax @@ -133,13 +148,21 @@ data TyCon } | SynTyCon { - tyConUnique :: Unique, - tyConName :: Name, - tyConKind :: Kind, - tyConArity :: Arity, - - tyConTyVars :: [TyVar], -- Bound tyvars - synTcRhs :: SynTyConRhs -- Expanded type in here + tyConUnique :: Unique, + tyConName :: Name, + tyConKind :: Kind, + tyConArity :: Arity, + + tyConTyVars :: [TyVar], -- Bound tyvars + + tyConArgPoss :: Maybe [Int], -- for associated families: for each + -- tyvar in the AT decl, gives the + -- position of that tyvar in the class + -- argument list (starting from 0). + -- NB: Length is less than tyConArity + -- if higher kind signature. + + synTcRhs :: SynTyConRhs -- Expanded type in here } | PrimTyCon { -- Primitive types; cannot be defined in Haskell @@ -164,8 +187,10 @@ data TyCon tyConUnique :: Unique, tyConName :: Name, tyConArity :: Arity, - coKindFun :: [Type] -> Kind - } + coKindFun :: [Type] -> (Type,Type) + } -- INVARAINT: coKindFun is always applied to exactly 'arity' args + -- E.g. for trans (c1 :: ta=tb) (c2 :: tb=tc), the coKindFun returns + -- the kind as a pair of types: (ta,tc) | SuperKindTyCon { -- Super Kinds, TY (box) and CO (diamond). -- They have no kind; and arity zero @@ -173,10 +198,6 @@ data TyCon tyConName :: Name } -type KindCon = TyCon - -type SuperKindCon = TyCon - type FieldLabel = Name data AlgTyConRhs @@ -256,6 +277,10 @@ data AlgTyConParent = -- An ordinary type constructor has no parent. -- the representation type -- with the type instance +hasParent :: AlgTyConParent -> Bool +hasParent NoParentTyCon = False +hasParent _other = True + data SynTyConRhs = OpenSynTyCon Kind -- Type family: *result* kind given | SynonymTyCon Type -- Mentioning head type vars. Acts as a template for @@ -399,6 +424,7 @@ mkAlgTyCon name kind tyvars stupid rhs sel_ids parent is_rec gen_info gadt_syn tyConKind = kind, tyConArity = length tyvars, tyConTyVars = tyvars, + tyConArgPoss = Nothing, algTcStupidTheta = stupid, algTcRhs = rhs, algTcSelIds = sel_ids, @@ -468,6 +494,7 @@ mkSynTyCon name kind tyvars rhs tyConKind = kind, tyConArity = length tyvars, tyConTyVars = tyvars, + tyConArgPoss = Nothing, synTcRhs = rhs } @@ -530,13 +557,23 @@ isDataTyCon tc@(AlgTyCon {algTcRhs = rhs}) OpenNewTyCon -> False NewTyCon {} -> False AbstractTyCon -> pprPanic "isDataTyCon" (ppr tc) - isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity isDataTyCon other = False isNewTyCon :: TyCon -> Bool -isNewTyCon (AlgTyCon {algTcRhs = NewTyCon {}}) = True -isNewTyCon other = False +isNewTyCon (AlgTyCon {algTcRhs = rhs}) = case rhs of + OpenNewTyCon -> True + NewTyCon {} -> True + _ -> False +isNewTyCon other = False + +-- This is an important refinement as typical newtype optimisations do *not* +-- hold for newtype families. Why? Given a type `T a', if T is a newtype +-- family, there is no unique right hand side by which `T a' can be replaced +-- by a cast. +-- +isClosedNewTyCon :: TyCon -> Bool +isClosedNewTyCon tycon = isNewTyCon tycon && not (isOpenTyCon tycon) isProductTyCon :: TyCon -> Bool -- A "product" tycon @@ -573,6 +610,19 @@ isOpenTyCon (AlgTyCon {algTcRhs = OpenDataTyCon }) = True isOpenTyCon (AlgTyCon {algTcRhs = OpenNewTyCon }) = True isOpenTyCon _ = False +assocTyConArgPoss_maybe :: TyCon -> Maybe [Int] +assocTyConArgPoss_maybe (AlgTyCon { tyConArgPoss = poss }) = poss +assocTyConArgPoss_maybe (SynTyCon { tyConArgPoss = poss }) = poss +assocTyConArgPoss_maybe _ = Nothing + +isTyConAssoc :: TyCon -> Bool +isTyConAssoc = isJust . assocTyConArgPoss_maybe + +setTyConArgPoss :: TyCon -> [Int] -> TyCon +setTyConArgPoss tc@(AlgTyCon {}) poss = tc { tyConArgPoss = Just poss } +setTyConArgPoss tc@(SynTyCon {}) poss = tc { tyConArgPoss = Just poss } +setTyConArgPoss tc _ = pprPanic "setTyConArgPoss" (ppr tc) + isTupleTyCon :: TyCon -> Bool -- The unit tycon didn't used to be classed as a tuple tycon -- but I thought that was silly so I've undone it @@ -613,13 +663,21 @@ isSuperKindTyCon :: TyCon -> Bool isSuperKindTyCon (SuperKindTyCon {}) = True isSuperKindTyCon other = False -isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, [Type] -> Kind) +isCoercionTyCon_maybe :: TyCon -> Maybe (Arity, [Type] -> (Type,Type)) isCoercionTyCon_maybe (CoercionTyCon {tyConArity = ar, coKindFun = rule}) = Just (ar, rule) isCoercionTyCon_maybe other = Nothing +isCoercionTyCon :: TyCon -> Bool isCoercionTyCon (CoercionTyCon {}) = True isCoercionTyCon other = False + +isImplicitTyCon :: TyCon -> Bool +isImplicitTyCon SynTyCon{} = False +isImplicitTyCon AlgTyCon{algTcParent = parent} = hasParent parent +isImplicitTyCon other = True + -- catches: FunTyCon, TupleTyCon, PrimTyCon, + -- CoercionTyCon, SuperKindTyCon \end{code} @@ -712,9 +770,9 @@ newTyConRep :: TyCon -> ([TyVar], Type) newTyConRep (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon { nt_rep = rep }}) = (tvs, rep) newTyConRep tycon = pprPanic "newTyConRep" (ppr tycon) -newTyConCo :: TyCon -> Maybe TyCon -newTyConCo (AlgTyCon {tyConTyVars = tvs, algTcRhs = NewTyCon { nt_co = co }}) = co -newTyConCo tycon = pprPanic "newTyConCo" (ppr tycon) +newTyConCo_maybe :: TyCon -> Maybe TyCon +newTyConCo_maybe (AlgTyCon {algTcRhs = NewTyCon { nt_co = co }}) = co +newTyConCo_maybe _ = Nothing tyConPrimRep :: TyCon -> PrimRep tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep @@ -769,8 +827,8 @@ tyConClass_maybe (AlgTyCon {algTcParent = ClassTyCon clas}) = Just clas tyConClass_maybe ther_tycon = Nothing isFamInstTyCon :: TyCon -> Bool -isFamInstTyCon (AlgTyCon {algTcParent = FamilyTyCon _ _ _}) = True -isFamInstTyCon other_tycon = False +isFamInstTyCon (AlgTyCon {algTcParent = FamilyTyCon _ _ _ }) = True +isFamInstTyCon other_tycon = False tyConFamInst_maybe :: TyCon -> Maybe (TyCon, [Type]) tyConFamInst_maybe (AlgTyCon {algTcParent = FamilyTyCon fam instTys _}) =