Skip to content
Snippets Groups Projects
Commit 7e6bb343 authored by Joachim Breitner's avatar Joachim Breitner
Browse files

Speculative evaluate thunks known to Converge

This is an attempt to use the by-products of nested cpr analysis.
parent fca15ac5
No related merge requests found
......@@ -27,9 +27,9 @@ module Demand (
peelFV,
DmdResult, CPRResult,
isBotRes, isTopRes, resTypeArgDmd,
isBotRes, isTopRes, resTypeArgDmd,
topRes, convRes, botRes, cprProdRes, vanillaCprProdRes, cprSumRes,
appIsBottom, isBottomingSig, isConvSig, pprIfaceStrictSig,
appIsBottom, isBottomingSig, isConvSig, pprIfaceStrictSig,
trimCPRInfo, returnsCPR, returnsCPR_maybe,
StrictSig(..), mkStrictSig, mkClosedStrictSig, nopSig, botSig, cprProdSig, convergeSig,
isNopSig, splitStrictSig, increaseStrictSigArity,
......@@ -812,6 +812,10 @@ isBotRes :: DmdResult -> Bool
isBotRes Diverges = True
isBotRes _ = False
isConvRes :: DmdResult -> Bool
isConvRes (Converges {}) = True
isConvRes _ = False
trimCPRInfo :: Bool -> Bool -> DmdResult -> DmdResult
trimCPRInfo trim_all trim_sums res
= trimR res
......@@ -1439,6 +1443,9 @@ isNopSig (StrictSig ty) = isNopDmdType ty
isBottomingSig :: StrictSig -> Bool
isBottomingSig (StrictSig (DmdType _ _ res)) = isBotRes res
isConvSig :: StrictSig -> Bool
isConvSig (StrictSig (DmdType _ _ res)) = isConvRes res
nopSig, botSig :: StrictSig
nopSig = StrictSig nopDmdType
botSig = StrictSig botDmdType
......
......@@ -47,7 +47,7 @@ module Id (
-- ** Predicates on Ids
isImplicitId, isDeadBinder,
isStrictId,
isStrictId, isConvId,
isExportedId, isLocalId, isGlobalId,
isRecordSelector, isNaughtyRecordSelector,
isClassOpId_maybe, isDFunId,
......@@ -495,6 +495,11 @@ isStrictId id
-- Take the best of both strictnesses - old and new
(isStrictDmd (idDemandInfo id))
isConvId :: Id -> Bool
isConvId id
= ASSERT2( isId id, text "isConvId: not an id: " <+> ppr id )
(isConvSig (idStrictness id))
---------------------------------
-- UNFOLDING
idUnfolding :: Id -> Unfolding
......
......@@ -1347,7 +1347,7 @@ simplNonRecE env bndr (rhs, rhs_se) (bndrs, body) cont
; -- pprTrace "preInlineUncond" (ppr bndr <+> ppr rhs) $
simplLam (extendIdSubst env bndr (mkContEx rhs_se rhs)) bndrs body cont }
| isStrictId bndr -> -- Includes coercions
| isStrictId bndr || isConvId bndr -> -- Includes coercions
do { simplExprF (rhs_se `setFloats` env) rhs
(StrictBind bndr bndrs body env cont) }
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment