X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FbasicTypes%2FDataCon.lhs;h=e5a624fe29d54cf2f1df38025c59e192f62c5bee;hb=7df9b88b9e0565f438f16d8005526ffda80a1dbe;hp=2c4400b3b60d748b11037cbcd3d1765f91689a37;hpb=5822cb8d13aa3c05d2b46b4510c13d94b902eb21;p=ghc-hetmet.git diff --git a/compiler/basicTypes/DataCon.lhs b/compiler/basicTypes/DataCon.lhs index 2c4400b..e5a624f 100644 --- a/compiler/basicTypes/DataCon.lhs +++ b/compiler/basicTypes/DataCon.lhs @@ -44,7 +44,6 @@ import ListSetOps import Util import Maybes import FastString -import PackageConfig import Module import Data.Char @@ -88,15 +87,20 @@ differently, as follows. Note [Data Constructor Naming] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -Each data constructor C has two, and possibly three, Names associated with it: +Each data constructor C has two, and possibly up to four, Names associated with it: - OccName Name space Used for + OccName Name space Name of --------------------------------------------------------------------------- - * The "source data con" C DataName The DataCon itself - * The "real data con" C VarName Its worker Id - * The "wrapper data con" $WC VarName Wrapper Id (optional) - -Each of these three has a distinct Unique. The "source data con" name + * The "data con itself" C DataName DataCon + * The "worker data con" C VarName Id (the worker) + * The "wrapper data con" $WC VarName Id (the wrapper) + * The "newtype coercion" :CoT TcClsName TyCon + +EVERY data constructor (incl for newtypes) has the former two (the +data con itself, and its worker. But only some data constructors have a +wrapper (see Note [The need for a wrapper]). + +Each of these three has a distinct Unique. The "data con itself" name appears in the output of the renamer, and names the Haskell-source data constructor. The type checker translates it into either the wrapper Id (if it exists) or worker Id (otherwise). @@ -130,6 +134,8 @@ The "wrapper Id", $WC, goes as follows nothing for the wrapper to do. That is, if its defn would be $wC = C +Note [The need for a wrapper] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Why might the wrapper have anything to do? Two reasons: * Unboxing strict fields (with -funbox-strict-fields) @@ -153,6 +159,8 @@ Why might the wrapper have anything to do? Two reasons: The third argument is a coerion [a] :: [a]:=:[a] +INVARIANT: the dictionary constructor for a class + never has a wrapper. A note about the stupid context @@ -330,19 +338,21 @@ data DataCon dcRepTyCon :: TyCon, -- Result tycon, T dcRepType :: Type, -- Type of the constructor - -- forall a x y. (a:=:(x,y), Ord x) => x -> y -> MkT a + -- forall a x y. (a:=:(x,y), x~y, Ord x) => + -- x -> y -> T a -- (this is *not* of the constructor wrapper Id: -- see Note [Data con representation] below) -- Notice that the existential type parameters come *second*. -- Reason: in a case expression we may find: - -- case (e :: T t) of { MkT b (d:Ord b) (x:t) (xs:[b]) -> ... } + -- case (e :: T t) of + -- MkT x y co1 co2 (d:Ord x) (v:r) (w:F s) -> ... -- It's convenient to apply the rep-type of MkT to 't', to get - -- forall b. Ord b => ... + -- forall x y. (t:=:(x,y), x~y, Ord x) => x -> y -> T t -- and use that to check the pattern. Mind you, this is really only - -- use in CoreLint. + -- used in CoreLint. - -- Finally, the curried worker function that corresponds to the constructor + -- The curried worker function that corresponds to the constructor: -- It doesn't have an unfolding; the code generator saturates these Ids -- and allocates a real constructor when it finds one. -- @@ -368,7 +378,7 @@ data DataConIds -- The 'Nothing' case of DCIds is important -- Not only is this efficient, -- but it also ensures that the wrapper is replaced - -- by the worker (becuase it *is* the worker) + -- by the worker (because it *is* the worker) -- even when there are no args. E.g. in -- f (:) x -- the (:) *is* the worker. @@ -525,6 +535,7 @@ mkDataCon name declared_infix eqSpecPreds :: [(TyVar,Type)] -> ThetaType eqSpecPreds spec = [ mkEqPred (mkTyVarTy tv, ty) | (tv,ty) <- spec ] +mk_dict_strict_mark :: PredType -> StrictnessMark mk_dict_strict_mark pred | isStrictPred pred = MarkedStrict | otherwise = NotMarkedStrict \end{code} @@ -608,6 +619,7 @@ dataConSourceArity dc = length (dcOrigArgTys dc) -- {\em representation} of the data constructor. This may be more than appear -- in the source code; the extra ones are the existentially quantified -- dictionaries +dataConRepArity :: DataCon -> Int dataConRepArity (MkData {dcRepArgTys = arg_tys}) = length arg_tys isNullarySrcDataCon, isNullaryRepDataCon :: DataCon -> Bool @@ -666,7 +678,7 @@ dataConInstArgTys dc@(MkData {dcRepArgTys = rep_arg_tys, dcUnivTyVars = univ_tvs, dcEqSpec = eq_spec, dcExTyVars = ex_tvs}) inst_tys = ASSERT2 ( length univ_tvs == length inst_tys - , ptext SLIT("dataConInstArgTys") <+> ppr dc $$ ppr univ_tvs $$ ppr inst_tys) + , ptext (sLit "dataConInstArgTys") <+> ppr dc $$ ppr univ_tvs $$ ppr inst_tys) ASSERT2 ( null ex_tvs && null eq_spec, ppr dc ) map (substTyWith univ_tvs inst_tys) rep_arg_tys @@ -681,7 +693,7 @@ dataConInstOrigArgTys dc@(MkData {dcOrigArgTys = arg_tys, dcUnivTyVars = univ_tvs, dcExTyVars = ex_tvs}) inst_tys = ASSERT2( length tyvars == length inst_tys - , ptext SLIT("dataConInstOrigArgTys") <+> ppr dc $$ ppr tyvars $$ ppr inst_tys ) + , ptext (sLit "dataConInstOrigArgTys") <+> ppr dc $$ ppr tyvars $$ ppr inst_tys ) map (substTyWith tyvars inst_tys) arg_tys where tyvars = univ_tvs ++ ex_tvs @@ -696,7 +708,7 @@ dataConInstOrigDictsAndArgTys dc@(MkData {dcOrigArgTys = arg_tys, dcUnivTyVars = univ_tvs, dcExTyVars = ex_tvs}) inst_tys = ASSERT2( length tyvars == length inst_tys - , ptext SLIT("dataConInstOrigDictsAndArgTys") <+> ppr dc $$ ppr tyvars $$ ppr inst_tys ) + , ptext (sLit "dataConInstOrigDictsAndArgTys") <+> ppr dc $$ ppr tyvars $$ ppr inst_tys ) map (substTyWith tyvars inst_tys) (mkPredTys dicts ++ arg_tys) where tyvars = univ_tvs ++ ex_tvs @@ -784,14 +796,16 @@ splitProductType_maybe ty where data_con = ASSERT( not (null (tyConDataCons tycon)) ) head (tyConDataCons tycon) - other -> Nothing + _other -> Nothing +splitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type]) splitProductType str ty = case splitProductType_maybe ty of Just stuff -> stuff Nothing -> pprPanic (str ++ ": not a product") (pprType ty) +deepSplitProductType_maybe :: Type -> Maybe (TyCon, [Type], DataCon, [Type]) deepSplitProductType_maybe ty = do { (res@(tycon, tycon_args, _, _)) <- splitProductType_maybe ty ; let {result @@ -804,6 +818,7 @@ deepSplitProductType_maybe ty ; result } +deepSplitProductType :: String -> Type -> (TyCon, [Type], DataCon, [Type]) deepSplitProductType str ty = case deepSplitProductType_maybe ty of Just stuff -> stuff