X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2Fmain%2FTidyPgm.lhs;h=d87b02622a253f40a1338c6299f0b286db728b10;hb=4f6437613948d90abc9f1e337ad6eb2209186526;hp=1f65d212e67aac414c0f64341e31250fc8c683ce;hpb=e517644d3a3272f4306654d0f50db28c664a9a8b;p=ghc-hetmet.git diff --git a/compiler/main/TidyPgm.lhs b/compiler/main/TidyPgm.lhs index 1f65d21..d87b026 100644 --- a/compiler/main/TidyPgm.lhs +++ b/compiler/main/TidyPgm.lhs @@ -20,7 +20,7 @@ import CoreLint import CoreUtils import VarEnv import VarSet -import Var +import Var hiding( mkGlobalId ) import Id import IdInfo import InstEnv @@ -34,21 +34,17 @@ import OccName import TcType import DataCon import TyCon -import Class import Module import HscTypes import Maybes import ErrUtils import UniqSupply import Outputable -import FastTypes hiding (fastOr) +import FastBool hiding ( fastOr ) import Data.List ( partition ) import Data.Maybe ( isJust ) import Data.IORef ( IORef, readIORef, writeIORef ) - -_dummy :: FS.FastString -_dummy = FSLIT("") \end{code} @@ -154,7 +150,7 @@ mkBootModDetails hsc_env exports type_env insts fam_insts tidyBootTypeEnv :: NameSet -> TypeEnv -> TypeEnv tidyBootTypeEnv exports type_env - = tidyTypeEnv True exports type_env final_ids + = tidyTypeEnv True False exports type_env final_ids where -- Find the LocalIds in the type env that are exported -- Make them into GlobalIds, and tidy their types @@ -257,8 +253,7 @@ RHSs, so that they print nicely in interfaces. \begin{code} tidyProgram :: HscEnv -> ModGuts -> IO (CgGuts, ModDetails) -tidyProgram hsc_env - (ModGuts { mg_module = mod, mg_exports = exports, +tidyProgram hsc_env (ModGuts { mg_module = mod, mg_exports = exports, mg_types = type_env, mg_insts = insts, mg_fam_insts = fam_insts, mg_binds = binds, @@ -274,6 +269,7 @@ tidyProgram hsc_env ; showPass dflags "Tidy Core" ; let { omit_prags = dopt Opt_OmitInterfacePragmas dflags + ; th = dopt Opt_TemplateHaskell dflags ; ext_ids = findExternalIds omit_prags binds ; ext_rules | omit_prags = [] @@ -292,8 +288,8 @@ tidyProgram hsc_env ; let { export_set = availsToNameSet exports ; final_ids = [ id | id <- bindersOfBinds tidy_binds, isExternalName (idName id)] - ; tidy_type_env = tidyTypeEnv omit_prags export_set type_env - final_ids + ; tidy_type_env = tidyTypeEnv omit_prags th export_set + type_env final_ids ; tidy_insts = tidyInstances (lookup_dfun tidy_type_env) insts -- A DFunId will have a binding in tidy_binds, and so -- will now be in final_env, replete with IdInfo @@ -306,21 +302,19 @@ tidyProgram hsc_env -- and indeed it does, but if omit_prags is on, ext_rules is -- empty - ; implicit_binds = getImplicitBinds type_env - ; all_tidy_binds = implicit_binds ++ tidy_binds ; alg_tycons = filter isAlgTyCon (typeEnvTyCons type_env) } - ; endPass dflags "Tidy Core" Opt_D_dump_simpl all_tidy_binds + ; endPass dflags "Tidy Core" Opt_D_dump_simpl tidy_binds ; dumpIfSet_core dflags Opt_D_dump_simpl "Tidy Core Rules" (pprRules tidy_rules) - ; let dir_imp_mods = map fst (moduleEnvElts dir_imps) + ; let dir_imp_mods = moduleEnvKeys dir_imps ; return (CgGuts { cg_module = mod, cg_tycons = alg_tycons, - cg_binds = all_tidy_binds, + cg_binds = tidy_binds, cg_dir_imps = dir_imp_mods, cg_foreign = foreign_stubs, cg_dep_pkgs = dep_pkgs deps, @@ -343,7 +337,9 @@ lookup_dfun type_env dfun_id _other -> pprPanic "lookup_dfun" (ppr dfun_id) -------------------------- -tidyTypeEnv :: Bool -> NameSet -> TypeEnv -> [Id] -> TypeEnv +tidyTypeEnv :: Bool -- Compiling without -O, so omit prags + -> Bool -- Template Haskell is on + -> NameSet -> TypeEnv -> [Id] -> TypeEnv -- The competed type environment is gotten from -- Dropping any wired-in things, and then @@ -357,10 +353,10 @@ tidyTypeEnv :: Bool -> NameSet -> TypeEnv -> [Id] -> TypeEnv -- This truncates the type environment to include only the -- exported Ids and things needed from them, which saves space -tidyTypeEnv omit_prags exports type_env final_ids - = let type_env1 = filterNameEnv keep_it type_env +tidyTypeEnv th omit_prags exports type_env final_ids + = let type_env1 = filterNameEnv keep_it type_env type_env2 = extendTypeEnvWithIds type_env1 final_ids - type_env3 | omit_prags = mapNameEnv (trimThing exports) type_env2 + type_env3 | omit_prags = mapNameEnv (trimThing th exports) type_env2 | otherwise = type_env2 in type_env3 @@ -377,20 +373,32 @@ isWiredInThing :: TyThing -> Bool isWiredInThing thing = isWiredInName (getName thing) -------------------------- -trimThing :: NameSet -> TyThing -> TyThing +trimThing :: Bool -> NameSet -> TyThing -> TyThing -- Trim off inessentials, for boot files and no -O -trimThing exports (ATyCon tc) - | not (mustExposeTyCon exports tc) - = ATyCon (makeTyConAbstract tc) +trimThing th exports (ATyCon tc) + | not th && not (mustExposeTyCon exports tc) + = ATyCon (makeTyConAbstract tc) -- Note [Trimming and Template Haskell] -trimThing _exports (AnId id) +trimThing _th _exports (AnId id) | not (isImplicitId id) = AnId (id `setIdInfo` vanillaIdInfo) -trimThing _exports other_thing +trimThing _th _exports other_thing = other_thing +{- Note [Trimming and Template Haskell] + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider (Trac #2386) this + module M(T, makeOne) where + data T = Yay String + makeOne = [| Yay "Yep" |] +Notice that T is exported abstractly, but makeOne effectively exports it too! +A module that splices in $(makeOne) will then look for a declartion of Yay, +so it'd better be there. Hence, brutally but simply, we switch off type +constructor trimming if TH is enabled in this module. -} + + mustExposeTyCon :: NameSet -- Exports -> TyCon -- The tycon -> Bool -- Can its rep be hidden? @@ -403,13 +411,14 @@ mustExposeTyCon exports tc | isEnumerationTyCon tc -- For an enumeration, exposing the constructors = True -- won't lead to the need for further exposure -- (This includes data types with no constructors.) - | isOpenTyCon tc -- open type family + | isOpenTyCon tc -- Open type family = True + | otherwise -- Newtype, datatype = any exported_con (tyConDataCons tc) -- Expose rep if any datacon or field is exported - || (isNewTyCon tc && isFFITy (snd (newTyConRep tc))) + || (isNewTyCon tc && isFFITy (snd (newTyConRhs tc))) -- Expose the rep for newtypes if the rep is an FFI type. -- For a very annoying reason. 'Foreign import' is meant to -- be able to look through newtypes transparently, but it @@ -424,31 +433,6 @@ tidyInstances tidy_dfun ispecs where tidy ispec = setInstanceDFunId ispec $ tidy_dfun (instanceDFunId ispec) - -getImplicitBinds :: TypeEnv -> [CoreBind] -getImplicitBinds type_env - = map get_defn (concatMap implicit_con_ids (typeEnvTyCons type_env) - ++ concatMap other_implicit_ids (typeEnvElts type_env)) - -- Put the constructor wrappers first, because - -- other implicit bindings (notably the fromT functions arising - -- from generics) use the constructor wrappers. At least that's - -- what External Core likes - where - implicit_con_ids tc = mapCatMaybes dataConWrapId_maybe (tyConDataCons tc) - - other_implicit_ids (ATyCon tc) = filter (not . isNaughtyRecordSelector) (tyConSelIds tc) - -- The "naughty" ones are not real functions at all - -- They are there just so we can get decent error messages - -- See Note [Naughty record selectors] in MkId.lhs - other_implicit_ids (AClass cl) = classSelIds cl - other_implicit_ids _other = [] - - get_defn :: Id -> CoreBind - get_defn id = NonRec id (tidyExpr emptyTidyEnv rhs) - where - rhs = unfoldingTemplate (idUnfolding id) - -- Don't forget to tidy the body ! Otherwise you get silly things like - -- \ tpl -> case tpl of tpl -> (tpl,tpl) -> tpl \end{code} @@ -743,12 +727,13 @@ tidyTopPair :: VarEnv Bool -- in the IdInfo of one early in the group tidyTopPair ext_ids rhs_tidy_env caf_info name' (bndr, rhs) - | isGlobalId bndr -- Injected binding for record selector, etc - = (bndr, tidyExpr rhs_tidy_env rhs) - | otherwise = (bndr', rhs') where - bndr' = mkVanillaGlobal name' ty' idinfo' + bndr' = mkGlobalId details name' ty' idinfo' + -- Preserve the GlobalIdDetails of existing global-ids + details = case globalIdDetails bndr of + NotGlobalId -> VanillaGlobal + old_details -> old_details ty' = tidyTopType (idType bndr) rhs' = tidyExpr rhs_tidy_env rhs idinfo = idInfo bndr @@ -817,7 +802,7 @@ tidyWorker _tidy_env _show_unfold NoWorker = NoWorker tidyWorker tidy_env show_unfold (HasWorker work_id wrap_arity) | show_unfold = HasWorker (tidyVarOcc tidy_env work_id) wrap_arity - | otherwise = WARN( True, ppr work_id ) NoWorker + | otherwise = NoWorker -- NB: do *not* expose the worker if show_unfold is off, -- because that means this thing is a loop breaker or -- marked NOINLINE or something like that @@ -825,8 +810,12 @@ tidyWorker tidy_env show_unfold (HasWorker work_id wrap_arity) -- then you can make the simplifier go into an infinite loop, because -- in effect the unfolding is exposed. See Trac #1709 -- - -- Mind you, it probably should not be w/w'd in the first place; - -- hence the WARN + -- You might think that if show_unfold is False, then the thing should + -- not be w/w'd in the first place. But a legitimate reason is this: + -- the function returns bottom + -- In this case, show_unfold will be false (we don't expose unfoldings + -- for bottoming functions), but we might still have a worker/wrapper + -- split (see Note [Worker-wrapper for bottoming functions] in WorkWrap.lhs \end{code} %************************************************************************