X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FsimplCore%2FSimplCore.lhs;h=09f3e679fd28a3755ebd59f67779c9f888b42e1f;hb=29ca2190efa2284e767949b0fab4e00a68db59bd;hp=a58f126ae8b21b995b923df7b9ad858b5daf4581;hpb=68afb16743cafd5b7495771d359891c6dfc5a186;p=ghc-hetmet.git diff --git a/ghc/compiler/simplCore/SimplCore.lhs b/ghc/compiler/simplCore/SimplCore.lhs index a58f126..ec8ed27 100644 --- a/ghc/compiler/simplCore/SimplCore.lhs +++ b/ghc/compiler/simplCore/SimplCore.lhs @@ -1,573 +1,506 @@ % -% (c) The GRASP/AQUA Project, Glasgow University, 1992-1996 +% (c) The GRASP/AQUA Project, Glasgow University, 1992-1998 % \section[SimplCore]{Driver for simplifying @Core@ programs} \begin{code} -#include "HsVersions.h" - -module SimplCore ( core2core ) where +module SimplCore ( core2core, simplifyExpr ) where -import Ubiq{-uitous-} +#include "HsVersions.h" -import AnalFBWW ( analFBWW ) -import Bag ( isEmptyBag, foldBag ) -import BinderInfo ( BinderInfo{-instance Outputable-} ) -import CgCompInfo ( uNFOLDING_CREATION_THRESHOLD, - uNFOLDING_USE_THRESHOLD, - uNFOLDING_OVERRIDE_THRESHOLD, - uNFOLDING_CON_DISCOUNT_WEIGHT +import CmdLineOpts ( CoreToDo(..), SimplifierSwitch(..), + SimplifierMode(..), DynFlags, DynFlag(..), dopt, + dopt_CoreToDo, buildCoreToDo ) -import CmdLineOpts ( CoreToDo(..), SimplifierSwitch(..), switchIsOn, - opt_D_show_passes, - opt_D_simplifier_stats, - opt_D_verbose_core2core, - opt_DoCoreLinting, - opt_FoldrBuildOn, - opt_ReportWhyUnfoldingsDisallowed, - opt_ShowImportSpecs, - opt_UnfoldingCreationThreshold, - opt_UnfoldingOverrideThreshold, - opt_UnfoldingUseThreshold - ) -import CoreLint ( lintCoreBindings ) import CoreSyn -import CoreUnfold -import CoreUtils ( substCoreBindings, manifestlyWHNF ) -import ErrUtils ( ghcExit ) +import TcIface ( loadImportedRules ) +import HscTypes ( HscEnv(..), ModGuts(..), ExternalPackageState(..), + ModDetails(..), HomeModInfo(..), hscEPS ) +import CSE ( cseProgram ) +import Rules ( RuleBase, ruleBaseIds, emptyRuleBase, + extendRuleBaseList, pprRuleBase, ruleCheckProgram ) +import Module ( moduleEnvElts ) +import PprCore ( pprCoreBindings, pprCoreExpr, pprIdRules ) +import OccurAnal ( occurAnalyseBinds, occurAnalyseGlobalExpr ) +import CoreUtils ( coreBindsSize ) +import Simplify ( simplTopBinds, simplExpr ) +import SimplEnv ( SimplEnv, simplBinders, mkSimplEnv, setInScopeSet ) +import SimplMonad +import ErrUtils ( dumpIfSet, dumpIfSet_dyn, showPass ) +import CoreLint ( endPass ) +import VarEnv ( mkInScopeSet ) import FloatIn ( floatInwards ) import FloatOut ( floatOutwards ) -import FoldrBuildWW ( mkFoldrBuildWW ) -import Id ( idType, toplevelishId, idWantsToBeINLINEd, - unfoldingUnfriendlyId, - nullIdEnv, addOneToIdEnv, delOneFromIdEnv, - lookupIdEnv, IdEnv(..), - GenId{-instance Outputable-} - ) -import IdInfo ( mkUnfolding ) +import Id ( idIsFrom, idSpecialisation, setIdSpecialisation ) +import VarSet import LiberateCase ( liberateCase ) -import MagicUFs ( MagicUnfoldingFun ) -import Maybes ( maybeToBool ) -import Outputable ( Outputable(..){-instance * (,) -} ) -import PprCore ( pprCoreBinding, GenCoreExpr{-instance Outputable-} ) -import PprStyle ( PprStyle(..) ) -import PprType ( GenType{-instance Outputable-}, GenTyVar{-ditto-} ) -import Pretty ( ppShow, ppAboves, ppAbove, ppCat, ppStr ) import SAT ( doStaticArgs ) -import SCCauto ( addAutoCostCentres ) -import SimplMonad ( zeroSimplCount, showSimplCount, SimplCount ) -import SimplPgm ( simplifyPgm ) -import SimplVar ( leastItCouldCost ) -import Specialise -import SpecUtils ( pprSpecErrs ) -import StrictAnal ( saWwTopBinds ) -import TyVar ( nullTyVarEnv, GenTyVar{-instance Eq-} ) -import Unique ( Unique{-instance Eq-} ) -import UniqSupply ( splitUniqSupply ) -import Util ( panic{-ToDo:rm-} ) - -#if ! OMIT_DEFORESTER -import Deforest ( deforestProgram ) -import DefUtils ( deforestable ) +import Specialise ( specProgram) +import SpecConstr ( specConstrProgram) +import DmdAnal ( dmdAnalPgm ) +import WorkWrap ( wwTopBinds ) +#ifdef OLD_STRICTNESS +import StrictAnal ( saBinds ) +import CprAnalyse ( cprAnalyse ) #endif -isWrapperFor = panic "SimplCore.isWrapperFor (ToDo)" -isWrapperId = panic "SimplCore.isWrapperId (ToDo)" +import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply ) +import IO ( hPutStr, stderr ) +import Outputable +import List ( partition ) +import Maybes ( orElse ) \end{code} +%************************************************************************ +%* * +\subsection{The driver for the simplifier} +%* * +%************************************************************************ + \begin{code} -core2core :: [CoreToDo] -- spec of what core-to-core passes to do - -> FAST_STRING -- module name (profiling only) - -> PprStyle -- printing style (for debugging only) - -> UniqSupply -- a name supply - -> [TyCon] -- local data tycons and tycon specialisations - -> FiniteMap TyCon [(Bool, [Maybe Type])] - -> [CoreBinding] -- input... - -> IO - ([CoreBinding], -- results: program, plus... - IdEnv UnfoldingDetails, -- unfoldings to be exported from here - SpecialiseData) -- specialisation data - -core2core core_todos module_name ppr_style us local_tycons tycon_specs binds - = if null core_todos then -- very rare, I suspect... - -- well, we still must do some renumbering - return ( - (substCoreBindings nullIdEnv nullTyVarEnv binds us, - nullIdEnv, - init_specdata) - ) - else - (if do_verbose_core2core then - hPutStr stderr "VERBOSE CORE-TO-CORE:\n" - else return ()) >> - - -- better do the main business - foldl_mn do_core_pass - (binds, us, nullIdEnv, init_specdata, zeroSimplCount) - core_todos - >>= \ (processed_binds, _, inline_env, spec_data, simpl_stats) -> - - (if opt_D_simplifier_stats - then hPutStr stderr ("\nSimplifier Stats:\n") - >> - hPutStr stderr (showSimplCount simpl_stats) - >> - hPutStr stderr "\n" - else return () - ) >> - - return (processed_binds, inline_env, spec_data) - where - init_specdata = initSpecData local_tycons tycon_specs - - do_verbose_core2core = opt_D_verbose_core2core - - lib_case_threshold -- ToDo: HACK HACK HACK : FIX ME FIX ME FIX ME - -- Use 4x a known threshold - = case opt_UnfoldingOverrideThreshold of - Nothing -> 4 * uNFOLDING_USE_THRESHOLD - Just xx -> 4 * xx - - ------------- - core_linter = if opt_DoCoreLinting - then lintCoreBindings ppr_style - else ( \ whodunnit spec_done binds -> binds ) - - -------------- - do_core_pass info@(binds, us, inline_env, spec_data, simpl_stats) to_do - = let - (us1, us2) = splitUniqSupply us - in - case to_do of - CoreDoSimplify simpl_sw_chkr - -> _scc_ "CoreSimplify" - begin_pass ("Simplify" ++ if switchIsOn simpl_sw_chkr SimplDoFoldrBuild - then " (foldr/build)" else "") >> - case (simplifyPgm binds simpl_sw_chkr simpl_stats us1) of - (p, it_cnt, simpl_stats2) - -> end_pass False us2 p inline_env spec_data simpl_stats2 - ("Simplify (" ++ show it_cnt ++ ")" - ++ if switchIsOn simpl_sw_chkr SimplDoFoldrBuild - then " foldr/build" else "") - - CoreDoFoldrBuildWorkerWrapper - -> _scc_ "CoreDoFoldrBuildWorkerWrapper" - begin_pass "FBWW" >> - case (mkFoldrBuildWW us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FBWW" } - - CoreDoFoldrBuildWWAnal - -> _scc_ "CoreDoFoldrBuildWWAnal" - begin_pass "AnalFBWW" >> - case (analFBWW binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "AnalFBWW" } - - CoreLiberateCase - -> _scc_ "LiberateCase" - begin_pass "LiberateCase" >> - case (liberateCase lib_case_threshold binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "LiberateCase" } - - CoreDoCalcInlinings1 -- avoid inlinings w/ cost-centres - -> _scc_ "CoreInlinings1" - begin_pass "CalcInlinings" >> - case (calcInlinings False inline_env binds) of { inline_env2 -> - end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" } - - CoreDoCalcInlinings2 -- allow inlinings w/ cost-centres - -> _scc_ "CoreInlinings2" - begin_pass "CalcInlinings" >> - case (calcInlinings True inline_env binds) of { inline_env2 -> - end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" } - - CoreDoFloatInwards - -> _scc_ "FloatInwards" - begin_pass "FloatIn" >> - case (floatInwards binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatIn" } - - CoreDoFullLaziness - -> _scc_ "CoreFloating" - begin_pass "FloatOut" >> - case (floatOutwards us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatOut" } - - CoreDoStaticArgs - -> _scc_ "CoreStaticArgs" - begin_pass "StaticArgs" >> - case (doStaticArgs binds us1) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "StaticArgs" } - -- Binds really should be dependency-analysed for static- - -- arg transformation... Not to worry, they probably are. - -- (I don't think it *dies* if they aren't [WDP 94/04/15]) - - CoreDoStrictness - -> _scc_ "CoreStranal" - begin_pass "StrAnal" >> - case (saWwTopBinds us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "StrAnal" } - - CoreDoSpecialising - -> _scc_ "Specialise" - begin_pass "Specialise" >> - case (specProgram us1 binds spec_data) of { - (p, spec_data2@(SpecData _ spec_noerrs _ _ _ - spec_errs spec_warn spec_tyerrs)) -> - - -- if we got errors, we die straight away - (if not spec_noerrs || - (opt_ShowImportSpecs && not (isEmptyBag spec_warn)) then - hPutStr stderr (ppShow 1000 {-pprCols-} - (pprSpecErrs module_name spec_errs spec_warn spec_tyerrs)) - >> hPutStr stderr "\n" - else - return ()) >> - - (if not spec_noerrs then -- Stop here if specialisation errors occured - ghcExit 1 - else - return ()) >> - - end_pass False us2 p inline_env spec_data2 simpl_stats "Specialise" - } - - CoreDoDeforest -#if OMIT_DEFORESTER - -> error "ERROR: CoreDoDeforest: not built into compiler\n" -#else - -> _scc_ "Deforestation" - begin_pass "Deforestation" >> - case (deforestProgram binds us1) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "Deforestation" } +core2core :: HscEnv + -> ModGuts + -> IO ModGuts + +core2core hsc_env guts + = do + let dflags = hsc_dflags hsc_env + core_todos + | Just todo <- dopt_CoreToDo dflags = todo + | otherwise = buildCoreToDo dflags + + us <- mkSplitUniqSupply 's' + let (cp_us, ru_us) = splitUniqSupply us + + -- COMPUTE THE RULE BASE TO USE + (imp_rule_base, guts') <- prepareRules hsc_env guts ru_us + + -- DO THE BUSINESS + (stats, guts'') <- doCorePasses hsc_env cp_us + (zeroSimplCount dflags) + imp_rule_base guts' core_todos + + dumpIfSet_dyn dflags Opt_D_dump_simpl_stats + "Grand total simplifier statistics" + (pprSimplCount stats) + + return guts'' + + +simplifyExpr :: DynFlags -- includes spec of what core-to-core passes to do + -> CoreExpr + -> IO CoreExpr +-- simplifyExpr is called by the driver to simplify an +-- expression typed in at the interactive prompt +simplifyExpr dflags expr + = do { + ; showPass dflags "Simplify" + + ; us <- mkSplitUniqSupply 's' + + ; let (expr', _counts) = initSmpl dflags us $ + simplExprGently gentleSimplEnv expr + + ; dumpIfSet_dyn dflags Opt_D_dump_simpl "Simplified expression" + (pprCoreExpr expr') + + ; return expr' + } + +gentleSimplEnv :: SimplEnv +gentleSimplEnv = mkSimplEnv SimplGently + (isAmongSimpl []) + emptyRuleBase + +doCorePasses :: HscEnv + -> UniqSupply -- uniques + -> SimplCount -- simplifier stats + -> RuleBase -- the main rule base + -> ModGuts -- local binds in (with rules attached) + -> [CoreToDo] -- which passes to do + -> IO (SimplCount, ModGuts) + +doCorePasses hsc_env us stats rb guts [] + = return (stats, guts) + +doCorePasses hsc_env us stats rb guts (to_do : to_dos) + = do + let (us1, us2) = splitUniqSupply us + (stats1, rb1, guts1) <- doCorePass to_do hsc_env us1 rb guts + doCorePasses hsc_env us2 (stats `plusSimplCount` stats1) rb1 guts1 to_dos + +doCorePass (CoreDoSimplify mode sws) = _scc_ "Simplify" simplifyPgm mode sws +doCorePass CoreCSE = _scc_ "CommonSubExpr" trBinds cseProgram +doCorePass CoreLiberateCase = _scc_ "LiberateCase" trBinds liberateCase +doCorePass CoreDoFloatInwards = _scc_ "FloatInwards" trBinds floatInwards +doCorePass (CoreDoFloatOutwards f) = _scc_ "FloatOutwards" trBindsU (floatOutwards f) +doCorePass CoreDoStaticArgs = _scc_ "StaticArgs" trBinds doStaticArgs +doCorePass CoreDoStrictness = _scc_ "Stranal" trBinds dmdAnalPgm +doCorePass CoreDoWorkerWrapper = _scc_ "WorkWrap" trBindsU wwTopBinds +doCorePass CoreDoSpecialising = _scc_ "Specialise" trBindsU specProgram +doCorePass CoreDoSpecConstr = _scc_ "SpecConstr" trBindsU specConstrProgram +doCorePass CoreDoGlomBinds = trBinds glomBinds +doCorePass CoreDoPrintCore = observe printCore +doCorePass (CoreDoRuleCheck phase pat) = observe (ruleCheck phase pat) +doCorePass CoreDoNothing = observe (\ _ _ -> return ()) +#ifdef OLD_STRICTNESS +doCorePass CoreDoOldStrictness = _scc_ "OldStrictness" trBinds doOldStrictness #endif - CoreDoAutoCostCentres - -> _scc_ "AutoSCCs" - begin_pass "AutoSCCs" >> - case (addAutoCostCentres module_name binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "AutoSCCs" } - - CoreDoPrintCore -- print result of last pass - -> end_pass True us2 binds inline_env spec_data simpl_stats "Print" - - - ------------------------------------------------- - - begin_pass - = if opt_D_show_passes - then \ what -> hPutStr stderr ("*** Core2Core: "++what++"\n") - else \ what -> return () - - end_pass print us2 binds2 inline_env2 - spec_data2@(SpecData spec_done _ _ _ _ _ _ _) - simpl_stats2 what - = -- report verbosely, if required - (if (do_verbose_core2core && not print) || - (print && not do_verbose_core2core) - then - hPutStr stderr ("\n*** "++what++":\n") - >> - hPutStr stderr (ppShow 1000 - (ppAboves (map (pprCoreBinding ppr_style) binds2))) - >> - hPutStr stderr "\n" - else - return ()) >> - let - linted_binds = core_linter what spec_done binds2 - in - return - (linted_binds, -- processed binds, possibly run thru CoreLint - us2, -- UniqueSupply for the next guy - inline_env2, -- possibly-updated inline env - spec_data2, -- possibly-updated specialisation info - simpl_stats2 -- accumulated simplifier stats - ) - --- here so it can be inlined... -foldl_mn f z [] = return z -foldl_mn f z (x:xs) = f z x >>= \ zz -> - foldl_mn f zz xs -\end{code} +#ifdef OLD_STRICTNESS +doOldStrictness dfs binds + = do binds1 <- saBinds dfs binds + binds2 <- cprAnalyse dfs binds1 + return binds2 +#endif ---- ToDo: maybe move elsewhere --- +printCore _ binds = dumpIfSet True "Print Core" (pprCoreBindings binds) -For top-level, exported binders that either (a)~have been INLINEd by -the programmer or (b)~are sufficiently ``simple'' that they should be -inlined, we want to record this info in a suitable IdEnv. +ruleCheck phase pat dflags binds = do showPass dflags "RuleCheck" + printDump (ruleCheckProgram phase pat binds) + +-- Most passes return no stats and don't change rules +trBinds :: (DynFlags -> [CoreBind] -> IO [CoreBind]) + -> HscEnv -> UniqSupply -> RuleBase -> ModGuts + -> IO (SimplCount, RuleBase, ModGuts) +trBinds do_pass hsc_env us rb guts + = do { binds' <- do_pass dflags (mg_binds guts) + ; return (zeroSimplCount dflags, rb, guts { mg_binds = binds' }) } + where + dflags = hsc_dflags hsc_env + +trBindsU :: (DynFlags -> UniqSupply -> [CoreBind] -> IO [CoreBind]) + -> HscEnv -> UniqSupply -> RuleBase -> ModGuts + -> IO (SimplCount, RuleBase, ModGuts) +trBindsU do_pass hsc_env us rb guts + = do { binds' <- do_pass dflags us (mg_binds guts) + ; return (zeroSimplCount dflags, rb, guts { mg_binds = binds' }) } + where + dflags = hsc_dflags hsc_env + +-- Observer passes just peek; don't modify the bindings at all +observe :: (DynFlags -> [CoreBind] -> IO a) + -> HscEnv -> UniqSupply -> RuleBase -> ModGuts + -> IO (SimplCount, RuleBase, ModGuts) +observe do_pass hsc_env us rb guts + = do { binds <- do_pass dflags (mg_binds guts) + ; return (zeroSimplCount dflags, rb, guts) } + where + dflags = hsc_dflags hsc_env +\end{code} -But: if something has a ``wrapper unfolding,'' we do NOT automatically -give it a regular unfolding (exception below). We usually assume its -worker will get a ``regular'' unfolding. We can then treat these two -levels of unfolding separately (we tend to be very friendly towards -wrapper unfoldings, for example), giving more fine-tuned control. -The exception is: If the ``regular unfolding'' mentions no other -global Ids (i.e., it's all PrimOps and cases and local Ids) then we -assume it must be really good and we take it anyway. -We also need to check that everything in the RHS (values and types) -will be visible on the other side of an interface, too. +%************************************************************************ +%* * +\subsection{Dealing with rules} +%* * +%************************************************************************ + +-- prepareLocalRuleBase takes the CoreBinds and rules defined in this module. +-- It attaches those rules that are for local Ids to their binders, and +-- returns the remainder attached to Ids in an IdSet. \begin{code} -calcInlinings :: Bool -- True => inlinings with _scc_s are OK - -> IdEnv UnfoldingDetails - -> [CoreBinding] - -> IdEnv UnfoldingDetails - -calcInlinings scc_s_OK inline_env_so_far top_binds - = let - result = foldl calci inline_env_so_far top_binds - in - --pprTrace "inline env:\n" (ppAboves (map pp_item (getIdEnvMapping result))) - result - where - pp_item (binder, details) - = ppCat [ppr PprDebug binder, ppStr "=>", pp_det details] - where - pp_det NoUnfoldingDetails = ppStr "_N_" ---LATER: pp_det (IWantToBeINLINEd _) = ppStr "INLINE" - pp_det (GenForm _ _ expr guide) - = ppAbove (ppr PprDebug guide) (ppr PprDebug expr) - pp_det other = ppStr "???" - - ------------ - my_trace = if opt_ReportWhyUnfoldingsDisallowed - then trace - else \ msg stuff -> stuff - - (unfolding_creation_threshold, explicit_creation_threshold) - = case opt_UnfoldingCreationThreshold of - Nothing -> (uNFOLDING_CREATION_THRESHOLD, False) - Just xx -> (xx, True) - - unfold_use_threshold - = case opt_UnfoldingUseThreshold of - Nothing -> uNFOLDING_USE_THRESHOLD - Just xx -> xx - - unfold_override_threshold - = case opt_UnfoldingOverrideThreshold of - Nothing -> uNFOLDING_OVERRIDE_THRESHOLD - Just xx -> xx - - con_discount_weight = uNFOLDING_CON_DISCOUNT_WEIGHT - - calci inline_env (Rec pairs) - = foldl (calc True{-recursive-}) inline_env pairs - - calci inline_env bind@(NonRec binder rhs) - = calc False{-not recursive-} inline_env (binder, rhs) - - --------------------------------------- - - calc is_recursive inline_env (binder, rhs) - | not (toplevelishId binder) - = --pprTrace "giving up on not top-level:" (ppr PprDebug binder) - ignominious_defeat - - | rhs_mentions_an_unmentionable - || (not explicit_INLINE_requested - && (rhs_looks_like_a_caf || guidance_says_don't || guidance_size_too_big)) - = let - my_my_trace - = if explicit_INLINE_requested - && not (isWrapperId binder) -- these always claim to be INLINEd - && not have_inlining_already - then trace -- we'd better have a look... - else my_trace - - which = if scc_s_OK then " (late):" else " (early):" - in - my_my_trace ("unfolding disallowed for"++which++(ppShow 80 (ppr PprDebug binder))) ( - ignominious_defeat - ) - - | rhs `isWrapperFor` binder - -- Don't add an explicit "unfolding"; let the worker/wrapper - -- stuff do its thing. INLINE things don't get w/w'd, so - -- they will be OK. - = ignominious_defeat - -#if ! OMIT_DEFORESTER - -- For the deforester: bypass the barbed wire for recursive - -- functions that want to be inlined and are tagged deforestable - -- by the user, allowing these things to be communicated - -- across module boundaries. - - | is_recursive && - explicit_INLINE_requested && - deforestable binder && - scc_s_OK -- hack, only get them in - -- calc_inlinings2 - = glorious_success UnfoldAlways +prepareRules :: HscEnv + -> ModGuts + -> UniqSupply + -> IO (RuleBase, -- Rule base for imported things, incl + -- (a) rules defined in this module (orphans) + -- (b) rules from other packages + -- (c) rules from other modules in home package + ModGuts) -- Modified fields are + -- (a) Bindings have rules attached, + -- (b) Rules are now just orphan rules + +prepareRules hsc_env@(HscEnv { hsc_dflags = dflags, hsc_HPT = hpt }) + guts@(ModGuts { mg_binds = binds, mg_rules = local_rules }) + us + = do { eps <- hscEPS hsc_env + + ; let -- Simplify the local rules; boringly, we need to make an in-scope set + -- from the local binders, to avoid warnings from Simplify.simplVar + local_ids = mkInScopeSet (mkVarSet (bindersOfBinds binds)) + env = setInScopeSet gentleSimplEnv local_ids + (better_rules,_) = initSmpl dflags us (mapSmpl (simplRule env) local_rules) + + (orphan_rules, rules_for_locals) = partition isOrphanRule better_rules + -- Get the rules for locally-defined Ids out of the RuleBase + -- If we miss any rules for Ids defined here, then we end up + -- giving the local decl a new Unique (because the in-scope-set is (hackily) the + -- same as the non-local-rule-id set, so the Id looks as if it's in scope + -- and hence should be cloned), and now the binding for the class method + -- doesn't have the same Unique as the one in the Class and the tc-env + -- Example: class Foo a where + -- op :: a -> a + -- {-# RULES "op" op x = x #-} + + -- NB: we assume that the imported rules dont include + -- rules for Ids in this module; if there is, the above bad things may happen + + pkg_rule_base = eps_rule_base eps + hpt_rule_base = foldl add_rules pkg_rule_base (moduleEnvElts hpt) + imp_rule_base = extendRuleBaseList hpt_rule_base orphan_rules + + -- Update the binders in the local bindings with the lcoal rules + -- Update the binders of top-level bindings by + -- attaching the rules for each locally-defined Id to that Id. + -- + -- Reason + -- - It makes the rules easier to look up + -- - It means that transformation rules and specialisations for + -- locally defined Ids are handled uniformly + -- - It keeps alive things that are referred to only from a rule + -- (the occurrence analyser knows about rules attached to Ids) + -- - It makes sure that, when we apply a rule, the free vars + -- of the RHS are more likely to be in scope + -- - The imported rules are carried in the in-scope set + -- which is extended on each iteration by the new wave of + -- local binders; any rules which aren't on the binding will + -- thereby get dropped + local_rule_base = extendRuleBaseList emptyRuleBase rules_for_locals + binds_w_rules = updateBinders local_rule_base binds + + ; dumpIfSet_dyn dflags Opt_D_dump_rules "Transformation rules" + (vcat [text "Local rules", pprIdRules better_rules, + text "", + text "Imported rules", pprRuleBase imp_rule_base]) + +#ifdef DEBUG + ; let bad_rules = filter (idIsFrom (mg_module guts)) + (varSetElems (ruleBaseIds imp_rule_base)) + ; WARN( not (null bad_rules), ppr bad_rules ) return () #endif + ; return (imp_rule_base, guts { mg_binds = binds_w_rules, mg_rules = orphan_rules }) + } + where + add_rules rule_base mod_info = extendRuleBaseList rule_base (md_rules (hm_details mod_info)) - | is_recursive && not rhs_looks_like_a_data_val - -- The only recursive defns we are prepared to tolerate at the - -- moment is top-level very-obviously-a-data-value ones. - -- We *need* these for dictionaries to be exported! - = --pprTrace "giving up on rec:" (ppr PprDebug binder) - ignominious_defeat +updateBinders :: RuleBase -> [CoreBind] -> [CoreBind] +updateBinders rule_base binds + = map update_bndrs binds + where + rule_ids = ruleBaseIds rule_base - -- Not really interested unless it's exported, but doing it - -- this way (not worrying about export-ness) gets us all the - -- workers/specs, etc., too; which we will need for generating - -- interfaces. We are also not interested if this binder is - -- in the environment we already have (perhaps from a previous - -- run of calcInlinings -- "earlier" is presumed to mean - -- "better"). + update_bndrs (NonRec b r) = NonRec (update_bndr b) r + update_bndrs (Rec prs) = Rec [(update_bndr b, r) | (b,r) <- prs] - | explicit_INLINE_requested - = glorious_success UnfoldAlways + update_bndr bndr = case lookupVarSet rule_ids bndr of + Nothing -> bndr + Just id -> bndr `setIdSpecialisation` idSpecialisation id +\end{code} - | otherwise - = glorious_success guidance - where - guidance - = calcUnfoldingGuidance scc_s_OK max_out_threshold rhs - where - max_out_threshold = if explicit_INLINE_requested - then 100000 -- you asked for it, you got it - else unfolding_creation_threshold - - guidance_size - = case guidance of - UnfoldAlways -> 0 -- *extremely* small - EssentialUnfolding -> 0 -- ditto - UnfoldIfGoodArgs _ _ _ size -> size - - guidance_says_don't = case guidance of { UnfoldNever -> True; _ -> False } - - guidance_size_too_big - -- Does the guidance suggest that this unfolding will - -- be of no use *no matter* the arguments given to it? - -- Could be more sophisticated... - = case guidance of - UnfoldAlways -> False - EssentialUnfolding -> False - UnfoldIfGoodArgs _ no_val_args arg_info_vec size - - -> if explicit_creation_threshold then - False -- user set threshold; don't second-guess... - - else if no_val_args == 0 && rhs_looks_like_a_data_val then - False -- we'd like a top-level data constr to be - -- visible even if it is never unfolded - else - let - cost - = leastItCouldCost con_discount_weight size no_val_args - arg_info_vec rhs_arg_tys - in --- (if (unfold_use_threshold < cost) then (pprTrace "cost:" (ppInt cost)) else \x->x ) ( - unfold_use_threshold < cost --- ) - - - rhs_looks_like_a_caf = not (manifestlyWHNF rhs) - - rhs_looks_like_a_data_val - = case (collectBinders rhs) of - (_, _, [], Con _ _) -> True - other -> False - - rhs_arg_tys - = case (collectBinders rhs) of - (_, _, val_binders, _) -> map idType val_binders - - (mentioned_ids, _, _, mentions_litlit) - = mentionedInUnfolding (\x -> x) rhs - - rhs_mentions_an_unmentionable - = foldBag (||) unfoldingUnfriendlyId False mentioned_ids - || mentions_litlit - -- ToDo: probably need to chk tycons/classes... - - mentions_no_other_ids = isEmptyBag mentioned_ids - - explicit_INLINE_requested - -- did it come from a user {-# INLINE ... #-}? - -- (Warning: must avoid including wrappers.) - = idWantsToBeINLINEd binder - && not (rhs `isWrapperFor` binder) - - have_inlining_already = maybeToBool (lookupIdEnv inline_env binder) - - ignominious_defeat = inline_env -- just give back what we got - - {- - "glorious_success" is ours if we've found a suitable unfolding. - - But we check for a couple of fine points. - - (1) If this Id already has an inlining in the inline_env, - we don't automatically take it -- the earlier one is - "likely" to be better. - - But if the new one doesn't mention any other global - Ids, and it's pretty small (< UnfoldingOverrideThreshold), - then we take the chance that the new one *is* better. - - (2) If we have an Id w/ a worker/wrapper split (with - an unfolding for the wrapper), we tend to want to keep - it -- and *nuke* any inlining that we conjured up - earlier. - - But, again, if this unfolding doesn't mention any - other global Ids (and small enough), then it is - probably better than the worker/wrappery, so we take - it. - -} - glorious_success guidance - = let - new_env = addOneToIdEnv inline_env binder (mkUnfolding guidance rhs) - - foldr_building = opt_FoldrBuildOn - in - if (not have_inlining_already) then - -- Not in env: we take it no matter what - -- NB: we could check for worker/wrapper-ness, - -- but the truth is we probably haven't run - -- the strictness analyser yet. - new_env - - else if explicit_INLINE_requested then - -- If it was a user INLINE, then we know it's already - -- in the inline_env; we stick with what we already - -- have. - --pprTrace "giving up on INLINE:" (ppr PprDebug binder) - ignominious_defeat - - else if isWrapperId binder then - -- It's in the env, but we have since worker-wrapperised; - -- we either take this new one (because it's so good), - -- or we *undo* the one in the inline_env, so the - -- wrapper-inlining will take over. - - if mentions_no_other_ids {- *** && size <= unfold_override_threshold -} then - new_env - else - delOneFromIdEnv inline_env binder - - else - -- It's in the env, nothing to do w/ worker wrapper; - -- we'll take it if it is better. - - if not foldr_building -- ANDY hates us... (see below) - && mentions_no_other_ids - && guidance_size <= unfold_override_threshold then - new_env - else - --pprTrace "giving up on final hurdle:" (ppCat [ppr PprDebug binder, ppInt guidance_size, ppInt unfold_override_threshold]) - ignominious_defeat -- and at the last hurdle, too! +We must do some gentle simplification on the template (but not the RHS) +of each rule. The case that forced me to add this was the fold/build rule, +which without simplification looked like: + fold k z (build (/\a. g a)) ==> ... +This doesn't match unless you do eta reduction on the build argument. + +\begin{code} +simplRule env rule@(IdCoreRule id _ (BuiltinRule _ _)) + = returnSmpl rule +simplRule env (IdCoreRule id is_orph (Rule act name bndrs args rhs)) + = simplBinders env bndrs `thenSmpl` \ (env, bndrs') -> + mapSmpl (simplExprGently env) args `thenSmpl` \ args' -> + simplExprGently env rhs `thenSmpl` \ rhs' -> + returnSmpl (IdCoreRule id is_orph (Rule act name bndrs' args' rhs')) + +-- It's important that simplExprGently does eta reduction. +-- For example, in a rule like: +-- augment g (build h) +-- we do not want to get +-- augment (\a. g a) (build h) +-- otherwise we don't match when given an argument like +-- (\a. h a a) +-- +-- The simplifier does indeed do eta reduction (it's in +-- Simplify.completeLam) but only if -O is on. +\end{code} + +\begin{code} +simplExprGently :: SimplEnv -> CoreExpr -> SimplM CoreExpr +-- Simplifies an expression +-- does occurrence analysis, then simplification +-- and repeats (twice currently) because one pass +-- alone leaves tons of crud. +-- Used (a) for user expressions typed in at the interactive prompt +-- (b) the LHS and RHS of a RULE +-- +-- The name 'Gently' suggests that the SimplifierMode is SimplGently, +-- and in fact that is so.... but the 'Gently' in simplExprGently doesn't +-- enforce that; it just simplifies the expression twice + +simplExprGently env expr + = simplExpr env (occurAnalyseGlobalExpr expr) `thenSmpl` \ expr1 -> + simplExpr env (occurAnalyseGlobalExpr expr1) +\end{code} + + +%************************************************************************ +%* * +\subsection{Glomming} +%* * +%************************************************************************ + +\begin{code} +glomBinds :: DynFlags -> [CoreBind] -> IO [CoreBind] +-- Glom all binds together in one Rec, in case any +-- transformations have introduced any new dependencies +-- +-- NB: the global invariant is this: +-- *** the top level bindings are never cloned, and are always unique *** +-- +-- We sort them into dependency order, but applying transformation rules may +-- make something at the top refer to something at the bottom: +-- f = \x -> p (q x) +-- h = \y -> 3 +-- +-- RULE: p (q x) = h x +-- +-- Applying this rule makes f refer to h, +-- although it doesn't appear to in the source program. +-- This pass lets us control where it happens. +-- +-- NOTICE that this cannot happen for rules whose head is a locally-defined +-- function. It only happens for rules whose head is an imported function +-- (p in the example above). So, for example, the rule had been +-- RULE: f (p x) = h x +-- then the rule for f would be attached to f itself (in its IdInfo) +-- by prepareLocalRuleBase and h would be regarded by the occurrency +-- analyser as free in f. + +glomBinds dflags binds + = do { showPass dflags "GlomBinds" ; + let { recd_binds = [Rec (flattenBinds binds)] } ; + return recd_binds } + -- Not much point in printing the result... + -- just consumes output bandwidth \end{code} -ANDY, on the hatred of the check above; why obliterate it? Consider - head xs = foldr (\ x _ -> x) (_|_) xs +%************************************************************************ +%* * +\subsection{The driver for the simplifier} +%* * +%************************************************************************ -This then is exported via a pragma. However, -*if* you include the extra code above, you will -export the non-foldr/build version. +\begin{code} +simplifyPgm :: SimplifierMode + -> [SimplifierSwitch] + -> HscEnv + -> UniqSupply + -> RuleBase + -> ModGuts + -> IO (SimplCount, RuleBase, ModGuts) -- New bindings + +simplifyPgm mode switches hsc_env us rule_base guts + = do { + showPass dflags "Simplify"; + + (termination_msg, it_count, counts_out, rule_base', guts') + <- do_iteration us rule_base 1 (zeroSimplCount dflags) guts; + + dumpIfSet (dopt Opt_D_verbose_core2core dflags + && dopt Opt_D_dump_simpl_stats dflags) + "Simplifier statistics" + (vcat [text termination_msg <+> text "after" <+> ppr it_count <+> text "iterations", + text "", + pprSimplCount counts_out]); + + endPass dflags "Simplify" Opt_D_verbose_core2core (mg_binds guts'); + + return (counts_out, rule_base', guts') + } + where + dflags = hsc_dflags hsc_env + phase_info = case mode of + SimplGently -> "gentle" + SimplPhase n -> show n + + sw_chkr = isAmongSimpl switches + max_iterations = intSwitchSet sw_chkr MaxSimplifierIterations `orElse` 2 + + do_iteration us rule_base iteration_no counts guts + -- iteration_no is the number of the iteration we are + -- about to begin, with '1' for the first + | iteration_no > max_iterations -- Stop if we've run out of iterations + = do { +#ifdef DEBUG + if max_iterations > 2 then + hPutStr stderr ("NOTE: Simplifier still going after " ++ + show max_iterations ++ + " iterations; bailing out.\n") + else + return (); +#endif + -- Subtract 1 from iteration_no to get the + -- number of iterations we actually completed + return ("Simplifier baled out", iteration_no - 1, counts, rule_base, guts) + } + + -- Try and force thunks off the binds; significantly reduces + -- space usage, especially with -O. JRS, 000620. + | let sz = coreBindsSize (mg_binds guts) in sz == sz + = do { + -- Occurrence analysis + let { tagged_binds = _scc_ "OccAnal" occurAnalyseBinds (mg_binds guts) } ; + + dumpIfSet_dyn dflags Opt_D_dump_occur_anal "Occurrence analysis" + (pprCoreBindings tagged_binds); + + -- Get any new rules, and extend the rule base + -- (on the side this extends the package rule base in the + -- ExternalPackageTable, ready for the next complation + -- in --make mode) + -- We need to do this regularly, because simplification can + -- poke on IdInfo thunks, which in turn brings in new rules + -- behind the scenes. Otherwise there's a danger we'll simply + -- miss the rules for Ids hidden inside imported inlinings + new_rules <- loadImportedRules hsc_env guts ; + let { rule_base' = extendRuleBaseList rule_base new_rules + ; simpl_env = mkSimplEnv mode sw_chkr rule_base' } ; + -- The new rule base Ids are used to initialise + -- the in-scope set. That way, the simplifier will change any + -- occurrences of the imported id to the one in the imported_rule_ids + -- set, which are decorated with their rules. + + -- Simplify the program + -- We do this with a *case* not a *let* because lazy pattern + -- matching bit us with bad space leak! + -- With a let, we ended up with + -- let + -- t = initSmpl ... + -- counts' = snd t + -- in + -- case t of {(_,counts') -> if counts'=0 then ... } + -- So the conditional didn't force counts', because the + -- selection got duplicated. Sigh! + case initSmpl dflags us1 (simplTopBinds simpl_env tagged_binds) of { + (binds', counts') -> do { + + let { guts' = guts { mg_binds = binds' } + ; all_counts = counts `plusSimplCount` counts' + ; herald = "Simplifier phase " ++ phase_info ++ + ", iteration " ++ show iteration_no ++ + " out of " ++ show max_iterations + } ; + + -- Stop if nothing happened; don't dump output + if isZeroSimplCount counts' then + return ("Simplifier reached fixed point", iteration_no, + all_counts, rule_base', guts') + else do { + + -- Dump the result of this iteration + dumpIfSet_dyn dflags Opt_D_dump_simpl_iterations herald + (pprSimplCount counts') ; + + endPass dflags herald Opt_D_dump_simpl_iterations binds' ; + + -- Loop + do_iteration us2 rule_base' (iteration_no + 1) all_counts guts' + } } } } + where + (us1, us2) = splitUniqSupply us +\end{code}