[commit: ghc] master: Notes and code cosmetics (063a1b2)
git at git.haskell.org
git at git.haskell.org
Fri Jan 10 15:39:08 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/063a1b25459a9f1576bd5c29b6aa931b6b3da690/ghc
>---------------------------------------------------------------
commit 063a1b25459a9f1576bd5c29b6aa931b6b3da690
Author: Joachim Breitner <mail at joachim-breitner.de>
Date: Fri Jan 10 14:22:41 2014 +0000
Notes and code cosmetics
Explain why defaultDmd resTypeArgDmd are similar, but both needed, and
apply slight code cosmetics.
>---------------------------------------------------------------
063a1b25459a9f1576bd5c29b6aa931b6b3da690
compiler/basicTypes/Demand.lhs | 35 ++++++++++++++++++++++++-----------
1 file changed, 24 insertions(+), 11 deletions(-)
diff --git a/compiler/basicTypes/Demand.lhs b/compiler/basicTypes/Demand.lhs
index d408e6d..27ef491 100644
--- a/compiler/basicTypes/Demand.lhs
+++ b/compiler/basicTypes/Demand.lhs
@@ -27,7 +27,7 @@ module Demand (
peelFV,
DmdResult, CPRResult,
- isBotRes, isTopRes, resTypeArgDmd,
+ isBotRes, isTopRes,
topRes, botRes, cprProdRes, vanillaCprProdRes, cprSumRes,
appIsBottom, isBottomingSig, pprIfaceStrictSig,
trimCPRInfo, returnsCPR, returnsCPR_maybe,
@@ -819,15 +819,33 @@ retCPR_maybe (RetSum t) = Just t
retCPR_maybe RetProd = Just fIRST_TAG
retCPR_maybe NoCPR = Nothing
+-- See Notes [Default demand on free variales]
+-- and [defaultDmd vs. resTypeArgDmd]
+defaultDmd :: Termination r -> JointDmd
+defaultDmd Diverges = botDmd
+defaultDmd _ = absDmd
+
resTypeArgDmd :: DmdResult -> JointDmd
-- TopRes and BotRes are polymorphic, so that
-- BotRes === Bot -> BotRes === ...
-- TopRes === Top -> TopRes === ...
-- This function makes that concrete
+-- Also see Note [defaultDmd vs. resTypeArgDmd]
resTypeArgDmd r | isBotRes r = botDmd
resTypeArgDmd _ = topDmd
\end{code}
+Note [defaultDmd and resTypeArgDmd]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+These functions are similar: They express the demand on something not
+explictitly mentioned in the environment resp. the argument list. Yet they are
+different:
+ * Variables not mentioned in the free variables environment are definitely
+ unused, so we can use absDmd there.
+ * Further arguments *can* be used, of course. Hence topDmd is used.
+
+
%************************************************************************
%* *
Whether a demand justifies a w/w split
@@ -1020,12 +1038,11 @@ lubDmdType (DmdType fv1 ds1 r1) (DmdType fv2 ds2 r2)
where
lub_fv = plusVarEnv_CD lubDmd fv1 (defaultDmd r1) fv2 (defaultDmd r2)
- -- Extend the shorter argument list to match the longer
- lub_ds (d1:ds1) (d2:ds2) = lubDmd d1 d2 : lub_ds ds1 ds2
- lub_ds [] [] = []
- lub_ds ds1 [] = map (`lubDmd` resTypeArgDmd r2) ds1
- lub_ds [] ds2 = map (resTypeArgDmd r1 `lubDmd`) ds2
-
+ -- Extend the shorter argument list to match the longer, using resTypeArgDmd
+ lub_ds (d1:ds1) (d2:ds2) = lubDmd d1 d2 : lub_ds ds1 ds2
+ lub_ds (d1:ds1) [] = (d1 `lubDmd` resTypeArgDmd r2) : lub_ds ds1 []
+ lub_ds [] (d2:ds2) = (resTypeArgDmd r1 `lubDmd` d2) : lub_ds [] ds2
+ lub_ds [] [] = []
type BothDmdArg = (DmdEnv, Termination ())
@@ -1261,10 +1278,6 @@ peelFV (DmdType fv ds res) id = -- pprTrace "rfv" (ppr id <+> ppr dmd $$ ppr fv)
-- See note [Default demand on free variables]
dmd = lookupVarEnv fv id `orElse` defaultDmd res
-defaultDmd :: Termination r -> Demand
-defaultDmd Diverges = botDmd
-defaultDmd _ = absDmd
-
addDemand :: Demand -> DmdType -> DmdType
addDemand dmd (DmdType fv ds res) = DmdType fv (dmd:ds) res
\end{code}
More information about the ghc-commits
mailing list