X-Git-Url: http://git.megacz.com/?p=ghc-hetmet.git;a=blobdiff_plain;f=compiler%2FsimplCore%2FSimplUtils.lhs;h=c541096c40a39752865d1ffcd7af464510891677;hp=0f6cf733a4697e104d4a620c11f814094d92be65;hb=72462499b891d5779c19f3bda03f96e24f9554ae;hpb=c3fe0f3699fa59261a340686bba648c981b3511d diff --git a/compiler/simplCore/SimplUtils.lhs b/compiler/simplCore/SimplUtils.lhs index 0f6cf73..c541096 100644 --- a/compiler/simplCore/SimplUtils.lhs +++ b/compiler/simplCore/SimplUtils.lhs @@ -10,14 +10,14 @@ module SimplUtils ( -- Inlining, preInlineUnconditionally, postInlineUnconditionally, - activeInline, activeRule, inlineMode, + activeInline, activeRule, -- The continuation type SimplCont(..), DupFlag(..), ArgInfo(..), contIsDupable, contResultType, contIsTrivial, contArgs, dropArgs, - countValArgs, countArgs, splitInlineCont, + countValArgs, countArgs, mkBoringStop, mkLazyArgStop, contIsRhsOrArg, - interestingCallContext, interestingArgContext, + interestingCallContext, interestingArg, mkArgInfo, @@ -34,6 +34,7 @@ import qualified CoreSubst import PprCore import CoreFVs import CoreUtils +import CoreArity ( etaExpand, exprEtaExpandArity ) import CoreUnfold import Name import Id @@ -51,7 +52,7 @@ import MonadUtils import Outputable import FastString -import List( nub ) +import Data.List \end{code} @@ -112,7 +113,7 @@ data SimplCont SimplCont | StrictArg -- e C - OutExpr -- e + OutExpr -- e; *always* of form (Var v `App1` e1 .. `App` en) CallCtxt -- Whether *this* argument position is interesting ArgInfo -- Whether the function at the head of e has rules, etc SimplCont -- plus strictness flags for *further* args @@ -214,63 +215,11 @@ dropArgs :: Int -> SimplCont -> SimplCont dropArgs 0 cont = cont dropArgs n (ApplyTo _ _ _ cont) = dropArgs (n-1) cont dropArgs n other = pprPanic "dropArgs" (ppr n <+> ppr other) - --------------------- -splitInlineCont :: SimplCont -> Maybe (SimplCont, SimplCont) --- Returns Nothing if the continuation should dissolve an InlineMe Note --- Return Just (c1,c2) otherwise, --- where c1 is the continuation to put inside the InlineMe --- and c2 outside - --- Example: (__inline_me__ (/\a. e)) ty --- Here we want to do the beta-redex without dissolving the InlineMe --- See test simpl017 (and Trac #1627) for a good example of why this is important - -splitInlineCont (ApplyTo dup (Type ty) se c) - | Just (c1, c2) <- splitInlineCont c = Just (ApplyTo dup (Type ty) se c1, c2) -splitInlineCont cont@(Stop {}) = Just (mkBoringStop, cont) -splitInlineCont cont@(StrictBind {}) = Just (mkBoringStop, cont) -splitInlineCont cont@(StrictArg {}) = Just (mkBoringStop, cont) -splitInlineCont _ = Nothing -\end{code} - - -\begin{code} -interestingArg :: OutExpr -> Bool - -- An argument is interesting if it has *some* structure - -- We are here trying to avoid unfolding a function that - -- is applied only to variables that have no unfolding - -- (i.e. they are probably lambda bound): f x y z - -- There is little point in inlining f here. -interestingArg (Var v) = hasSomeUnfolding (idUnfolding v) - -- Was: isValueUnfolding (idUnfolding v') - -- But that seems over-pessimistic - || isDataConWorkId v - -- This accounts for an argument like - -- () or [], which is definitely interesting -interestingArg (Type _) = False -interestingArg (App fn (Type _)) = interestingArg fn -interestingArg (Note _ a) = interestingArg a - --- Idea (from Sam B); I'm not sure if it's a good idea, so commented out for now --- interestingArg expr | isUnLiftedType (exprType expr) --- -- Unlifted args are only ever interesting if we know what they are --- = case expr of --- Lit lit -> True --- _ -> False - -interestingArg _ = True - -- Consider let x = 3 in f x - -- The substitution will contain (x -> ContEx 3), and we want to - -- to say that x is an interesting argument. - -- But consider also (\x. f x y) y - -- The substitution will contain (x -> ContEx y), and we want to say - -- that x is not interesting (assuming y has no unfolding) \end{code} -Comment about interestingCallContext -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Note [Interesting call context] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ We want to avoid inlining an expression where there can't possibly be any gain, such as in an argument position. Hence, if the continuation is interesting (eg. a case scrutinee, application etc.) then we @@ -305,6 +254,7 @@ default case. \begin{code} interestingCallContext :: SimplCont -> CallCtxt +-- See Note [Interesting call context] interestingCallContext cont = interesting cont where @@ -342,24 +292,25 @@ interestingCallContext cont ------------------- mkArgInfo :: Id + -> [CoreRule] -- Rules for function -> Int -- Number of value args - -> SimplCont -- Context of the cal + -> SimplCont -- Context of the call -> ArgInfo -mkArgInfo fun n_val_args call_cont +mkArgInfo fun rules n_val_args call_cont | n_val_args < idArity fun -- Note [Unsaturated functions] = ArgInfo { ai_rules = False , ai_strs = vanilla_stricts , ai_discs = vanilla_discounts } | otherwise - = ArgInfo { ai_rules = interestingArgContext fun call_cont + = ArgInfo { ai_rules = interestingArgContext rules call_cont , ai_strs = add_type_str (idType fun) arg_stricts , ai_discs = arg_discounts } where vanilla_discounts, arg_discounts :: [Int] vanilla_discounts = repeat 0 arg_discounts = case idUnfolding fun of - CoreUnfolding _ _ _ _ (UnfoldIfGoodArgs _ discounts _ _) + CoreUnfolding {uf_guidance = UnfoldIfGoodArgs {ug_args = discounts}} -> discounts ++ vanilla_discounts _ -> vanilla_discounts @@ -413,7 +364,7 @@ it'll just be floated out again. Even if f has lots of discounts on its first argument -- it must be saturated for these to kick in -} -interestingArgContext :: Id -> SimplCont -> Bool +interestingArgContext :: [CoreRule] -> 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 @@ -424,16 +375,18 @@ interestingArgContext :: Id -> SimplCont -> Bool -- where h has rules, then we do want to inline f; hence the -- call_cont argument to interestingArgContext -- --- The interesting_arg_ctxt flag makes this happen; if it's +-- The ai-rules 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 call_cont - = idHasRules fn || go call_cont +interestingArgContext rules call_cont + = notNull rules || enclosing_fn_has_rules where + enclosing_fn_has_rules = go call_cont + go (Select {}) = False go (ApplyTo {}) = False go (StrictArg _ cci _ _) = interesting cci @@ -480,13 +433,7 @@ unboxed tuples and suchlike. INLINE pragmas ~~~~~~~~~~~~~~ -SimplGently is also used as the mode to simplify inside an InlineMe note. - -\begin{code} -inlineMode :: SimplifierMode -inlineMode = SimplGently -\end{code} - +We don't simplify inside InlineRules (which come from INLINE pragmas). It really is important to switch off inlinings inside such expressions. Consider the following example @@ -611,9 +558,9 @@ preInlineUnconditionally env top_lvl bndr rhs where phase = getMode env active = case phase of - SimplGently -> isAlwaysActive prag - SimplPhase n _ -> isActive n prag - prag = idInlinePragma bndr + SimplGently -> isEarlyActive act + SimplPhase n _ -> isActive n act + act = idInlineActivation bndr try_once in_lam int_cxt -- There's one textual occurrence | not in_lam = isNotTopLevel top_lvl || early_phase @@ -696,7 +643,7 @@ story for now. \begin{code} postInlineUnconditionally :: SimplEnv -> TopLevelFlag - -> InId -- The binder (an OutId would be fine too) + -> OutId -- The binder (an InId would be fine too) -> OccInfo -- From the InId -> OutExpr -> Unfolding @@ -706,6 +653,7 @@ postInlineUnconditionally env top_lvl bndr occ_info rhs unfolding | isLoopBreaker occ_info = False -- If it's a loop-breaker of any kind, don't inline -- because it might be referred to "earlier" | isExportedId bndr = False + | isInlineRule unfolding = False -- Note [InlineRule and postInlineUnconditionally] | exprIsTrivial rhs = True | otherwise = case occ_info of @@ -767,9 +715,9 @@ postInlineUnconditionally env top_lvl bndr occ_info rhs unfolding where active = case getMode env of - SimplGently -> isAlwaysActive prag - SimplPhase n _ -> isActive n prag - prag = idInlinePragma bndr + SimplGently -> isAlwaysActive act + SimplPhase n _ -> isActive n act + act = idInlineActivation bndr activeInline :: SimplEnv -> OutId -> Bool activeInline env id @@ -790,9 +738,9 @@ activeInline env id -- and they are now constructed as Compulsory unfoldings (in MkId) -- so they'll happen anyway. - SimplPhase n _ -> isActive n prag + SimplPhase n _ -> isActive n act where - prag = idInlinePragma id + act = idInlineActivation id activeRule :: DynFlags -> SimplEnv -> Maybe (Activation -> Bool) -- Nothing => No rules at all @@ -810,6 +758,23 @@ activeRule dflags env SimplPhase n _ -> Just (isActive n) \end{code} +Note [InlineRule and postInlineUnconditionally] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Do not do postInlineUnconditionally if the Id has an InlineRule, otherwise +we lose the unfolding. Example + + -- f has InlineRule with rhs (e |> co) + -- where 'e' is big + f = e |> co + +Then there's a danger we'll optimise to + + f' = e + f = f' |> co + +and now postInlineUnconditionally, losing the InlineRule on f. Now f' +won't inline because 'e' is too big. + %************************************************************************ %* * @@ -818,14 +783,14 @@ activeRule dflags env %************************************************************************ \begin{code} -mkLam :: [OutBndr] -> OutExpr -> SimplM OutExpr +mkLam :: SimplEnv -> [OutBndr] -> OutExpr -> SimplM OutExpr -- mkLam tries three things -- a) eta reduction, if that gives a trivial expression -- b) eta expansion [only if there are some value lambdas] -mkLam [] body +mkLam _b [] body = return body -mkLam bndrs body +mkLam env bndrs body = do { dflags <- getDOptsSmpl ; mkLam' dflags bndrs body } where @@ -846,8 +811,10 @@ mkLam bndrs body ; return etad_lam } | dopt Opt_DoLambdaEtaExpansion dflags, - any isRuntimeVar bndrs - = do { body' <- tryEtaExpansion dflags body + not (inGentleMode env), -- In gentle mode don't eta-expansion + any isRuntimeVar bndrs -- because it can clutter up the code + -- with casts etc that may not be removed + = do { let body' = tryEtaExpansion dflags body ; return (mkLams bndrs body') } | otherwise @@ -1032,11 +999,10 @@ when computing arity; and etaExpand adds the coerces as necessary when actually computing the expansion. \begin{code} -tryEtaExpansion :: DynFlags -> OutExpr -> SimplM OutExpr +tryEtaExpansion :: DynFlags -> OutExpr -> OutExpr -- There is at least one runtime binder in the binders -tryEtaExpansion dflags body = do - us <- getUniquesM - return (etaExpand fun_arity us body (exprType body)) +tryEtaExpansion dflags body + = etaExpand fun_arity body where fun_arity = exprEtaExpandArity dflags body \end{code} @@ -1189,7 +1155,7 @@ abstractFloats main_tvs body_env body = do { uniq <- getUniqueM ; let poly_name = setNameUnique (idName var) uniq -- Keep same name poly_ty = mkForAllTys tvs_here (idType var) -- But new type of course - poly_id = transferPolyIdInfo var $ -- Note [transferPolyIdInfo] in Id.lhs + poly_id = transferPolyIdInfo var tvs_here $ -- Note [transferPolyIdInfo] in Id.lhs mkLocalId poly_name poly_ty ; return (poly_id, mkTyApps (Var poly_id) (mkTyVarTys tvs_here)) } -- In the olden days, it was crucial to copy the occInfo of the original var,