X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=ghc%2Fcompiler%2FsimplCore%2FSimplCore.lhs;h=2356d85055d28a0c09ab69397946cbf3f09f4559;hb=731f53de7930c38b5023a871146bd0ec066edf3a;hp=1c99c714a2016c3c2134fed9b3d86cd0bc7a1c77;hpb=7d61cb61daa5e433a0cb85b34b7f0c58b2f961ff;p=ghc-hetmet.git diff --git a/ghc/compiler/simplCore/SimplCore.lhs b/ghc/compiler/simplCore/SimplCore.lhs index 1c99c71..2356d85 100644 --- a/ghc/compiler/simplCore/SimplCore.lhs +++ b/ghc/compiler/simplCore/SimplCore.lhs @@ -1,592 +1,589 @@ % -% (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 -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(..), switchIsOn, - opt_D_show_passes, - opt_D_simplifier_stats, +import CmdLineOpts ( CoreToDo(..), SimplifierSwitch(..), + SwitchResult(..), switchIsOn, intSwitchSet, + opt_D_dump_occur_anal, opt_D_dump_rules, + opt_D_dump_simpl_iterations, + opt_D_dump_simpl_stats, + opt_D_dump_simpl, opt_D_dump_rules, opt_D_verbose_core2core, - opt_DoCoreLinting, - opt_FoldrBuildOn, - opt_ReportWhyUnfoldingsDisallowed, - opt_ShowImportSpecs, - opt_UnfoldingCreationThreshold, - opt_UnfoldingOverrideThreshold, - opt_UnfoldingUseThreshold + opt_D_dump_occur_anal, + opt_UsageSPOn, ) -import CoreLint ( lintCoreBindings ) +import CoreLint ( beginPass, endPass ) import CoreSyn +import CSE ( cseProgram ) +import Rules ( RuleBase, ProtoCoreRule(..), pprProtoCoreRule, prepareRuleBase, orphanRule ) import CoreUnfold -import CoreUtils ( substCoreBindings, manifestlyWHNF ) +import PprCore ( pprCoreBindings ) +import OccurAnal ( occurAnalyseBinds ) +import CoreUtils ( exprIsTrivial, coreExprType ) +import Simplify ( simplTopBinds, simplExpr ) +import SimplUtils ( etaCoreExpr, findDefault, simplBinders ) +import SimplMonad +import Const ( Con(..), Literal(..), literalType, mkMachInt ) +import ErrUtils ( dumpIfSet ) import FloatIn ( floatInwards ) import FloatOut ( floatOutwards ) -import FoldrBuildWW ( mkFoldrBuildWW ) -import Id ( idType, toplevelishId, idWantsToBeINLINEd, - unfoldingUnfriendlyId, - nullIdEnv, addOneToIdEnv, delOneFromIdEnv, - lookupIdEnv, IdEnv(..), - GenId{-instance Outputable-} +import Id ( Id, mkSysLocal, mkVanillaId, isBottomingId, + idType, setIdType, idName, idInfo, setIdNoDiscard ) -import IdInfo ( mkUnfolding ) -import LiberateCase ( liberateCase ) -import MagicUFs ( MagicUnfoldingFun ) -import MainMonad ( writeMn, exitMn, thenMn, thenMn_, returnMn, - MainIO(..) +import VarEnv +import VarSet +import Module ( Module ) +import Name ( mkLocalName, tidyOccName, tidyTopName, + NamedThing(..), OccName ) -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 TyCon ( TyCon, isDataTyCon ) +import PrimOp ( PrimOp(..) ) +import PrelInfo ( unpackCStringId, unpackCString2Id, addr2IntegerId ) +import Type ( Type, splitAlgTyConApp_maybe, + isUnLiftedType, + tidyType, tidyTypes, tidyTopType, tidyTyVar, tidyTyVars, + Type + ) +import TysWiredIn ( smallIntegerDataCon, isIntegerTy ) +import LiberateCase ( liberateCase ) 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 ) -#endif - -isWrapperFor = panic "SimplCore.isWrapperFor (ToDo)" -isWrapperId = panic "SimplCore.isWrapperId (ToDo)" +import Specialise ( specProgram) +import UsageSPInf ( doUsageSPInf ) +import StrictAnal ( saBinds ) +import WorkWrap ( wwTopBinds ) +import CprAnalyse ( cprAnalyse ) + +import Unique ( Unique, Uniquable(..), + ratioTyConKey + ) +import UniqSupply ( UniqSupply, mkSplitUniqSupply, splitUniqSupply, uniqFromSupply ) +import Constants ( tARGET_MIN_INT, tARGET_MAX_INT ) +import Util ( mapAccumL ) +import SrcLoc ( noSrcLoc ) +import Bag +import Maybes +import IO ( hPutStr, stderr ) +import Outputable + +import Ratio ( numerator, denominator ) \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... - -> MainIO - ([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 - = BSCC("Core2Core") - if null core_todos then -- very rare, I suspect... - -- well, we still must do some renumbering - returnMn ( - (substCoreBindings nullIdEnv nullTyVarEnv binds us, - nullIdEnv, - init_specdata) - ) +core2core :: [CoreToDo] -- Spec of what core-to-core passes to do + -> [CoreBind] -- Binds in + -> [ProtoCoreRule] -- Rules + -> IO ([CoreBind], [ProtoCoreRule]) + +core2core core_todos binds rules + = do + us <- mkSplitUniqSupply 's' + let (cp_us, us1) = splitUniqSupply us + (ru_us, ps_us) = splitUniqSupply us1 + + better_rules <- simplRules ru_us rules binds + + let (binds1, rule_base) = prepareRuleBase binds better_rules + + -- Do the main business + (stats, processed_binds) <- doCorePasses zeroSimplCount cp_us binds1 + rule_base core_todos + + dumpIfSet opt_D_dump_simpl_stats + "Grand total simplifier statistics" + (pprSimplCount stats) + + -- Do the post-simplification business + post_simpl_binds <- doPostSimplification ps_us processed_binds + + -- Return results + return (post_simpl_binds, filter orphanRule better_rules) + + +doCorePasses stats us binds irs [] + = return (stats, binds) + +doCorePasses stats us binds irs (to_do : to_dos) + = do + let (us1, us2) = splitUniqSupply us + (stats1, binds1) <- doCorePass us1 binds irs to_do + doCorePasses (stats `plusSimplCount` stats1) us2 binds1 irs to_dos + +doCorePass us binds rb (CoreDoSimplify sw_chkr) = _scc_ "Simplify" simplifyPgm rb sw_chkr us binds +doCorePass us binds rb CoreCSE = _scc_ "CommonSubExpr" noStats (cseProgram binds) +doCorePass us binds rb CoreLiberateCase = _scc_ "LiberateCase" noStats (liberateCase binds) +doCorePass us binds rb CoreDoFloatInwards = _scc_ "FloatInwards" noStats (floatInwards binds) +doCorePass us binds rb CoreDoFullLaziness = _scc_ "FloatOutwards" noStats (floatOutwards us binds) +doCorePass us binds rb CoreDoStaticArgs = _scc_ "StaticArgs" noStats (doStaticArgs us binds) +doCorePass us binds rb CoreDoStrictness = _scc_ "Stranal" noStats (saBinds binds) +doCorePass us binds rb CoreDoWorkerWrapper = _scc_ "WorkWrap" noStats (wwTopBinds us binds) +doCorePass us binds rb CoreDoSpecialising = _scc_ "Specialise" noStats (specProgram us binds) +doCorePass us binds rb CoreDoCPResult = _scc_ "CPResult" noStats (cprAnalyse binds) +doCorePass us binds rb CoreDoPrintCore = _scc_ "PrintCore" noStats (printCore binds) +doCorePass us binds rb CoreDoUSPInf + = _scc_ "CoreUsageSPInf" + if opt_UsageSPOn then + noStats (doUsageSPInf us binds) else - (if do_verbose_core2core then - writeMn stderr "VERBOSE CORE-TO-CORE:\n" - else returnMn ()) `thenMn_` - - -- better do the main business - foldl_mn do_core_pass - (binds, us, nullIdEnv, init_specdata, zeroSimplCount) - core_todos - `thenMn` \ (processed_binds, _, inline_env, spec_data, simpl_stats) -> - - (if opt_D_simplifier_stats - then writeMn stderr ("\nSimplifier Stats:\n") - `thenMn_` - writeMn stderr (showSimplCount simpl_stats) - `thenMn_` - writeMn stderr "\n" - else returnMn () - ) `thenMn_` - - returnMn (processed_binds, inline_env, spec_data) - ESCC + trace "WARNING: ignoring requested -fusagesp pass; requires -fusagesp-on" $ + noStats (return binds) + +printCore binds = do dumpIfSet True "Print Core" + (pprCoreBindings binds) + return binds + +noStats thing = do { result <- thing; return (zeroSimplCount, result) } +\end{code} + + +%************************************************************************ +%* * +\subsection{Dealing with rules} +%* * +%************************************************************************ + +We must do some gentle simplifiation 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} +simplRules :: UniqSupply -> [ProtoCoreRule] -> [CoreBind] -> IO [ProtoCoreRule] +simplRules us rules binds + = do let (better_rules,_) = initSmpl sw_chkr us bind_vars black_list_all (mapSmpl simplRule rules) + + dumpIfSet opt_D_dump_rules + "Transformation rules" + (vcat (map pprProtoCoreRule better_rules)) + + return better_rules + where + black_list_all v = True -- This stops all inlining + sw_chkr any = SwBool False -- A bit bogus + + -- Boringly, we need to gather the in-scope set. + -- Typically this thunk won't even be force, but the test in + -- simpVar fails if it isn't right, and it might conceivably matter + bind_vars = foldr (unionVarSet . mkVarSet . bindersOf) emptyVarSet binds + + +simplRule rule@(ProtoCoreRule is_local id (Rule name bndrs args rhs)) + | not is_local + = returnSmpl rule -- No need to fiddle with imported rules + | otherwise + = simplBinders bndrs $ \ bndrs' -> + mapSmpl simplExpr args `thenSmpl` \ args' -> + simplExpr rhs `thenSmpl` \ rhs' -> + returnSmpl (ProtoCoreRule is_local id (Rule name bndrs' args' rhs')) +\end{code} + +%************************************************************************ +%* * +\subsection{The driver for the simplifier} +%* * +%************************************************************************ + +\begin{code} +simplifyPgm :: RuleBase + -> (SimplifierSwitch -> SwitchResult) + -> UniqSupply + -> [CoreBind] -- Input + -> IO (SimplCount, [CoreBind]) -- New bindings + +simplifyPgm (imported_rule_ids, rule_lhs_fvs) + sw_chkr us binds + = do { + beginPass "Simplify"; + + -- 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. Our solution is to do this occasional glom-together step, + -- just once per overall simplfication step. + + let { recd_binds = [Rec (flattenBinds binds)] }; + + (termination_msg, it_count, counts_out, binds') <- iteration us 1 zeroSimplCount recd_binds; + + dumpIfSet (opt_D_verbose_core2core && opt_D_dump_simpl_stats) + "Simplifier statistics" + (vcat [text termination_msg <+> text "after" <+> ppr it_count <+> text "iterations", + text "", + pprSimplCount counts_out]); + + endPass "Simplify" + (opt_D_verbose_core2core && not opt_D_dump_simpl_iterations) + binds' ; + + return (counts_out, binds') + } 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 - -> BSCC("CoreSimplify") - begin_pass ("Simplify" ++ if switchIsOn simpl_sw_chkr SimplDoFoldrBuild - then " (foldr/build)" else "") `thenMn_` - 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 "") - ESCC - - CoreDoFoldrBuildWorkerWrapper - -> BSCC("CoreDoFoldrBuildWorkerWrapper") - begin_pass "FBWW" `thenMn_` - case (mkFoldrBuildWW us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FBWW" - } ESCC - - CoreDoFoldrBuildWWAnal - -> BSCC("CoreDoFoldrBuildWWAnal") - begin_pass "AnalFBWW" `thenMn_` - case (analFBWW binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "AnalFBWW" - } ESCC - - CoreLiberateCase - -> BSCC("LiberateCase") - begin_pass "LiberateCase" `thenMn_` - case (liberateCase lib_case_threshold binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "LiberateCase" - } ESCC - - CoreDoCalcInlinings1 -- avoid inlinings w/ cost-centres - -> BSCC("CoreInlinings1") - begin_pass "CalcInlinings" `thenMn_` - case (calcInlinings False inline_env binds) of { inline_env2 -> - end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" - } ESCC - - CoreDoCalcInlinings2 -- allow inlinings w/ cost-centres - -> BSCC("CoreInlinings2") - begin_pass "CalcInlinings" `thenMn_` - case (calcInlinings True inline_env binds) of { inline_env2 -> - end_pass False us2 binds inline_env2 spec_data simpl_stats "CalcInlinings" - } ESCC - - CoreDoFloatInwards - -> BSCC("FloatInwards") - begin_pass "FloatIn" `thenMn_` - case (floatInwards binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatIn" - } ESCC - - CoreDoFullLaziness - -> BSCC("CoreFloating") - begin_pass "FloatOut" `thenMn_` - case (floatOutwards us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "FloatOut" - } ESCC - - CoreDoStaticArgs - -> BSCC("CoreStaticArgs") - begin_pass "StaticArgs" `thenMn_` - 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]) - } ESCC - - CoreDoStrictness - -> BSCC("CoreStranal") - begin_pass "StrAnal" `thenMn_` - case (saWwTopBinds us1 binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "StrAnal" - } ESCC - - CoreDoSpecialising - -> BSCC("Specialise") - begin_pass "Specialise" `thenMn_` - 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 - writeMn stderr (ppShow 1000 {-pprCols-} - (pprSpecErrs module_name spec_errs spec_warn spec_tyerrs)) - `thenMn_` writeMn stderr "\n" - else - returnMn ()) `thenMn_` - - (if not spec_noerrs then -- Stop here if specialisation errors occured - exitMn 1 - else - returnMn ()) `thenMn_` - - end_pass False us2 p inline_env spec_data2 simpl_stats "Specialise" - } - ESCC - - CoreDoDeforest -#if OMIT_DEFORESTER - -> error "ERROR: CoreDoDeforest: not built into compiler\n" -#else - -> BSCC("Deforestation") - begin_pass "Deforestation" `thenMn_` - case (deforestProgram binds us1) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "Deforestation" - } - ESCC -#endif - - CoreDoAutoCostCentres - -> BSCC("AutoSCCs") - begin_pass "AutoSCCs" `thenMn_` - case (addAutoCostCentres module_name binds) of { binds2 -> - end_pass False us2 binds2 inline_env spec_data simpl_stats "AutoSCCs" - } - ESCC - - 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 -> writeMn stderr ("*** Core2Core: "++what++"\n") - else \ what -> returnMn () - - 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 - writeMn stderr ("\n*** "++what++":\n") - `thenMn_` - writeMn stderr (ppShow 1000 - (ppAboves (map (pprCoreBinding ppr_style) binds2))) - `thenMn_` - writeMn stderr "\n" - else - returnMn ()) `thenMn_` - let - linted_binds = core_linter what spec_done binds2 - in - returnMn - (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 [] = returnMn z -foldl_mn f z (x:xs) = f z x `thenMn` \ zz -> - foldl_mn f zz xs + max_iterations = getSimplIntSwitch sw_chkr MaxSimplifierIterations + black_list_fn = blackListed rule_lhs_fvs (intSwitchSet sw_chkr SimplInlinePhase) + + core_iter_dump binds | opt_D_verbose_core2core = pprCoreBindings binds + | otherwise = empty + + iteration us iteration_no counts binds + = do { + -- Occurrence analysis + let { tagged_binds = _scc_ "OccAnal" occurAnalyseBinds binds } ; + + dumpIfSet opt_D_dump_occur_anal "Occurrence analysis" + (pprCoreBindings tagged_binds); + + -- Simplify + let { (binds', counts') = initSmpl sw_chkr us1 imported_rule_ids + black_list_fn + (simplTopBinds tagged_binds); + -- The imported_rule_ids are used by initSmpl 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. + + all_counts = counts `plusSimplCount` counts' + } ; + + -- Stop if nothing happened; don't dump output + if isZeroSimplCount counts' then + return ("Simplifier reached fixed point", iteration_no, all_counts, binds') + else do { + + -- Dump the result of this iteration + dumpIfSet opt_D_dump_simpl_iterations + ("Simplifier iteration " ++ show iteration_no + ++ " out of " ++ show max_iterations) + (pprSimplCount counts') ; + + if opt_D_dump_simpl_iterations then + endPass ("Simplifier iteration " ++ show iteration_no ++ " result") + opt_D_verbose_core2core + binds' + else + return [] ; + + -- Stop if we've run out of iterations + if iteration_no == max_iterations then + do { + if max_iterations > 2 then + hPutStr stderr ("NOTE: Simplifier still going after " ++ + show max_iterations ++ + " iterations; bailing out.\n") + else return (); + + return ("Simplifier baled out", iteration_no, all_counts, binds') + } + + -- Else loop + else iteration us2 (iteration_no + 1) all_counts binds' + } } + where + (us1, us2) = splitUniqSupply us \end{code} ---- ToDo: maybe move elsewhere --- -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. +%************************************************************************ +%* * +\subsection{PostSimplification} +%* * +%************************************************************************ + +Several tasks are performed by the post-simplification pass + +1. Make the representation of NoRep literals explicit, and + float their bindings to the top level. We only do the floating + part for NoRep lits inside a lambda (else no gain). We need to + take care with let x = "foo" in e + that we don't end up with a silly binding + let x = y in e + with a floated "foo". What a bore. + +4. Do eta reduction for lambda abstractions appearing in: + - the RHS of case alternatives + - the body of a let + + These will otherwise turn into local bindings during Core->STG; + better to nuke them if possible. (In general the simplifier does + eta expansion not eta reduction, up to this point. It does eta + on the RHSs of bindings but not the RHSs of case alternatives and + let bodies) + + +------------------- NOT DONE ANY MORE ------------------------ +[March 98] Indirections are now elimianted by the occurrence analyser +1. Eliminate indirections. The point here is to transform + x_local = E + x_exported = x_local + ==> + x_exported = E + +[Dec 98] [Not now done because there is no penalty in the code + generator for using the former form] +2. Convert + case x of {...; x' -> ...x'...} + ==> + case x of {...; _ -> ...x... } + See notes in SimplCase.lhs, near simplDefault for the reasoning here. +-------------------------------------------------------------- + +Special case +~~~~~~~~~~~~ + +NOT ENABLED AT THE MOMENT (because the floated Ids are global-ish +things, and we need local Ids for non-floated stuff): -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. + Don't float stuff out of a binder that's marked as a bottoming Id. + Reason: it doesn't do any good, and creates more CAFs that increase + the size of SRTs. + +eg. + + f = error "string" + +is translated to + + f' = unpackCString# "string" + f = error f' + +hence f' and f become CAFs. Instead, the special case for +tidyTopBinding below makes sure this comes out as + + f = let f' = unpackCString# "string" in error f' + +and we can safely ignore f as a CAF, since it can only ever be entered once. -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. \begin{code} -calcInlinings :: Bool -- True => inlinings with _scc_s are OK - -> IdEnv UnfoldingDetails - -> [CoreBinding] - -> IdEnv UnfoldingDetails +doPostSimplification :: UniqSupply -> [CoreBind] -> IO [CoreBind] +doPostSimplification us binds_in + = do + beginPass "Post-simplification pass" + let binds_out = initPM us (postSimplTopBinds binds_in) + endPass "Post-simplification pass" opt_D_verbose_core2core binds_out + +postSimplTopBinds :: [CoreBind] -> PostM [CoreBind] +postSimplTopBinds binds + = mapPM postSimplTopBind binds `thenPM` \ binds' -> + returnPM (bagToList (unionManyBags binds')) + +postSimplTopBind :: CoreBind -> PostM (Bag CoreBind) +postSimplTopBind (NonRec bndr rhs) + | isBottomingId bndr -- Don't lift out floats for bottoming Ids + -- See notes above + = getFloatsPM (postSimplExpr rhs) `thenPM` \ (rhs', floats) -> + returnPM (unitBag (NonRec bndr (foldrBag Let rhs' floats))) + +postSimplTopBind bind + = getFloatsPM (postSimplBind bind) `thenPM` \ (bind', floats) -> + returnPM (floats `snocBag` bind') + +postSimplBind (NonRec bndr rhs) + = postSimplExpr rhs `thenPM` \ rhs' -> + returnPM (NonRec bndr rhs') + +postSimplBind (Rec pairs) + = mapPM postSimplExpr rhss `thenPM` \ rhss' -> + returnPM (Rec (bndrs `zip` rhss')) + where + (bndrs, rhss) = unzip pairs +\end{code} -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 + +Expressions +~~~~~~~~~~~ +\begin{code} +postSimplExpr (Var v) = returnPM (Var v) +postSimplExpr (Type ty) = returnPM (Type ty) + +postSimplExpr (App fun arg) + = postSimplExpr fun `thenPM` \ fun' -> + postSimplExpr arg `thenPM` \ arg' -> + returnPM (App fun' arg') + +postSimplExpr (Con (Literal lit) args) + = ASSERT( null args ) + litToRep lit `thenPM` \ (lit_ty, lit_expr) -> + getInsideLambda `thenPM` \ in_lam -> + if in_lam && not (exprIsTrivial lit_expr) then + -- It must have been a no-rep literal with a + -- non-trivial representation; and we're inside a lambda; + -- so float it to the top + addTopFloat lit_ty lit_expr `thenPM` \ v -> + returnPM (Var v) + else + returnPM lit_expr + +postSimplExpr (Con con args) + = mapPM postSimplExpr args `thenPM` \ args' -> + returnPM (Con con args') + +postSimplExpr (Lam bndr body) + = insideLambda bndr $ + postSimplExpr body `thenPM` \ body' -> + returnPM (Lam bndr body') + +postSimplExpr (Let bind body) + = postSimplBind bind `thenPM` \ bind' -> + postSimplExprEta body `thenPM` \ body' -> + returnPM (Let bind' body') + +postSimplExpr (Note note body) + = postSimplExpr body `thenPM` \ body' -> + -- Do *not* call postSimplExprEta here + -- We don't want to turn f = \x -> coerce t (\y -> f x y) + -- into f = \x -> coerce t (f x) + -- because then f has a lower arity. + -- This is not only bad in general, it causes the arity to + -- not match the [Demand] on an Id, + -- which confuses the importer of this module. + returnPM (Note note body') + +postSimplExpr (Case scrut case_bndr alts) + = postSimplExpr scrut `thenPM` \ scrut' -> + mapPM ps_alt alts `thenPM` \ alts' -> + returnPM (Case scrut' case_bndr alts') 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 -#endif - - | 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 - - -- 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"). - - | explicit_INLINE_requested - = glorious_success UnfoldAlways - - | otherwise - = glorious_success guidance + ps_alt (con,bndrs,rhs) = postSimplExprEta rhs `thenPM` \ rhs' -> + returnPM (con, bndrs, rhs') - 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! +postSimplExprEta e = postSimplExpr e `thenPM` \ e' -> + returnPM (etaCoreExpr e') +\end{code} + + +%************************************************************************ +%* * +\subsection[coreToStg-lits]{Converting literals} +%* * +%************************************************************************ + +Literals: the NoRep kind need to be de-no-rep'd. +We always replace them with a simple variable, and float a suitable +binding out to the top level. + +\begin{code} +litToRep :: Literal -> PostM (Type, CoreExpr) + +litToRep (NoRepStr s ty) + = returnPM (ty, rhs) + where + rhs = if (any is_NUL (_UNPK_ s)) + + then -- Must cater for NULs in literal string + mkApps (Var unpackCString2Id) + [mkLit (MachStr s), + mkLit (mkMachInt (toInteger (_LENGTH_ s)))] + + else -- No NULs in the string + App (Var unpackCStringId) (mkLit (MachStr s)) + + is_NUL c = c == '\0' +\end{code} + +If an Integer is small enough (Haskell implementations must support +Ints in the range $[-2^29+1, 2^29-1]$), wrap it up in @int2Integer@; +otherwise, wrap with @addr2Integer@. + +\begin{code} +litToRep (NoRepInteger i integer_ty) + = returnPM (integer_ty, rhs) + where + rhs | i > tARGET_MIN_INT && -- Small enough, so start from an Int + i < tARGET_MAX_INT + = Con (DataCon smallIntegerDataCon) [Con (Literal (mkMachInt i)) []] + + | otherwise -- Big, so start from a string + = App (Var addr2IntegerId) (Con (Literal (MachStr (_PK_ (show i)))) []) + + +litToRep (NoRepRational r rational_ty) + = postSimplExpr (mkLit (NoRepInteger (numerator r) integer_ty)) `thenPM` \ num_arg -> + postSimplExpr (mkLit (NoRepInteger (denominator r) integer_ty)) `thenPM` \ denom_arg -> + returnPM (rational_ty, mkConApp ratio_data_con [Type integer_ty, num_arg, denom_arg]) + where + (ratio_data_con, integer_ty) + = case (splitAlgTyConApp_maybe rational_ty) of + Just (tycon, [i_ty], [con]) + -> ASSERT(isIntegerTy i_ty && getUnique tycon == ratioTyConKey) + (con, i_ty) + + _ -> (panic "ratio_data_con", panic "integer_ty") + +litToRep other_lit = returnPM (literalType other_lit, mkLit other_lit) \end{code} -ANDY, on the hatred of the check above; why obliterate it? Consider - head xs = foldr (\ x _ -> x) (_|_) xs +%************************************************************************ +%* * +\subsection{The monad} +%* * +%************************************************************************ + +\begin{code} +type PostM a = Bool -- True <=> inside a *value* lambda + -> (UniqSupply, Bag CoreBind) -- Unique supply and Floats in + -> (a, (UniqSupply, Bag CoreBind)) + +initPM :: UniqSupply -> PostM a -> a +initPM us m + = case m False {- not inside lambda -} (us, emptyBag) of + (result, _) -> result + +returnPM v in_lam usf = (v, usf) +thenPM m k in_lam usf = case m in_lam usf of + (r, usf') -> k r in_lam usf' + +mapPM f [] = returnPM [] +mapPM f (x:xs) = f x `thenPM` \ r -> + mapPM f xs `thenPM` \ rs -> + returnPM (r:rs) + +insideLambda :: CoreBndr -> PostM a -> PostM a +insideLambda bndr m in_lam usf | isId bndr = m True usf + | otherwise = m in_lam usf + +getInsideLambda :: PostM Bool +getInsideLambda in_lam usf = (in_lam, usf) + +getFloatsPM :: PostM a -> PostM (a, Bag CoreBind) +getFloatsPM m in_lam (us, floats) + = let + (a, (us', floats')) = m in_lam (us, emptyBag) + in + ((a, floats'), (us', floats)) + +addTopFloat :: Type -> CoreExpr -> PostM Id +addTopFloat lit_ty lit_rhs in_lam (us, floats) + = let + (us1, us2) = splitUniqSupply us + uniq = uniqFromSupply us1 + lit_id = mkSysLocal SLIT("lf") uniq lit_ty + in + (lit_id, (us2, floats `snocBag` NonRec lit_id lit_rhs)) +\end{code} + -This then is exported via a pragma. However, -*if* you include the extra code above, you will -export the non-foldr/build version.