[commit: ghc] wip/nested-cpr: Apply IO stricness hack only to information about arguments (4f055ee)
git at git.haskell.org
git at git.haskell.org
Thu Dec 5 19:00:05 UTC 2013
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/nested-cpr
Link : http://ghc.haskell.org/trac/ghc/changeset/4f055ee8d890e23c8ad02a5864d0b6069420bbec/ghc
>---------------------------------------------------------------
commit 4f055ee8d890e23c8ad02a5864d0b6069420bbec
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Thu Nov 28 10:29:47 2013 +0000
Apply IO stricness hack only to information about arguments
but retain the CPR information in the result.
>---------------------------------------------------------------
4f055ee8d890e23c8ad02a5864d0b6069420bbec
compiler/basicTypes/Demand.lhs | 9 ++++++++-
compiler/stranal/DmdAnal.lhs | 4 +++-
compiler/stranal/WwLib.lhs | 3 ++-
3 files changed, 13 insertions(+), 3 deletions(-)
diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs
index 5f140df..aee44ba 100644
--- a/compiler/basicTypes/Demand.lhs
+++ b/compiler/basicTypes/Demand.lhs
@@ -20,7 +20,7 @@ module Demand (
DmdType(..), dmdTypeDepth, lubDmdType, bothDmdType,
topDmdType, botDmdType, mkDmdType, mkTopDmdType,
- addDemand,
+ addDemand, dmdTypeArgTop,
DmdEnv, emptyDmdEnv,
peelFV,
@@ -1132,6 +1132,13 @@ splitDmdTy :: DmdType -> (Demand, DmdType)
splitDmdTy (DmdType fv (dmd:dmds) res_ty) = (dmd, DmdType fv dmds res_ty)
splitDmdTy ty@(DmdType _ [] res_ty) = (resTypeArgDmd res_ty, ty)
+-- We want to forget what we know about the arguments, but keep the information
+-- of the result, see Note [IO Strictness Hack]
+dmdTypeArgTop :: DmdType -> DmdType
+dmdTypeArgTop d@(DmdType _ _ res)
+ = let (DmdType env' ds' res') = d `lubDmdType` topDmdType
+ in DmdType env' ds' (if opt_NestedCprOff then res' else res)
+
strictenDmd :: JointDmd -> CleanDemand
strictenDmd (JD {strd = s, absd = u})
= CD { sd = poke_s s, ud = poke_u u }
diff --git a/compiler/stranal/DmdAnal.lhs b/compiler/stranal/DmdAnal.lhs
index 9863610..0d7c8fe 100644
--- a/compiler/stranal/DmdAnal.lhs
+++ b/compiler/stranal/DmdAnal.lhs
@@ -310,9 +310,11 @@ dmdAnalAlt env dmd (con,bndrs,rhs)
(rhs_ty, rhs') = dmdAnal env dmd rhs
rhs_ty' = addDataConPatDmds con bndrs rhs_ty
(alt_ty, bndrs') = annotateBndrs env rhs_ty' bndrs
- final_alt_ty | io_hack_reqd = alt_ty `lubDmdType` topDmdType
+ final_alt_ty | io_hack_reqd = dmdTypeArgTop alt_ty
| otherwise = alt_ty
+ -- Note [IO Strictness Hack]
+ --
-- There's a hack here for I/O operations. Consider
-- case foo x s of { (# s, r #) -> y }
-- Is this strict in 'y'. Normally yes, but what if 'foo' is an I/O
diff --git a/compiler/stranal/WwLib.lhs b/compiler/stranal/WwLib.lhs
index 4acf255..7dfff78 100644
--- a/compiler/stranal/WwLib.lhs
+++ b/compiler/stranal/WwLib.lhs
@@ -32,6 +32,7 @@ import Maybes
import Util
import Outputable
import DynFlags
+import StaticFlags ( opt_NestedCprOff )
import FastString
\end{code}
@@ -503,7 +504,7 @@ deepSplitCprType_maybe :: ConTag -> Type -> Maybe (DataCon, [Type], [Type], Coer
deepSplitCprType_maybe con_tag ty
| let (co, ty1) = topNormaliseNewType_maybe ty `orElse` (mkReflCo Representational ty, ty)
, Just (tc, tc_args) <- splitTyConApp_maybe ty1
- , isDataTyCon tc
+ , isDataTyCon tc || (not opt_NestedCprOff && isUnboxedTupleTyCon tc)
, let cons = tyConDataCons tc
con = ASSERT( cons `lengthAtLeast` con_tag ) cons !! (con_tag - fIRST_TAG)
= Just (con, tc_args, dataConInstArgTys con tc_args, co)
More information about the ghc-commits
mailing list