[commit: ghc] wip/T14152: Do not assign an unfolding to exit join points (a1bd762)
git at git.haskell.org
git at git.haskell.org
Tue Aug 29 17:03:34 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/T14152
Link : http://ghc.haskell.org/trac/ghc/changeset/a1bd7624ff7012d39dd1decd9f68fb81cebbd966/ghc
>---------------------------------------------------------------
commit a1bd7624ff7012d39dd1decd9f68fb81cebbd966
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Tue Aug 29 18:01:06 2017 +0100
Do not assign an unfolding to exit join points
to prevent them from being inlied.
>---------------------------------------------------------------
a1bd7624ff7012d39dd1decd9f68fb81cebbd966
compiler/simplCore/Simplify.hs | 27 +++++++++++++++++++--------
1 file changed, 19 insertions(+), 8 deletions(-)
diff --git a/compiler/simplCore/Simplify.hs b/compiler/simplCore/Simplify.hs
index 7d83be6..e0cfc00 100644
--- a/compiler/simplCore/Simplify.hs
+++ b/compiler/simplCore/Simplify.hs
@@ -42,7 +42,7 @@ import CoreOpt ( pushCoTyArg, pushCoValArg
import Rules ( mkRuleInfo, lookupRule, getRules )
--import TysPrim ( intPrimTy ) -- temporalily commented out. See #8326
import BasicTypes ( TopLevelFlag(..), isNotTopLevel, isTopLevel,
- RecFlag(..) )
+ RecFlag(..), isOneOcc )
import MonadUtils ( foldlM, mapAccumLM, liftIO )
import Maybes ( isJust, fromJust, orElse, catMaybes )
--import Unique ( hasKey ) -- temporalily commented out. See #8326
@@ -1744,14 +1744,16 @@ exitify exitUniques pairs =
| is_exit = do
-- create an id for the exit path
u <- getUnique
- let res_ty = exprType e
- args = filter (`elemVarSet` fvs) captured
- args_tys = map idType args
- ty = mkFunTys args_tys res_ty
- v = mkSysLocal (fsLit "exit") u ty `asJoinId` length args
+ let args = filter (`elemVarSet` fvs) captured
rhs = mkLams args e
- e' = mkVarApps (Var v) args
- addExit v rhs
+ ty = exprType rhs
+ join_arity = length args
+ v = mkSysLocal (fsLit "exit") u ty `asJoinId` join_arity
+ --v' = v `setIdUnfolding` mkCoreUnfolding InlineRhs False rhs UnfNever
+ v' = v `setIdOccInfo` exit_occ_info
+
+ e' = mkVarApps (Var v') args
+ addExit v' rhs
return e'
where
-- An exit expression has no recursive calls
@@ -1761,6 +1763,10 @@ exitify exitUniques pairs =
is_interesting = not (isEmptyVarSet (fvs `minusVarSet` mkVarSet captured))
fvs = exprFreeVars e
+ exit_occ_info = OneOcc { occ_in_lam = True
+ , occ_one_br = True
+ , occ_int_cxt = False
+ , occ_tail = AlwaysTailCalled join_arity }
go captured (Case scrut bndr ty alts) = do
alts' <- mapM (goAlt (bndr:captured)) alts
@@ -3477,6 +3483,11 @@ simplLetUnfolding :: SimplEnv-> TopLevelFlag
simplLetUnfolding env top_lvl cont_mb id new_rhs unf
| isStableUnfolding unf
= simplUnfolding env top_lvl cont_mb id unf
+ -- A join point that occurs under a lambda: This means that
+ -- this join point is called from a recursive group, and we do not
+ -- want to inine them!
+ | isJoinId id, isOneOcc (idOccInfo id), occ_in_lam (idOccInfo id)
+ = return unf
| otherwise
= is_bottoming `seq` -- See Note [Force bottoming field]
do { dflags <- getDynFlags
More information about the ghc-commits
mailing list