X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2Ftypes%2FTyCon.lhs;h=eb773464e1e4409dfc54e7909c51e9b347f7a359;hb=685e04e4af2e2332f2555990122596c7931cb543;hp=bee967c94d0c60f020d31286c95843d1362f2aa0;hpb=bca9dd54c2b39638cb4638aaccf6015a104a1df5;p=ghc-hetmet.git diff --git a/ghc/compiler/types/TyCon.lhs b/ghc/compiler/types/TyCon.lhs index bee967c..eb77346 100644 --- a/ghc/compiler/types/TyCon.lhs +++ b/ghc/compiler/types/TyCon.lhs @@ -13,10 +13,13 @@ module TyCon( isTupleTyCon, isUnboxedTupleTyCon, isBoxedTupleTyCon, tupleTyConBoxity, isRecursiveTyCon, newTyConRep, - mkAlgTyConRep, --mkAlgTyCon, + mkForeignTyCon, isForeignTyCon, + + mkAlgTyCon, --mkAlgTyCon, mkClassTyCon, mkFunTyCon, mkPrimTyCon, + mkLiftedPrimTyCon, mkTupleTyCon, mkSynTyCon, mkKindCon, @@ -29,12 +32,12 @@ module TyCon( tyConUnique, tyConTyVars, tyConArgVrcs_maybe, - tyConDataCons, tyConDataConsIfAvailable, - tyConFamilySize, + tyConDataCons, tyConDataConsIfAvailable, tyConFamilySize, + tyConSelIds, tyConTheta, tyConPrimRep, tyConArity, - isClassTyCon, + isClassTyCon, tyConClass_maybe, getSynTyConDefn, maybeTyConSingleCon, @@ -47,21 +50,22 @@ module TyCon( #include "HsVersions.h" -import {-# SOURCE #-} TypeRep ( Type, Kind, SuperKind ) +import {-# SOURCE #-} TypeRep ( Type, PredType, Kind, SuperKind ) -- Should just be Type(Type), but this fails due to bug present up to -- and including 4.02 involving slurping of hi-boot files. Bug is now fixed. import {-# SOURCE #-} DataCon ( DataCon, isExistentialDataCon ) -import Class ( ClassContext ) import Var ( TyVar, Id ) +import Class ( Class ) import BasicTypes ( Arity, RecFlag(..), Boxity(..), isBoxed, EP(..) ) import Name ( Name, nameUnique, NamedThing(getName) ) import PrelNames ( Unique, Uniquable(..), anyBoxConKey ) import PrimRep ( PrimRep(..), isFollowableRep ) import Outputable +import FastString \end{code} %************************************************************************ @@ -92,7 +96,7 @@ data TyCon tyConTyVars :: [TyVar], tyConArgVrcs :: ArgVrcs, - algTyConTheta :: ClassContext, + algTyConTheta :: [PredType], dataCons :: [DataCon], -- Its data constructors, with fully polymorphic types @@ -102,6 +106,8 @@ data TyCon -- (b) in a quest for fast compilation we don't import -- the constructors + selIds :: [Id], -- Its record selectors (if any) + noOfDataCons :: Int, -- Number of data constructors -- Usually this is the same as the length of the -- dataCons field, but the latter may be empty if @@ -118,17 +124,22 @@ data TyCon -- e.g. the TyCon for a Class dictionary, -- and TyCons with unboxed arguments - algTyConClass :: Bool -- True if this tycon comes from a class declaration + algTyConClass :: Maybe Class -- Just cl if this tycon came from a class declaration } - | PrimTyCon { -- Primitive types; cannot be defined in Haskell - -- NB: All of these guys are *unlifted*, but not all are *unboxed* + | PrimTyCon { -- Primitive types; cannot be defined in Haskell + -- Now includes foreign-imported types tyConUnique :: Unique, tyConName :: Name, tyConKind :: Kind, tyConArity :: Arity, tyConArgVrcs :: ArgVrcs, - primTyConRep :: PrimRep + primTyConRep :: PrimRep, -- Many primitive tycons are unboxed, but some are + -- boxed (represented by pointers). The PrimRep tells. + + isUnLifted :: Bool, -- Most primitive tycons are unlifted, + -- but foreign-imported ones may not be + tyConExtName :: Maybe FastString } | TupleTyCon { @@ -172,15 +183,17 @@ type ArgVrcs = [(Bool,Bool)] -- Tyvar variance info: [(occPos,occNeg)] data AlgTyConFlavour = DataTyCon -- Data type + | EnumTyCon -- Special sort of enumeration type + | NewTyCon Type -- Newtype, with its *ultimate* representation type -- By 'ultimate' I mean that the rep type is not itself -- a newtype or type synonym. - -- The rep type has explicit for-alls for the tyvars of - -- the TyCon. Thus: + -- The rep type has free type variables the tyConTyVars + -- Thus: -- newtype T a = MkT [(a,Int)] - -- The rep type is forall a. [(a,Int)] + -- The rep type is [(a,Int)] -- -- The rep type isn't entirely simple: -- for a recursive newtype we pick () as the rep type @@ -238,7 +251,7 @@ tyConGenIds tycon = case tyConGenInfo tycon of -- This is the making of a TyCon. Just the same as the old mkAlgTyCon, -- but now you also have to pass in the generic information about the type -- constructor - you can get hold of it easily (see Generics module) -mkAlgTyConRep name kind tyvars theta argvrcs cons ncons flavour rec +mkAlgTyCon name kind tyvars theta argvrcs cons ncons sels flavour rec gen_info = AlgTyCon { tyConName = name, @@ -249,14 +262,15 @@ mkAlgTyConRep name kind tyvars theta argvrcs cons ncons flavour rec tyConArgVrcs = argvrcs, algTyConTheta = theta, dataCons = cons, + selIds = sels, noOfDataCons = ncons, - algTyConClass = False, + algTyConClass = Nothing, algTyConFlavour = flavour, algTyConRec = rec, genInfo = gen_info } -mkClassTyCon name kind tyvars argvrcs con clas flavour +mkClassTyCon name kind tyvars argvrcs con clas flavour rec = AlgTyCon { tyConName = name, tyConUnique = nameUnique name, @@ -266,10 +280,11 @@ mkClassTyCon name kind tyvars argvrcs con clas flavour tyConArgVrcs = argvrcs, algTyConTheta = [], dataCons = [con], + selIds = [], noOfDataCons = 1, - algTyConClass = True, + algTyConClass = Just clas, algTyConFlavour = flavour, - algTyConRec = NonRecursive, + algTyConRec = rec, genInfo = Nothing } @@ -286,14 +301,42 @@ mkTupleTyCon name kind arity tyvars con boxed gen_info genInfo = gen_info } -mkPrimTyCon name kind arity arg_vrcs rep +-- Foreign-imported (.NET) type constructors are represented +-- as primitive, but *lifted*, TyCons for now. They are lifted +-- because the Haskell type T representing the (foreign) .NET +-- type T is actually implemented (in ILX) as a thunk +-- They have PtrRep +mkForeignTyCon name ext_name kind arity arg_vrcs = PrimTyCon { - tyConName = name, - tyConUnique = nameUnique name, - tyConKind = kind, - tyConArity = arity, + tyConName = name, + tyConUnique = nameUnique name, + tyConKind = kind, + tyConArity = arity, tyConArgVrcs = arg_vrcs, - primTyConRep = rep + primTyConRep = PtrRep, + isUnLifted = False, + tyConExtName = ext_name + } + + +-- most Prim tycons are lifted +mkPrimTyCon name kind arity arg_vrcs rep + = mkPrimTyCon' name kind arity arg_vrcs rep True + +-- but RealWorld is lifted +mkLiftedPrimTyCon name kind arity arg_vrcs rep + = mkPrimTyCon' name kind arity arg_vrcs rep False + +mkPrimTyCon' name kind arity arg_vrcs rep is_unlifted + = PrimTyCon { + tyConName = name, + tyConUnique = nameUnique name, + tyConKind = kind, + tyConArity = arity, + tyConArgVrcs = arg_vrcs, + primTyConRep = rep, + isUnLifted = is_unlifted, + tyConExtName = Nothing } mkSynTyCon name kind arity tyvars rhs argvrcs @@ -318,9 +361,9 @@ isFunTyCon _ = False isPrimTyCon (PrimTyCon {}) = True isPrimTyCon _ = False -isUnLiftedTyCon (PrimTyCon {}) = True -isUnLiftedTyCon (TupleTyCon { tyConBoxed = boxity}) = not (isBoxed boxity) -isUnLiftedTyCon _ = False +isUnLiftedTyCon (PrimTyCon {isUnLifted = is_unlifted}) = is_unlifted +isUnLiftedTyCon (TupleTyCon {tyConBoxed = boxity}) = not (isBoxed boxity) +isUnLiftedTyCon _ = False -- isBoxedTyCon should not be applied to SynTyCon, nor KindCon isBoxedTyCon (AlgTyCon {}) = True @@ -333,18 +376,26 @@ isAlgTyCon (AlgTyCon {}) = True isAlgTyCon (TupleTyCon {}) = True isAlgTyCon other = False --- isDataTyCon returns False for @newtype@ and for unboxed tuples -isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data}) = case new_or_data of - NewTyCon _ -> False - other -> True +-- isDataTyCon returns True for data types that are represented by +-- heap-allocated constructors. +-- These are srcutinised by Core-level @case@ expressions, and they +-- get info tables allocated for them. +-- True for all @data@ types +-- False for newtypes +-- unboxed tuples +isDataTyCon (AlgTyCon {algTyConFlavour = new_or_data, algTyConRec = is_rec}) + = case new_or_data of + NewTyCon _ -> False + other -> True + isDataTyCon (TupleTyCon {tyConBoxed = boxity}) = isBoxed boxity isDataTyCon other = False isNewTyCon (AlgTyCon {algTyConFlavour = NewTyCon _}) = True isNewTyCon other = False -newTyConRep (AlgTyCon {algTyConFlavour = NewTyCon rep}) = Just rep -newTyConRep other = Nothing +newTyConRep :: TyCon -> ([TyVar], Type) +newTyConRep (AlgTyCon {tyConTyVars = tvs, algTyConFlavour = NewTyCon rep}) = (tvs, rep) -- A "product" tycon -- has *one* constructor, @@ -379,11 +430,17 @@ tupleTyConBoxity tc = tyConBoxed tc isRecursiveTyCon (AlgTyCon {algTyConRec = Recursive}) = True isRecursiveTyCon other = False + +-- isForeignTyCon identifies foreign-imported type constructors +-- For the moment, they are primitive but lifted, but that may change +isForeignTyCon (PrimTyCon {isUnLifted = is_unlifted}) = not is_unlifted +isForeignTyCon other = False \end{code} \begin{code} tyConDataCons :: TyCon -> [DataCon] -tyConDataCons tycon = ASSERT2( not (null cons), ppr tycon ) cons +tyConDataCons tycon = ASSERT2( length cons == tyConFamilySize tycon, ppr tycon ) + cons where cons = tyConDataConsIfAvailable tycon @@ -401,15 +458,25 @@ tyConFamilySize (TupleTyCon {}) = 1 tyConFamilySize other = pprPanic "tyConFamilySize:" (ppr other) #endif +tyConSelIds :: TyCon -> [Id] +tyConSelIds (AlgTyCon {selIds = sels}) = sels +tyConSelIds other_tycon = [] +\end{code} + +\begin{code} tyConPrimRep :: TyCon -> PrimRep tyConPrimRep (PrimTyCon {primTyConRep = rep}) = rep -tyConPrimRep _ = PtrRep +tyConPrimRep tc = ASSERT( not (isUnboxedTupleTyCon tc) ) + PtrRep + -- We should not be asking what the representation of an + -- unboxed tuple is, because it isn't a first class value. \end{code} \begin{code} -tyConTheta :: TyCon -> ClassContext +tyConTheta :: TyCon -> [PredType] tyConTheta (AlgTyCon {algTyConTheta = theta}) = theta --- should ask about anything else +tyConTheta (TupleTyCon {}) = [] +-- shouldn't ask about anything else \end{code} @tyConArgVrcs_maybe@ gives a list of (occPos,occNeg) flags, one for @@ -445,8 +512,12 @@ maybeTyConSingleCon tc = pprPanic "maybeTyConSingleCon: unexpected tycon " $ \begin{code} isClassTyCon :: TyCon -> Bool -isClassTyCon (AlgTyCon {algTyConClass = is_class_tycon}) = is_class_tycon -isClassTyCon other_tycon = False +isClassTyCon (AlgTyCon {algTyConClass = Just _}) = True +isClassTyCon other_tycon = False + +tyConClass_maybe :: TyCon -> Maybe Class +tyConClass_maybe (AlgTyCon {algTyConClass = maybe_clas}) = maybe_clas +tyConClass_maybe ther_tycon = Nothing \end{code}