X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2Ftypecheck%2FTcDeriv.lhs;h=fab7c61ff07cd2e388a1bf4a0d7141255c112e18;hp=52ce0c20106540d2b614ca726a4f159b52e143fd;hb=HEAD;hpb=1b381af863d64aaa0a4dd9c816170c58e6131a9e diff --git a/compiler/typecheck/TcDeriv.lhs b/compiler/typecheck/TcDeriv.lhs index 52ce0c2..fab7c61 100644 --- a/compiler/typecheck/TcDeriv.lhs +++ b/compiler/typecheck/TcDeriv.lhs @@ -332,7 +332,7 @@ tcDeriving tycl_decls inst_decls deriv_decls ; dflags <- getDOpts ; liftIO (dumpIfSet_dyn dflags Opt_D_dump_deriv "Derived instances" - (ddump_deriving inst_info rn_binds)) + (ddump_deriving inst_info rn_binds repMetaTys repTyCons metaInsts)) {- ; when (not (null inst_info)) $ dumpDerivingInfo (ddump_deriving inst_info rn_binds) @@ -340,11 +340,26 @@ tcDeriving tycl_decls inst_decls deriv_decls ; return ( inst_info, rn_binds, rn_dus , concat (map metaTyCons2TyCons repMetaTys), repTyCons) } where - ddump_deriving :: [InstInfo Name] -> HsValBinds Name -> SDoc - ddump_deriving inst_infos extra_binds - = hang (ptext (sLit "Derived instances")) - 2 (vcat (map (\i -> pprInstInfoDetails i $$ text "") inst_infos) - $$ ppr extra_binds) + ddump_deriving :: [InstInfo Name] -> HsValBinds Name + -> [MetaTyCons] -- ^ Empty data constructors + -> [TyCon] -- ^ Rep type family instances + -> [[(InstInfo RdrName, DerivAuxBinds)]] + -- ^ Instances for the repMetaTys + -> SDoc + ddump_deriving inst_infos extra_binds repMetaTys repTyCons metaInsts + = hang (ptext (sLit "Derived instances")) + 2 (vcat (map (\i -> pprInstInfoDetails i $$ text "") inst_infos) + $$ ppr extra_binds) + $$ hangP "Generic representation" ( + hangP "Generated datatypes for meta-information" + (vcat (map ppr repMetaTys)) + -- The Outputable instance for TyCon unfortunately only prints the name... + $$ hangP "Representation types" + (vcat (map ppr repTyCons)) + $$ hangP "Meta-information instances" + (vcat (map (pprInstInfoDetails . fst) (concat metaInsts)))) + + hangP s x = text "" $$ hang (ptext (sLit s)) 2 x renameDeriv :: Bool -> LHsBinds RdrName @@ -476,7 +491,11 @@ makeDerivSpecs is_boot tycl_decls inst_decls deriv_decls (sel_tydata ++ sel_deriv_decls)) allTyNames -- We need to generate the extras to add to what has -- already been derived - ; mapM mkGenDerivExtras derTyDecls } + ; {- pprTrace "sel_tydata" (ppr sel_tydata) $ + pprTrace "sel_deriv_decls" (ppr sel_deriv_decls) $ + pprTrace "derTyDecls" (ppr derTyDecls) $ + pprTrace "deriv_decls" (ppr deriv_decls) $ -} + mapM mkGenDerivExtras derTyDecls } -- Merge and return ; return ( eqns1 ++ eqns2, generic_extras_deriv) } @@ -487,14 +506,22 @@ makeDerivSpecs is_boot tycl_decls inst_decls deriv_decls -- Extracts the name of the class in the deriving getClassName :: HsType Name -> Maybe Name - getClassName (HsPredTy (HsClassP n _)) = Just n - getClassName _ = Nothing + getClassName (HsForAllTy _ _ _ (L _ n)) = getClassName n + getClassName (HsPredTy (HsClassP n _)) = Just n + getClassName _ = Nothing -- Extracts the name of the type in the deriving + -- This function (and also getClassName above) is not really nice, and I + -- might not have covered all possible cases. I wonder if there is no easier + -- way to extract class and type name from a LDerivDecl... getTypeName :: HsType Name -> Maybe Name + getTypeName (HsForAllTy _ _ _ (L _ n)) = getTypeName n getTypeName (HsTyVar n) = Just n getTypeName (HsOpTy _ (L _ n) _) = Just n getTypeName (HsPredTy (HsClassP _ [L _ n])) = getTypeName n + getTypeName (HsAppTy (L _ n) _) = getTypeName n + getTypeName (HsParTy (L _ n)) = getTypeName n + getTypeName (HsKindSig (L _ n) _) = getTypeName n getTypeName _ = Nothing extractTyDataPreds decls @@ -1590,7 +1617,8 @@ genGenericRepExtras tc = let metaDts = MetaTyCons metaDTyCon metaCTyCons metaSTyCons rep0_tycon <- tc_mkRepTyCon tc metaDts - + + -- pprTrace "rep0" (ppr rep0_tycon) $ return (metaDts, rep0_tycon) {- genGenericAll :: TyCon