X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FsimplCore%2FSimplCore.lhs;h=be781e6d22a6b1a5e593fa071ded59eede5fc47e;hb=867d096a2d598791d13d85c20bf37d0f4174a667;hp=5ed34a4b712030a2f425c012acd768262df0cada;hpb=c605b86323cca9b8c8b5eed6dca715e6b87f9d65;p=ghc-hetmet.git diff --git a/ghc/compiler/simplCore/SimplCore.lhs b/ghc/compiler/simplCore/SimplCore.lhs index 5ed34a4..be781e6 100644 --- a/ghc/compiler/simplCore/SimplCore.lhs +++ b/ghc/compiler/simplCore/SimplCore.lhs @@ -8,19 +8,24 @@ module SimplCore ( core2core, simplifyExpr ) where #include "HsVersions.h" -import CmdLineOpts ( CoreToDo(..), SimplifierSwitch(..), SimplifierMode(..), - DynFlags, DynFlag(..), dopt, dopt_CoreToDo +import CmdLineOpts ( CoreToDo(..), SimplifierSwitch(..), + SimplifierMode(..), DynFlags, DynFlag(..), dopt, + dopt_CoreToDo ) import CoreSyn import CoreFVs ( ruleRhsFreeVars ) -import HscTypes ( PersistentCompilerState(..), - PackageRuleBase, HomeSymbolTable, IsExported, ModDetails(..) +import HscTypes ( HscEnv(..), GhciMode(..), + ModGuts(..), ModGuts, Avails, availsToNameSet, + PackageRuleBase, HomePackageTable, ModDetails(..), + HomeModInfo(..) ) import CSE ( cseProgram ) import Rules ( RuleBase, emptyRuleBase, ruleBaseFVs, ruleBaseIds, extendRuleBaseList, addRuleBaseFVs, pprRuleBase, ruleCheckProgram ) import Module ( moduleEnvElts ) +import Name ( Name, isExternalName ) +import NameSet ( elemNameSet ) import PprCore ( pprCoreBindings, pprCoreExpr ) import OccurAnal ( occurAnalyseBinds, occurAnalyseGlobalExpr ) import CoreUtils ( coreBindsSize ) @@ -31,17 +36,18 @@ import ErrUtils ( dumpIfSet, dumpIfSet_dyn, showPass ) import CoreLint ( endPass ) import FloatIn ( floatInwards ) import FloatOut ( floatOutwards ) -import Id ( idName, setIdLocalExported, isImplicitId ) +import Id ( idName, setIdLocalExported ) import VarSet import LiberateCase ( liberateCase ) import SAT ( doStaticArgs ) import Specialise ( specProgram) import SpecConstr ( specConstrProgram) -import UsageSPInf ( doUsageSPInf ) -import StrictAnal ( saBinds ) import DmdAnal ( dmdAnalPgm ) import WorkWrap ( wwTopBinds ) +#ifdef OLD_STRICTNESS +import StrictAnal ( saBinds ) import CprAnalyse ( cprAnalyse ) +#endif import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply ) import IO ( hPutStr, stderr ) @@ -58,29 +64,31 @@ import List ( partition ) %************************************************************************ \begin{code} -core2core :: DynFlags -- includes spec of what core-to-core passes to do - -> PersistentCompilerState - -> HomeSymbolTable - -> IsExported - -> ModDetails - -> IO ModDetails - -core2core dflags pcs hst is_exported - mod_details@(ModDetails { md_binds = binds_in, md_rules = rules_in }) +core2core :: HscEnv + -> PackageRuleBase + -> ModGuts + -> IO ModGuts + +core2core hsc_env pkg_rule_base + mod_impl@(ModGuts { mg_exports = exports, + mg_binds = binds_in, + mg_rules = rules_in }) = do - let core_todos = dopt_CoreToDo dflags - let pkg_rule_base = pcs_rules pcs -- Rule-base accumulated from imported packages - + let dflags = hsc_dflags hsc_env + hpt = hsc_HPT hsc_env + ghci_mode = hsc_mode hsc_env + core_todos = dopt_CoreToDo dflags us <- mkSplitUniqSupply 's' let (cp_us, ru_us) = splitUniqSupply us -- COMPUTE THE RULE BASE TO USE (rule_base, local_rule_ids, orphan_rules, rule_rhs_fvs) - <- prepareRules dflags pkg_rule_base hst ru_us binds_in rules_in + <- prepareRules dflags pkg_rule_base hpt ru_us binds_in rules_in -- PREPARE THE BINDINGS - let binds1 = updateBinders local_rule_ids rule_rhs_fvs is_exported binds_in + let binds1 = updateBinders ghci_mode local_rule_ids + rule_rhs_fvs exports binds_in -- DO THE BUSINESS (stats, processed_binds) @@ -93,23 +101,21 @@ core2core dflags pcs hst is_exported -- Return results -- We only return local orphan rules, i.e., local rules not attached to an Id -- The bindings cotain more rules, embedded in the Ids - return (mod_details { md_binds = processed_binds, md_rules = orphan_rules}) + return (mod_impl { mg_binds = processed_binds, mg_rules = orphan_rules}) simplifyExpr :: DynFlags -- includes spec of what core-to-core passes to do - -> PersistentCompilerState - -> HomeSymbolTable -> CoreExpr -> IO CoreExpr -- simplifyExpr is called by the driver to simplify an -- expression typed in at the interactive prompt -simplifyExpr dflags pcs hst expr +simplifyExpr dflags expr = do { ; showPass dflags "Simplify" ; us <- mkSplitUniqSupply 's' - ; let env = emptySimplEnv (SimplPhase 0) [] emptyVarSet + ; let env = emptySimplEnv SimplGently [] emptyVarSet (expr', _counts) = initSmpl dflags us (simplExprGently env expr) ; dumpIfSet_dyn dflags Opt_D_dump_simpl "Simplified expression" @@ -151,20 +157,19 @@ doCorePass dfs rb us binds (CoreDoFloatOutwards f) doCorePass dfs rb us binds CoreDoStaticArgs = _scc_ "StaticArgs" noStats dfs (doStaticArgs us binds) doCorePass dfs rb us binds CoreDoStrictness - = _scc_ "Stranal" noStats dfs (do { binds1 <- saBinds dfs binds ; - dmdAnalPgm dfs binds1 }) + = _scc_ "Stranal" noStats dfs (dmdAnalPgm dfs binds) doCorePass dfs rb us binds CoreDoWorkerWrapper = _scc_ "WorkWrap" noStats dfs (wwTopBinds dfs us binds) doCorePass dfs rb us binds CoreDoSpecialising = _scc_ "Specialise" noStats dfs (specProgram dfs us binds) doCorePass dfs rb us binds CoreDoSpecConstr = _scc_ "SpecConstr" noStats dfs (specConstrProgram dfs us binds) -doCorePass dfs rb us binds CoreDoCPResult - = _scc_ "CPResult" noStats dfs (cprAnalyse dfs binds) +#ifdef OLD_STRICTNESS +doCorePass dfs rb us binds CoreDoOldStrictness + = _scc_ "OldStrictness" noStats dfs (doOldStrictness dfs binds) +#endif doCorePass dfs rb us binds CoreDoPrintCore = _scc_ "PrintCore" noStats dfs (printCore binds) -doCorePass dfs rb us binds CoreDoUSPInf - = _scc_ "CoreUsageSPInf" noStats dfs (doUsageSPInf dfs us binds) doCorePass dfs rb us binds CoreDoGlomBinds = noStats dfs (glomBinds dfs binds) doCorePass dfs rb us binds (CoreDoRuleCheck phase pat) @@ -172,6 +177,13 @@ doCorePass dfs rb us binds (CoreDoRuleCheck phase pat) doCorePass dfs rb us binds CoreDoNothing = noStats dfs (return binds) +#ifdef OLD_STRICTNESS +doOldStrictness dfs binds + = do binds1 <- saBinds dfs binds + binds2 <- cprAnalyse dfs binds1 + return binds2 +#endif + printCore binds = do dumpIfSet True "Print Core" (pprCoreBindings binds) return binds @@ -202,7 +214,7 @@ noStats dfs thing = do { binds <- thing; return (zeroSimplCount dfs, binds) } -- so that the opportunity to apply the rule isn't lost too soon \begin{code} -prepareRules :: DynFlags -> PackageRuleBase -> HomeSymbolTable +prepareRules :: DynFlags -> PackageRuleBase -> HomePackageTable -> UniqSupply -> [CoreBind] -> [IdCoreRule] -- Local rules @@ -211,7 +223,7 @@ prepareRules :: DynFlags -> PackageRuleBase -> HomeSymbolTable [IdCoreRule], -- Orphan rules IdSet) -- RHS free vars of all rules -prepareRules dflags pkg_rule_base hst us binds local_rules +prepareRules dflags pkg_rule_base hpt us binds local_rules = do { let env = emptySimplEnv SimplGently [] local_ids (better_rules,_) = initSmpl dflags us (mapSmpl (simplRule env) local_rules) @@ -229,7 +241,7 @@ prepareRules dflags pkg_rule_base hst us binds local_rules rule_rhs_fvs = unionVarSets (map (ruleRhsFreeVars . snd) better_rules) local_rule_base = extendRuleBaseList emptyRuleBase local_rules local_rule_ids = ruleBaseIds local_rule_base -- Local Ids with rules attached - imp_rule_base = foldl add_rules pkg_rule_base (moduleEnvElts hst) + imp_rule_base = foldl add_rules pkg_rule_base (moduleEnvElts hpt) rule_base = extendRuleBaseList imp_rule_base orphan_rules final_rule_base = addRuleBaseFVs rule_base (ruleBaseFVs local_rule_base) -- The last step black-lists the free vars of local rules too @@ -242,22 +254,27 @@ prepareRules dflags pkg_rule_base hst us binds local_rules ; return (final_rule_base, local_rule_ids, orphan_rules, rule_rhs_fvs) } where - add_rules rule_base mds = extendRuleBaseList rule_base (md_rules mds) + add_rules rule_base mod_info = extendRuleBaseList rule_base (md_rules (hm_details mod_info)) -- Boringly, we need to gather the in-scope set. local_ids = foldr (unionVarSet . mkVarSet . bindersOf) emptyVarSet binds -updateBinders :: IdSet -- Locally defined ids with their Rules attached +updateBinders :: GhciMode + -> IdSet -- Locally defined ids with their Rules attached -> IdSet -- Ids free in the RHS of local rules - -> IsExported + -> Avails -- What is exported -> [CoreBind] -> [CoreBind] -- A horrible function -- Update the binders of top-level bindings as follows -- a) Attach the rules for each locally-defined Id to that Id. -- b) Set the no-discard flag if either the Id is exported, --- or it's mentoined in the RHS of a rule +-- or it's mentioned in the RHS of a rule +-- +-- You might wonder why exported Ids aren't already marked as such; +-- it's just because the type checker is rather busy already and +-- I didn't want to pass in yet another mapping. -- -- Reason for (a) -- - It makes the rules easier to look up @@ -275,19 +292,13 @@ updateBinders :: IdSet -- Locally defined ids with their Rules attached -- the rules (maybe we should?), so this substitution would make the rule -- bogus. -updateBinders rule_ids rule_rhs_fvs is_exported binds +updateBinders ghci_mode rule_ids rule_rhs_fvs exports binds = map update_bndrs binds where update_bndrs (NonRec b r) = NonRec (update_bndr b) r update_bndrs (Rec prs) = Rec [(update_bndr b, r) | (b,r) <- prs] update_bndr bndr - | isImplicitId bndr = bndr_with_rules - -- Constructors, selectors; doesn't - -- make sense to call setIdLocalExported - -- They can have rules, though; e.g. - -- class Foo a where { op :: a->a } - -- {-# RULES op x = y #-} | dont_discard bndr = setIdLocalExported bndr_with_rules | otherwise = bndr_with_rules where @@ -295,6 +306,19 @@ updateBinders rule_ids rule_rhs_fvs is_exported binds dont_discard bndr = is_exported (idName bndr) || bndr `elemVarSet` rule_rhs_fvs + + -- In interactive mode, we don't want to discard any top-level + -- entities at all (eg. do not inline them away during + -- simplification), and retain them all in the TypeEnv so they are + -- available from the command line. + -- + -- isExternalName separates the user-defined top-level names from those + -- introduced by the type checker. + is_exported :: Name -> Bool + is_exported | ghci_mode == Interactive = isExternalName + | otherwise = (`elemNameSet` export_fvs) + + export_fvs = availsToNameSet exports \end{code} @@ -333,6 +357,11 @@ simplExprGently :: SimplEnv -> CoreExpr -> SimplM CoreExpr -- 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) @@ -426,6 +455,23 @@ simplifyPgm dflags rule_base max_iterations = intSwitchSet sw_chkr MaxSimplifierIterations `orElse` 2 iteration us iteration_no counts binds + -- 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, binds) + } + -- Try and force thunks off the binds; significantly reduces -- space usage, especially with -O. JRS, 000620. | let sz = coreBindsSize binds in sz == sz @@ -444,7 +490,7 @@ simplifyPgm dflags rule_base -- t = initSmpl ... -- counts' = snd t -- in - -- case t of {(_,counts') -> if counts'=0 then ... + -- 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 { @@ -467,27 +513,12 @@ simplifyPgm dflags rule_base -- Dump the result of this iteration dumpIfSet_dyn dflags Opt_D_dump_simpl_iterations herald - (pprSimplCount counts') ; + (pprSimplCount counts') ; endPass dflags herald Opt_D_dump_simpl_iterations binds' ; - -- Stop if we've run out of iterations - if iteration_no == max_iterations then - do { -#ifdef DEBUG - if max_iterations > 2 then - hPutStr stderr ("NOTE: Simplifier still going after " ++ - show max_iterations ++ - " iterations; bailing out.\n") - else -#endif - return (); - - return ("Simplifier baled out", iteration_no, all_counts, binds') - } - - -- Else loop - else iteration us2 (iteration_no + 1) all_counts binds' + -- Loop + iteration us2 (iteration_no + 1) all_counts binds' } } } } where (us1, us2) = splitUniqSupply us