summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/GHC/Core/Opt/Arity.hs12
-rw-r--r--compiler/GHC/Core/Opt/DmdAnal.hs14
-rw-r--r--compiler/GHC/Core/Opt/OccurAnal.hs2
-rw-r--r--compiler/GHC/Core/Opt/Simplify/Utils.hs6
-rw-r--r--compiler/GHC/Core/Opt/WorkWrap.hs8
-rw-r--r--compiler/GHC/Types/Basic.hs4
-rw-r--r--compiler/GHC/Types/Demand.hs78
7 files changed, 62 insertions, 62 deletions
diff --git a/compiler/GHC/Core/Opt/Arity.hs b/compiler/GHC/Core/Opt/Arity.hs
index 77df389dfb..922c79b746 100644
--- a/compiler/GHC/Core/Opt/Arity.hs
+++ b/compiler/GHC/Core/Opt/Arity.hs
@@ -977,7 +977,7 @@ idDemandOneShots bndr
call_arity = idCallArity bndr
dmd_one_shots :: [OneShotInfo]
- -- If the demand info is Cx(C1(C1(.))) then we know that an
+ -- If the demand info is C(x,C(1,C(1,.))) then we know that an
-- application to one arg is also an application to three
dmd_one_shots = argOneShots (idDemandInfo bndr)
@@ -1086,10 +1086,10 @@ uses info from both Call Arity and demand analysis.
We may have /more/ call demands from the calls than we have lambdas
in the binding. E.g.
let f1 = \x. g x x in ...(f1 p q r)...
- -- Demand on f1 is Cx(C1(C1(L)))
+ -- Demand on f1 is C(x,C(1,C(1,L)))
let f2 = \y. error y in ...(f2 p q r)...
- -- Demand on f2 is Cx(C1(C1(L)))
+ -- Demand on f2 is C(x,C(1,C(1,L)))
In both these cases we can eta expand f1 and f2 to arity 3.
But /only/ for called-once demands. Suppose we had
@@ -2522,11 +2522,11 @@ Let's take the simple example of #21261, where `g` (actually, `f`) is defined as
g c = c 1 2 + c 3 4
Then this is how the pieces are put together:
- * Demand analysis infers `<SCS(C1(L))>` for `g`'s demand signature
+ * Demand analysis infers `<SC(S,C(1,L))>` for `g`'s demand signature
* When the Simplifier next simplifies the argument in `g (\x y. e x y)`, it
looks up the *evaluation context* of the argument in the form of the
- sub-demand `CS(C1(L))` and stores it in the 'SimplCont'.
+ sub-demand `C(S,C(1,L))` and stores it in the 'SimplCont'.
(Why does it drop the outer evaluation cardinality of the demand, `S`?
Because it's irrelevant! When we simplify an expression, we do so under the
assumption that it is currently under evaluation.)
@@ -2535,7 +2535,7 @@ Then this is how the pieces are put together:
* Then the simplifier takes apart the lambda and simplifies the lambda group
and then calls 'tryEtaReduce' when rebuilding the lambda, passing the
- evaluation context `CS(C1(L))` along. Then we simply peel off 2 call
+ evaluation context `C(S,C(1,L))` along. Then we simply peel off 2 call
sub-demands `Cn` and see whether all of the n's (here: `S=C_1N` and
`1=C_11`) were strict. And strict they are! Thus, it will eta-reduce
`\x y. e x y` to `e`.
diff --git a/compiler/GHC/Core/Opt/DmdAnal.hs b/compiler/GHC/Core/Opt/DmdAnal.hs
index 86775592bb..36c512d656 100644
--- a/compiler/GHC/Core/Opt/DmdAnal.hs
+++ b/compiler/GHC/Core/Opt/DmdAnal.hs
@@ -157,7 +157,7 @@ Consider a CoreProgram like
where e* are exported, but n* are not.
Intuitively, we can see that @n1@ is only ever called with two arguments
and in every call site, the first component of the result of the call
-is evaluated. Thus, we'd like it to have idDemandInfo @LCL(CM(P(1L,A))@.
+is evaluated. Thus, we'd like it to have idDemandInfo @LC(L,C(M,P(1L,A))@.
NB: We may *not* give e2 a similar annotation, because it is exported and
external callers might use it in arbitrary ways, expressed by 'topDmd'.
This can then be exploited by Nested CPR and eta-expansion,
@@ -671,7 +671,7 @@ There are several wrinkles:
values are evaluated even if they are not used. Example from #9254:
f :: (() -> (# Int#, () #)) -> ()
-- Strictness signature is
- -- <1C1(P(A,1L))>
+ -- <1C(1,P(A,1L))>
-- I.e. calls k, but discards first component of result
f k = case k () of (# _, r #) -> r
@@ -1176,10 +1176,10 @@ look a little puzzling. E.g.
( B -> j 4 )
( C -> \y. blah )
-The entire thing is in a C1(L) context, so j's strictness signature
+The entire thing is in a C(1,L) context, so j's strictness signature
will be [A]b
meaning one absent argument, returns bottom. That seems odd because
-there's a \y inside. But it's right because when consumed in a C1(L)
+there's a \y inside. But it's right because when consumed in a C(1,L)
context the RHS of the join point is indeed bottom.
Note [Demand signatures are computed for a threshold arity based on idArity]
@@ -1222,12 +1222,12 @@ analyse for more incoming arguments than idArity. Example:
then \y -> ... y ...
else \y -> ... y ...
-We'd analyse `f` under a unary call demand C1(L), corresponding to idArity
+We'd analyse `f` under a unary call demand C(1,L), corresponding to idArity
being 1. That's enough to look under the manifest lambda and find out how a
unary call would use `x`, but not enough to look into the lambdas in the if
branches.
-On the other hand, if we analysed for call demand C1(C1(L)), we'd get useful
+On the other hand, if we analysed for call demand C(1,C(1,L)), we'd get useful
strictness info for `y` (and more precise info on `x`) and possibly CPR
information, but
@@ -2335,7 +2335,7 @@ generator, though. So:
This way, correct information finds its way into the module interface
(strictness signatures!) and the code generator (single-entry thunks!)
-Note that, in contrast, the single-call information (CM(..)) /can/ be
+Note that, in contrast, the single-call information (C(M,..)) /can/ be
relied upon, as the simplifier tends to be very careful about not
duplicating actual function calls.
diff --git a/compiler/GHC/Core/Opt/OccurAnal.hs b/compiler/GHC/Core/Opt/OccurAnal.hs
index 59158a0e90..bf6393f292 100644
--- a/compiler/GHC/Core/Opt/OccurAnal.hs
+++ b/compiler/GHC/Core/Opt/OccurAnal.hs
@@ -2368,7 +2368,7 @@ A: Saturated applications: eg f e1 .. en
f's strictness signature into e1 .. en, but /only/ if n is enough to
saturate the strictness signature. A strictness signature like
- f :: C1(C1(L))LS
+ f :: C(1,C(1,L))LS
means that *if f is applied to three arguments* then it will guarantee to
call its first argument at most once, and to call the result of that at
diff --git a/compiler/GHC/Core/Opt/Simplify/Utils.hs b/compiler/GHC/Core/Opt/Simplify/Utils.hs
index 6a143c8be8..2a3a272f50 100644
--- a/compiler/GHC/Core/Opt/Simplify/Utils.hs
+++ b/compiler/GHC/Core/Opt/Simplify/Utils.hs
@@ -566,10 +566,10 @@ contEvalContext k = case k of
ApplyToTy{sc_cont=k} -> contEvalContext k
-- ApplyToVal{sc_cont=k} -> mkCalledOnceDmd $ contEvalContext k
-- Not 100% sure that's correct, . Here's an example:
- -- f (e x) and f :: <SCS(C1(L))>
+ -- f (e x) and f :: <SC(S,C(1,L))>
-- then what is the evaluation context of 'e' when we simplify it? E.g.,
- -- simpl e (ApplyToVal x $ Stop "CS(C1(L))")
- -- then it *should* be "C1(CS(C1(L))", so perhaps correct after all.
+ -- simpl e (ApplyToVal x $ Stop "C(S,C(1,L))")
+ -- then it *should* be "C(1,C(S,C(1,L))", so perhaps correct after all.
-- But for now we just panic:
ApplyToVal{} -> pprPanic "contEvalContext" (ppr k)
StrictArg{sc_fun=fun_info} -> subDemandIfEvaluated (head (ai_dmds fun_info))
diff --git a/compiler/GHC/Core/Opt/WorkWrap.hs b/compiler/GHC/Core/Opt/WorkWrap.hs
index 711ce6dbd8..d4fac1f869 100644
--- a/compiler/GHC/Core/Opt/WorkWrap.hs
+++ b/compiler/GHC/Core/Opt/WorkWrap.hs
@@ -925,15 +925,15 @@ attach OneShot annotations to the worker’s lambda binders.
Example:
-- Original function
- f [Demand=<L,1*C1(U)>] :: (a,a) -> a
+ f [Demand=<L,1*C(1,U)>] :: (a,a) -> a
f = \p -> ...
-- Wrapper
- f [Demand=<L,1*C1(U)>] :: a -> a -> a
+ f [Demand=<L,1*C(1,U)>] :: a -> a -> a
f = \p -> case p of (a,b) -> $wf a b
-- Worker
- $wf [Demand=<L,1*C1(C1(U))>] :: Int -> Int
+ $wf [Demand=<L,1*C(1,C(1,U))>] :: Int -> Int
$wf = \a b -> ...
We need to check whether the original function is called once, with
@@ -942,7 +942,7 @@ takes the arity of the original function (resp. the wrapper) and the demand on
the original function.
The demand on the worker is then calculated using mkWorkerDemand, and always of
-the form [Demand=<L,1*(C1(...(C1(U))))>]
+the form [Demand=<L,1*(C(1,...(C(1,U))))>]
Note [Thunk splitting]
~~~~~~~~~~~~~~~~~~~~~~
diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs
index bb8dcde29f..d4dcf3cb69 100644
--- a/compiler/GHC/Types/Basic.hs
+++ b/compiler/GHC/Types/Basic.hs
@@ -285,14 +285,14 @@ Moving parts:
f g x = Just (case g x of { ... })
Here 'f' is lazy in 'g', but it guarantees to call it no
- more than once. So g will get a C1(U) usage demand.
+ more than once. So g will get a C(1,U) usage demand.
* Occurrence analysis propagates this usage information
(in the demand signature of a function) to its calls.
Example, given 'f' above
f (\x.e) blah
- Since f's demand signature says it has a C1(U) usage demand on its
+ Since f's demand signature says it has a C(1,U) usage demand on its
first argument, the occurrence analyser sets the \x to be one-shot.
This is done via the occ_one_shots field of OccEnv.
diff --git a/compiler/GHC/Types/Demand.hs b/compiler/GHC/Types/Demand.hs
index 85a5fbb4e0..5956340187 100644
--- a/compiler/GHC/Types/Demand.hs
+++ b/compiler/GHC/Types/Demand.hs
@@ -618,10 +618,10 @@ multCard (Card a) (Card b)
-- * 'fst' puts demand @1P(1L,A)@ on its argument: It evaluates the argument
-- pair strictly and the first component strictly, but no nested info
-- beyond that (@L@). Its second argument is not used at all.
--- * '$' puts demand @1C1(L)@ on its first argument: It calls (@C@) the
+-- * '$' puts demand @1C(1,L)@ on its first argument: It calls (@C@) the
-- argument function with one argument, exactly once (@1@). No info
-- on how the result of that call is evaluated (@L@).
--- * 'maybe' puts demand @MCM(L)@ on its second argument: It evaluates
+-- * 'maybe' puts demand @MC(M,L)@ on its second argument: It evaluates
-- the argument function at most once ((M)aybe) and calls it once when
-- it is evaluated.
-- * @fst p + fst p@ puts demand @SP(SL,A)@ on @p@: It's @1P(1L,A)@
@@ -960,22 +960,22 @@ isWeakDmd dmd@(n :* _) = not (isStrict n) && is_plus_idem_dmd dmd
evalDmd :: Demand
evalDmd = C_1N :* topSubDmd
--- | First argument of 'GHC.Exts.maskAsyncExceptions#': @1C1(L)@.
+-- | First argument of 'GHC.Exts.maskAsyncExceptions#': @1C(1,L)@.
-- Called exactly once.
strictOnceApply1Dmd :: Demand
strictOnceApply1Dmd = C_11 :* mkCall C_11 topSubDmd
--- | First argument of 'GHC.Exts.atomically#': @SCS(L)@.
+-- | First argument of 'GHC.Exts.atomically#': @SC(S,L)@.
-- Called at least once, possibly many times.
strictManyApply1Dmd :: Demand
strictManyApply1Dmd = C_1N :* mkCall C_1N topSubDmd
--- | First argument of catch#: @MCM(L)@.
+-- | First argument of catch#: @MC(M,L)@.
-- Evaluates its arg lazily, but then applies it exactly once to one argument.
lazyApply1Dmd :: Demand
lazyApply1Dmd = C_01 :* mkCall C_01 topSubDmd
--- | Second argument of catch#: @MCM(C1(L))@.
+-- | Second argument of catch#: @MC(M,C(1,L))@.
-- Calls its arg lazily, but then applies it exactly once to an additional argument.
lazyApply2Dmd :: Demand
lazyApply2Dmd = C_01 :* mkCall C_01 (mkCall C_11 topSubDmd)
@@ -1017,11 +1017,11 @@ strictifyDictDmd _ dmd = dmd
lazifyDmd :: Demand -> Demand
lazifyDmd = multDmd C_01
--- | Wraps the 'SubDemand' with a one-shot call demand: @d@ -> @C1(d)@.
+-- | Wraps the 'SubDemand' with a one-shot call demand: @d@ -> @C(1,d)@.
mkCalledOnceDmd :: SubDemand -> SubDemand
mkCalledOnceDmd sd = mkCall C_11 sd
--- | @mkCalledOnceDmds n d@ returns @C1(C1...(C1 d))@ where there are @n@ @C1@'s.
+-- | @mkCalledOnceDmds n d@ returns @C(1,C1...C(1,d))@ where there are @n@ @C1@'s.
mkCalledOnceDmds :: Arity -> SubDemand -> SubDemand
mkCalledOnceDmds arity sd = iterate mkCalledOnceDmd sd !! arity
@@ -1080,9 +1080,9 @@ argOneShots (_ :* sd) = go sd
go _ = []
-- |
--- @saturatedByOneShots n CM(CM(...)) = True@
+-- @saturatedByOneShots n C(M,C(M,...)) = True@
-- <=>
--- There are at least n nested CM(..) calls.
+-- There are at least n nested C(M,..) calls.
-- See Note [Demand on the worker] in GHC.Core.Opt.WorkWrap
saturatedByOneShots :: Int -> Demand -> Bool
saturatedByOneShots _ AbsDmd = True
@@ -1195,8 +1195,8 @@ Premise:
myfoldl f z [] = z
myfoldl f !z (x:xs) = myfoldl (\a b -> f a b) (f z x) xs
```
- Here, we can give `f` a demand of `LCS(C1(L))` (instead of the lazier
- `LCL(C1(L))`) which says "Whenever `f` is evaluated (lazily), it is also
+ Here, we can give `f` a demand of `LC(S,C(1,L))` (instead of the lazier
+ `LC(L,C(1,L))`) which says "Whenever `f` is evaluated (lazily), it is also
called with two arguments".
And Note [Eta reduction based on evaluation context] means we can rewrite
`\a b -> f a b` to `f` in the call site of `myfoldl`. Nice!
@@ -1214,7 +1214,7 @@ Premise:
2 -> snd (g m)
_ -> uncurry (+) (g m)
```
- We want to give `g` the demand `MC1(P(MP(L),1P(L)))`, so we see that in each
+ We want to give `g` the demand `MC(1,P(MP(L),1P(L)))`, so we see that in each
call site of `g`, we are strict in the second component of the returned
pair. That in turn means that Nested CPR can unbox the result of the
division even though it might throw.
@@ -1226,14 +1226,14 @@ Note [SubDemand denotes at least one evaluation].
We *could* do better when both Demands are lazy already. Example
(fun 1, fun 2)
-Both args put Demand SCS(L) on `fun`. The lazy pair arg context lazifies
-this to LCS(L), and it would be reasonable to report this Demand on `fun` for
+Both args put Demand SC(S,L) on `fun`. The lazy pair arg context lazifies
+this to LC(S,L), and it would be reasonable to report this Demand on `fun` for
the entire pair expression; after all, `fun` is called whenever it is evaluated.
But our definition of `plusDmd` will compute
- LCS(L) + LCS(L) = (L+L)(M*CS(L) + M*CS(L)) = L(CL(L)) = L
+ LC(S,L) + LC(S,L) = (L+L)(M*C(S,L) + M*C(S,L)) = L(C(L,L)) = L
Which is clearly less precise.
Doing better here could mean to `lub` when both demands are lazy, e.g.,
- LCS(L) + LCS(L) = (L+L)(CS(L) ⊔ CS(L)) = L(CS(L))
+ LC(S,L) + LC(S,L) = (L+L)(C(S,L) ⊔ C(S,L)) = L(C(S,L))
Indeed that's what we did at one point between 9.4 and 9.6 after !7599, but it
means that we need a function `lubPlusSubDmd` that lubs on lower bounds but
plus'es upper bounds, implying maintenance challenges and complicated
@@ -1250,7 +1250,7 @@ pair, their interpretation is quite different. Example:
f x = fst x * snd x
-- f :: <SP(1L,1L)>, because 1P(1L,A)+1P(A,1L) = SP(1L,1L)
g x = fst (x 1) * snd (x 2)
- -- g :: <SCS(P(ML,ML))>, because 1C1(P(1L,A))+1C1(P(A,1L)) = SCS(P(ML,ML))
+ -- g :: <SC(S,P(ML,ML))>, because 1C(1,P(1L,A))+1C(1,P(A,1L)) = SC(S,P(ML,ML))
The point about this example is that both demands have P(A,1L)/P(1L,A) as
sub-expressions, but when these sub-demands occur
@@ -1296,21 +1296,21 @@ not matter for strictness analysis/lower bounds, thus it would be sound to use
Note [mkCall and plusSubDmd]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-We never rewrite a strict, non-absent Call sub-demand like CS(S) to a
+We never rewrite a strict, non-absent Call sub-demand like C(S,S) to a
polymorphic sub-demand like S, otherwise #21085 strikes. Consider the
following inequality (would also for M and 1 instead of L and S, but we forbid
such Polys):
- L+S = S = CS(S) < CS(L) = CL(L)+CS(S)
+ L+S = S = C(S,S) < C(S,L) = C(L,L)+C(S,S)
-Note that L=CL(L). If we also had S=CS(S), we'd be in trouble: Now
+Note that L=C(L,L). If we also had S=C(S,S), we'd be in trouble: Now
`plusSubDmd` would no longer maintain the equality relation on sub-demands,
much less monotonicity. Bad!
Clearly, `n <= Cn(n)` is unproblematic, as is `n >= Cn(n)` for any `n`
-except 1 and S. But `CS(S) >= S` would mean trouble, because then we'd get
-the problematic `CS(S) = S`. We have just established that `S < CS(S)`!
-As such, the rewrite CS(S) to S is anti-monotone and we forbid it, first
+except 1 and S. But `C(S,S) >= S` would mean trouble, because then we'd get
+the problematic `C(S,S) = S`. We have just established that `S < C(S,S)`!
+As such, the rewrite C(S,S) to S is anti-monotone and we forbid it, first
and foremost in `mkCall` (which is the only place that rewrites Cn(n) to n).
Crisis and #21085 averted!
@@ -1320,7 +1320,7 @@ Note [Computing one-shot info]
Consider a call
f (\pqr. e1) (\xyz. e2) e3
where f has usage signature
- <CM(CL(CM(L)))><CM(L)><L>
+ <C(M,C(L,C(M,L)))><C(M,L)><L>
Then argsOneShots returns a [[OneShotInfo]] of
[[OneShot,NoOneShotInfo,OneShot], [OneShot]]
The occurrence analyser propagates this one-shot infor to the
@@ -1371,7 +1371,7 @@ We then tried to store the Boxity in 'Demand' instead, for these reasons:
But then we regressed in T7837 (grep #19871 for boring specifics), which needed
to transfer an ambient unboxed *demand* on a dictionary selector to its argument
-dictionary, via a 'Call' sub-demand `C1(sd)`, as
+dictionary, via a 'Call' sub-demand `C(1,sd)`, as
Note [Demand transformer for a dictionary selector] explains. Annoyingly,
the boxity info has to be stored in the *sub-demand* `sd`! There's no demand
to store the boxity in. So we bit the bullet and now we store Boxity in
@@ -1919,16 +1919,16 @@ Consider
this has a strictness signature of
<1L><1L>b
meaning that we don't know what happens when we call err in weaker contexts than
-C1(C1(L)), like @err `seq` ()@ (1A) and @err 1 `seq` ()@ (CS(A)). We
+C(1,C(1,L)), like @err `seq` ()@ (1A) and @err 1 `seq` ()@ (C(S,A)). We
may not unleash the botDiv, hence assume topDiv. Of course, in
-@err 1 2 `seq` ()@ the incoming demand CS(CS(A)) is strong enough and we see
+@err 1 2 `seq` ()@ the incoming demand C(S,C(S,A)) is strong enough and we see
that the expression diverges.
Now consider a function
f g = g 1 2
-with signature <C1(C1(L))>, and the expression
+with signature <C(1,C(1,L))>, and the expression
f err `seq` ()
-now f puts a strictness demand of C1(C1(L)) onto its argument, which is unleashed
+now f puts a strictness demand of C(1,C(1,L)) onto its argument, which is unleashed
on err via the App rule. In contrast to weaker head strictness, this demand is
strong enough to unleash err's signature and hence we see that the whole
expression diverges!
@@ -1988,7 +1988,7 @@ Note [Demands from unsaturated function calls]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Consider a demand transformer d1 -> d2 -> r for f.
If a sufficiently detailed demand is fed into this transformer,
-e.g <C1(C1(L))> arising from "f x1 x2" in a strict, use-once context,
+e.g <C(1,C(1,L))> arising from "f x1 x2" in a strict, use-once context,
then d1 and d2 is precisely the demand unleashed onto x1 and x2 (similar for
the free variable environment) and furthermore the result information r is the
one we want to use.
@@ -1996,9 +1996,9 @@ one we want to use.
An anonymous lambda is also an unsaturated function all (needs one argument,
none given), so this applies to that case as well.
-But the demand fed into f might be less than C1(C1(L)). Then we have to
+But the demand fed into f might be less than C(1,C(1,L)). Then we have to
'multDmdType' the announced demand type. Examples:
- * Not strict enough, e.g. C1(C1(L)):
+ * Not strict enough, e.g. C(1,C(1,L)):
- We have to multiply all argument and free variable demands with C_01,
zapping strictness.
- We have to multiply divergence with C_01. If r says that f Diverges for sure,
@@ -2006,7 +2006,7 @@ But the demand fed into f might be less than C1(C1(L)). Then we have to
be passed. If the demand is lower, we may just as well converge.
If we were tracking definite convergence, than that would still hold under
a weaker demand than expected by the demand transformer.
- * Used more than once, e.g. CS(C1(L)):
+ * Used more than once, e.g. C(S,C(1,L)):
- Multiply with C_1N. Even if f puts a used-once demand on any of its argument
or free variables, if we call f multiple times, we may evaluate this
argument or free variable multiple times.
@@ -2076,8 +2076,8 @@ yields a more precise demand type:
incoming demand | demand type
--------------------------------
1A | <L><L>{}
- C1(C1(L)) | <1P(L)><L>{}
- C1(C1(1P(1P(L),A))) | <1P(A)><A>{}
+ C(1,C(1,L)) | <1P(L)><L>{}
+ C(1,C(1,1P(1P(L),A))) | <1P(A)><A>{}
Note that in the first example, the depth of the demand type was *higher* than
the arity of the incoming call demand due to the anonymous lambda.
@@ -2305,7 +2305,7 @@ element). Here's the diagram:
SubDemand --F_f----> DmdType
With
- α(C1(C1(_))) = >=2
+ α(C(1,C(1,_))) = >=2
α(_) = <2
γ(ty) = ty
and F_f being the abstract transformer of f's RHS and f_f being the abstracted
@@ -2335,7 +2335,7 @@ f d v = op_sel (sc_sel d) v
What do we learn about the demand on 'd'? Alas, we see only the
demand from 'sc_sel', namely '1P(1,A)'. We /don't/ see that 'd' really has a nested
-demand '1P(1P(A,1C1(1)),A)'. On the other hand, if we inlined the two selectors
+demand '1P(1P(A,1C(1,1)),A)'. On the other hand, if we inlined the two selectors
we'd have
f d x = case d of (x,_) ->
@@ -2582,7 +2582,7 @@ instance Outputable Demand where
-- | See Note [Demand notation]
instance Outputable SubDemand where
ppr (Poly b n) = pp_boxity b <> ppr n
- ppr (Call n sd) = char 'C' <> ppr n <> parens (ppr sd)
+ ppr (Call n sd) = char 'C' <> parens (ppr n <> comma <> ppr sd)
ppr (Prod b ds) = pp_boxity b <> char 'P' <> parens (fields ds)
where
fields [] = empty