X-Git-Url: http://git.megacz.com/?a=blobdiff_plain;f=compiler%2FsimplCore%2FSimplUtils.lhs;h=1e510421e72a1c94632f5c100e6faadc5557f97f;hb=f2dcf256399e9a2de6343c625630b51f8abf4863;hp=32ad40c7b42aa444f8f480f1574dff5db68072ec;hpb=27497880e4386b42cd078c15f82e1b02a92aae92;p=ghc-hetmet.git diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 32ad40c..1e51042 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -15,8 +15,9 @@ module SimplUtils ( SimplCont(..), DupFlag(..), LetRhsFlag(..), contIsDupable, contResultType, countValArgs, countArgs, pushContArgs, - mkBoringStop, mkRhsStop, contIsRhs, contIsRhsOrArg, - getContArgs, interestingCallContext, interestingArg, isStrictType + mkBoringStop, mkLazyArgStop, mkRhsStop, contIsRhs, contIsRhsOrArg, + getContArgs, interestingCallContext, interestingArgContext, + interestingArg, isStrictType ) where @@ -29,16 +30,16 @@ import StaticFlags ( opt_UF_UpdateInPlace, opt_SimplNoPreInlining, opt_RulesOff ) import CoreSyn import CoreFVs ( exprFreeVars ) -import CoreUtils ( cheapEqExpr, exprType, exprIsTrivial, exprIsCheap, +import CoreUtils ( cheapEqExpr, exprType, exprIsTrivial, etaExpand, exprEtaExpandArity, bindNonRec, mkCoerce2, findDefault, exprOkForSpeculation, exprIsHNF, mergeAlts ) import Literal ( mkStringLit ) import CoreUnfold ( smallEnoughToInline ) import MkId ( eRROR_ID ) -import Id ( idType, isDataConWorkId, idOccInfo, isDictId, +import Id ( Id, idType, isDataConWorkId, idOccInfo, isDictId, isDeadBinder, idNewDemandInfo, isExportedId, - idUnfolding, idNewStrictness, idInlinePragma, + idUnfolding, idNewStrictness, idInlinePragma, idHasRules ) import NewDemand ( isStrictDmd, isBotRes, splitStrictSig ) import SimplMonad @@ -63,18 +64,20 @@ import Outputable \begin{code} data SimplCont -- Strict contexts - = Stop OutType -- Type of the result + = Stop OutType -- Type of the result LetRhsFlag - Bool -- True <=> This is the RHS of a thunk whose type suggests - -- that update-in-place would be possible - -- (This makes the inliner a little keener.) + Bool -- True <=> There is something interesting about + -- the context, and hence the inliner + -- should be a bit keener (see interestingCallContext) + -- Two cases: + -- (a) This is the RHS of a thunk whose type suggests + -- that update-in-place would be possible + -- (b) This is an argument of a function that has RULES + -- Inlining the call might allow the rule to fire | CoerceIt OutType -- The To-type, simplified SimplCont - | InlinePlease -- This continuation makes a function very - SimplCont -- keen to inline itelf - | ApplyTo DupFlag InExpr SimplEnv -- The argument, as yet unsimplified, SimplCont -- and its environment @@ -86,7 +89,7 @@ data SimplCont -- Strict contexts | ArgOf LetRhsFlag -- An arbitrary strict context: the argument -- of a strict function, or a primitive-arg fn -- or a PrimOp - -- No DupFlag because we never duplicate it + -- No DupFlag, because we never duplicate it OutType -- arg_ty: type of the argument itself OutType -- cont_ty: the type of the expression being sought by the context -- f (error "foo") ==> coerce t (error "foo") @@ -110,7 +113,6 @@ instance Outputable SimplCont where ppr (Select dup bndr alts se cont) = (ptext SLIT("Select") <+> ppr dup <+> ppr bndr) $$ (nest 4 (ppr alts)) $$ ppr cont ppr (CoerceIt ty cont) = (ptext SLIT("CoerceIt") <+> ppr ty) $$ ppr cont - ppr (InlinePlease cont) = ptext SLIT("InlinePlease") $$ ppr cont data DupFlag = OkToDup | NoDup @@ -120,9 +122,14 @@ instance Outputable DupFlag where ------------------- -mkBoringStop, mkRhsStop :: OutType -> SimplCont -mkBoringStop ty = Stop ty AnArg (canUpdateInPlace ty) -mkRhsStop ty = Stop ty AnRhs (canUpdateInPlace ty) +mkBoringStop :: OutType -> SimplCont +mkBoringStop ty = Stop ty AnArg False + +mkLazyArgStop :: OutType -> Bool -> SimplCont +mkLazyArgStop ty has_rules = Stop ty AnArg (canUpdateInPlace ty || has_rules) + +mkRhsStop :: OutType -> SimplCont +mkRhsStop ty = Stop ty AnRhs (canUpdateInPlace ty) contIsRhs :: SimplCont -> Bool contIsRhs (Stop _ AnRhs _) = True @@ -139,14 +146,12 @@ contIsDupable (Stop _ _ _) = True contIsDupable (ApplyTo OkToDup _ _ _) = True contIsDupable (Select OkToDup _ _ _ _) = True contIsDupable (CoerceIt _ cont) = contIsDupable cont -contIsDupable (InlinePlease cont) = contIsDupable cont contIsDupable other = False ------------------- discardableCont :: SimplCont -> Bool discardableCont (Stop _ _ _) = False discardableCont (CoerceIt _ cont) = discardableCont cont -discardableCont (InlinePlease cont) = discardableCont cont discardableCont other = True discardCont :: SimplCont -- A continuation, expecting @@ -163,7 +168,6 @@ contResultType (Stop to_ty _ _) = to_ty contResultType (ArgOf _ _ to_ty _) = to_ty contResultType (ApplyTo _ _ _ cont) = contResultType cont contResultType (CoerceIt _ cont) = contResultType cont -contResultType (InlinePlease cont) = contResultType cont contResultType (Select _ _ _ _ cont) = contResultType cont ------------------- @@ -188,8 +192,7 @@ pushContArgs env (arg : args) cont = ApplyTo NoDup arg env (pushContArgs env arg getContArgs :: SwitchChecker -> OutId -> SimplCont -> ([(InExpr, SimplEnv, Bool)], -- Arguments; the Bool is true for strict args - SimplCont, -- Remaining continuation - Bool) -- Whether we came across an InlineCall + SimplCont) -- Remaining continuation -- getContArgs id k = (args, k', inl) -- args are the leading ApplyTo items in k -- (i.e. outermost comes first) @@ -202,22 +205,18 @@ getContArgs chkr fun orig_cont stricts | switchIsOn chkr NoCaseOfCase = vanilla_stricts | otherwise = computed_stricts in - go [] stricts False orig_cont + go [] stricts orig_cont where ---------------------------- -- Type argument - go acc ss inl (ApplyTo _ arg@(Type _) se cont) - = go ((arg,se,False) : acc) ss inl cont + go acc ss (ApplyTo _ arg@(Type _) se cont) + = go ((arg,se,False) : acc) ss cont -- NB: don't bother to instantiate the function type -- Value argument - go acc (s:ss) inl (ApplyTo _ arg se cont) - = go ((arg,se,s) : acc) ss inl cont - - -- An Inline continuation - go acc ss inl (InlinePlease cont) - = go acc ss True cont + go acc (s:ss) (ApplyTo _ arg se cont) + = go ((arg,se,s) : acc) ss cont -- We're run out of arguments, or else we've run out of demands -- The latter only happens if the result is guaranteed bottom @@ -229,9 +228,9 @@ getContArgs chkr fun orig_cont -- Then, especially in the first of these cases, we'd like to discard -- the continuation, leaving just the bottoming expression. But the -- type might not be right, so we may have to add a coerce. - go acc ss inl cont - | null ss && discardableCont cont = (reverse acc, discardCont cont, inl) - | otherwise = (reverse acc, cont, inl) + go acc ss cont + | null ss && discardableCont cont = (reverse acc, discardCont cont) + | otherwise = (reverse acc, cont) ---------------------------- vanilla_stricts, computed_stricts :: [Bool] @@ -375,14 +374,13 @@ interestingCallContext :: Bool -- False <=> no args at all interestingCallContext some_args some_val_args cont = interesting cont where - interesting (InlinePlease _) = True interesting (Select _ _ _ _ _) = some_args interesting (ApplyTo _ _ _ _) = True -- Can happen if we have (coerce t (f x)) y -- Perhaps True is a bit over-keen, but I've -- seen (coerce f) x, where f has an INLINE prag, -- So we have to give some motivaiton for inlining it interesting (ArgOf _ _ _ _) = some_val_args - interesting (Stop ty _ upd_in_place) = some_val_args && upd_in_place + interesting (Stop ty _ interesting) = some_val_args && interesting interesting (CoerceIt _ cont) = interesting cont -- If this call is the arg of a strict function, the context -- is a bit interesting. If we inline here, we may get useful @@ -401,6 +399,32 @@ interestingCallContext some_args some_val_args cont ------------------- +interestingArgContext :: Id -> SimplCont -> Bool +-- If the argument has form (f x y), where x,y are boring, +-- and f is marked INLINE, then we don't want to inline f. +-- But if the context of the argument is +-- g (f x y) +-- where g has rules, then we *do* want to inline f, in case it +-- exposes a rule that might fire. Similarly, if the context is +-- h (g (f x x)) +-- where h has rules, then we do want to inline f. +-- The interesting_arg_ctxt flag makes this happen; if it's +-- set, the inliner gets just enough keener to inline f +-- regardless of how boring f's arguments are, if it's marked INLINE +-- +-- The alternative would be to *always* inline an INLINE function, +-- regardless of how boring its context is; but that seems overkill +-- For example, it'd mean that wrapper functions were always inlined +interestingArgContext fn cont + = idHasRules fn || go cont + where + go (Select {}) = False + go (ApplyTo {}) = False + go (ArgOf {}) = True + go (CoerceIt _ c) = go c + go (Stop _ _ interesting) = interesting + +------------------- canUpdateInPlace :: Type -> Bool -- Consider let x = in ... -- If returns an explicit constructor, we might be able