From 5a535172d13b30c94766751d0bc21a494b8858ed Mon Sep 17 00:00:00 2001 From: Sebastian Graf <sebastian.graf@kit.edu> Date: Wed, 28 Sep 2022 16:36:08 +0200 Subject: [PATCH] Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231) Justification in #22231. Short form: In a demand like `1C1(C1(L))` it was too easy to confuse which `1` belongs to which `C`. Now that should be more obvious. Fixes #22231 --- compiler/GHC/Core/Opt/Arity.hs | 12 +-- compiler/GHC/Core/Opt/DmdAnal.hs | 14 ++-- compiler/GHC/Core/Opt/OccurAnal.hs | 2 +- compiler/GHC/Core/Opt/Simplify/Utils.hs | 6 +- compiler/GHC/Core/Opt/WorkWrap.hs | 8 +- compiler/GHC/Types/Basic.hs | 4 +- compiler/GHC/Types/Demand.hs | 78 +++++++++---------- docs/users_guide/using-optimisation.rst | 8 +- .../arityanal/should_compile/Arity01.stderr | 2 +- .../arityanal/should_compile/Arity02.stderr | 2 +- .../arityanal/should_compile/Arity04.stderr | 2 +- .../arityanal/should_compile/Arity05.stderr | 4 +- .../arityanal/should_compile/Arity06.stderr | 2 +- .../arityanal/should_compile/Arity08.stderr | 2 +- .../arityanal/should_compile/Arity11.stderr | 4 +- .../arityanal/should_compile/Arity14.stderr | 6 +- .../arityanal/should_compile/Arity15.stderr | 2 +- .../arityanal/should_compile/Arity16.stderr | 2 +- .../tests/determinism/determ004/determ004.hs | 4 +- .../should_compile/OpaqueNoSpecialise.stderr | 4 +- .../tests/simplCore/should_compile/T13156.hs | 2 +- .../simplCore/should_compile/T14152.stderr | 2 +- .../simplCore/should_compile/T14152a.stderr | 4 +- .../simplCore/should_compile/T18013.stderr | 2 +- .../simplCore/should_compile/T18355.stderr | 8 ++ .../simplCore/should_compile/T19890.stderr | 4 +- .../simplCore/should_compile/T21694b.stderr | 2 +- .../simplCore/should_compile/T21948.stderr | 6 +- .../simplCore/should_compile/T21960.stderr | 50 ++++++------ .../simplCore/should_compile/T7785.stderr | 4 +- .../stranal/should_compile/T18894.stderr | 10 +-- .../stranal/should_compile/T18894b.stderr | 4 +- .../stranal/should_compile/T18903.stderr | 2 +- .../stranal/should_compile/T20817.stderr | 2 +- testsuite/tests/stranal/should_run/T21717b.hs | 2 +- testsuite/tests/stranal/should_run/T9254.hs | 2 +- testsuite/tests/stranal/sigs/T16859.stderr | 4 +- testsuite/tests/stranal/sigs/T18957.stderr | 16 ++-- testsuite/tests/stranal/sigs/T19871.stderr | 4 +- testsuite/tests/stranal/sigs/T20746.stderr | 2 +- testsuite/tests/stranal/sigs/T21081.hs | 4 +- testsuite/tests/stranal/sigs/T21081.stderr | 12 +-- testsuite/tests/stranal/sigs/T21119.stderr | 8 +- testsuite/tests/stranal/sigs/T21717.stderr | 4 +- testsuite/tests/stranal/sigs/T21888.stderr | 12 +-- testsuite/tests/stranal/sigs/T5075.stderr | 4 +- testsuite/tests/stranal/sigs/UnsatFun.stderr | 12 +-- 47 files changed, 182 insertions(+), 174 deletions(-) diff --git a/compiler/GHC/Core/Opt/Arity.hs b/compiler/GHC/Core/Opt/Arity.hs index 77df389dfb9b..922c79b74624 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 86775592bb6a..36c512d65636 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 59158a0e9048..bf6393f29276 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 6a143c8be8bc..2a3a272f502e 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 711ce6dbd8c9..d4fac1f869c2 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 bb8dcde29f7c..d4dcf3cb6990 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 85a5fbb4e032..595634018733 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 diff --git a/docs/users_guide/using-optimisation.rst b/docs/users_guide/using-optimisation.rst index b5f8c5bb29a5..d3ca68a1df46 100644 --- a/docs/users_guide/using-optimisation.rst +++ b/docs/users_guide/using-optimisation.rst @@ -1354,7 +1354,7 @@ by saying ``-fno-wombat``. sd ::= card polymorphic sub-demand, card at every level | P(d,d,..) product sub-demand - | Ccard(sd) call sub-demand + | C(card,sd) call sub-demand For example, ``fst`` is strict in its argument, and also in the first component of the argument. It will not evaluate the argument's second @@ -1414,14 +1414,14 @@ by saying ``-fno-wombat``. maybe n _ Nothing = n maybe _ s (Just a) = s a - We give it demand signature ``<L><MCM(L)><1L>``. The ``CM(L)`` is a *call + We give it demand signature ``<L><MC(M,L)><1L>``. The ``C(M,L)`` is a *call sub-demand* that says "Called at most once, where the result is used according to ``L``". The expression ``f `seq` f 1`` puts ``f`` under - demand ``SC1(L)`` and serves as an example where the upper bound on + demand ``SC(1,L)`` and serves as an example where the upper bound on evaluation cardinality doesn't coincide with that of the call cardinality. Cardinality is always relative to the enclosing call cardinality, so - ``g 1 2 + g 3 4`` puts ``g`` under demand ``SCS(C1(L))``, which says + ``g 1 2 + g 3 4`` puts ``g`` under demand ``SC(S,C(1,L))``, which says "called multiple times (``S``), but every time it is called with one argument, it is applied exactly once to another argument (``1``)". diff --git a/testsuite/tests/arityanal/should_compile/Arity01.stderr b/testsuite/tests/arityanal/should_compile/Arity01.stderr index 40d65fe4ea5d..eba6d4bfca59 100644 --- a/testsuite/tests/arityanal/should_compile/Arity01.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity01.stderr @@ -41,7 +41,7 @@ F1.s1 = GHC.Num.Integer.IS 3# -- RHS size: {terms: 8, types: 7, coercions: 0, joins: 0/0} s :: forall {t1} {t2}. Num t1 => (t1 -> t2) -> t2 -[GblId, Arity=2, Str=<MP(A,A,A,A,A,A,1C1(L))><1C1(L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 60] 50 0}] +[GblId, Arity=2, Str=<MP(A,A,A,A,A,A,1C(1,L))><1C(1,L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 60] 50 0}] s = \ (@t) (@t1) ($dNum :: Num t) (f :: t -> t1) -> f (fromInteger @t $dNum F1.s1) -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} diff --git a/testsuite/tests/arityanal/should_compile/Arity02.stderr b/testsuite/tests/arityanal/should_compile/Arity02.stderr index 8f9c4eec0854..ee756cbf6591 100644 --- a/testsuite/tests/arityanal/should_compile/Arity02.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity02.stderr @@ -9,7 +9,7 @@ F2.f1 = GHC.Num.Integer.IS 0# -- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} f2f :: forall {t1} {t2}. (t1 -> Integer -> t2) -> t1 -> t2 -[GblId, Arity=2, Str=<1C1(C1(L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)}] +[GblId, Arity=2, Str=<1C(1,C(1,L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)}] f2f = \ (@t) (@t1) (h :: t -> Integer -> t1) (x :: t) -> h x F2.f1 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} diff --git a/testsuite/tests/arityanal/should_compile/Arity04.stderr b/testsuite/tests/arityanal/should_compile/Arity04.stderr index cd50e216627d..e1ade4ec1133 100644 --- a/testsuite/tests/arityanal/should_compile/Arity04.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity04.stderr @@ -15,7 +15,7 @@ f4g = \ (y :: Int) -> case y of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x Rec { -- RHS size: {terms: 17, types: 6, coercions: 0, joins: 0/0} f4h [Occ=LoopBreaker] :: (Int -> Int) -> Int -> Int -[GblId, Arity=2, Str=<1C1(L)><1P(SL)>, Unf=OtherCon []] +[GblId, Arity=2, Str=<1C(1,L)><1P(SL)>, Unf=OtherCon []] f4h = \ (f :: Int -> Int) (x :: Int) -> case x of wild { GHC.Types.I# x1 -> diff --git a/testsuite/tests/arityanal/should_compile/Arity05.stderr b/testsuite/tests/arityanal/should_compile/Arity05.stderr index 17a0fb668a5d..8632c955be06 100644 --- a/testsuite/tests/arityanal/should_compile/Arity05.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity05.stderr @@ -9,12 +9,12 @@ F5.f5g1 = GHC.Num.Integer.IS 1# -- RHS size: {terms: 12, types: 9, coercions: 0, joins: 0/0} f5g :: forall {a} {t}. Num a => (t -> a) -> t -> a -[GblId, Arity=3, Str=<SP(1C1(C1(L)),A,A,A,A,A,MC1(L))><MC1(L)><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 60 0] 90 0}] +[GblId, Arity=3, Str=<SP(1C(1,C(1,L)),A,A,A,A,A,MC(1,L))><MC(1,L)><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 60 0] 90 0}] f5g = \ (@a) (@t) ($dNum :: Num a) (h :: t -> a) (z :: t) -> + @a $dNum (h z) (fromInteger @a $dNum F5.f5g1) -- RHS size: {terms: 17, types: 12, coercions: 0, joins: 0/0} f5h :: forall {a} {t}. Num a => (t -> a) -> t -> (t -> a) -> a -[GblId, Arity=4, Str=<SP(SCS(C1(L)),A,A,A,A,A,MC1(L))><MC1(L)><L><MC1(L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [90 60 0 60] 150 0}] +[GblId, Arity=4, Str=<SP(SC(S,C(1,L)),A,A,A,A,A,MC(1,L))><MC(1,L)><L><MC(1,L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [90 60 0 60] 150 0}] f5h = \ (@a) (@t) ($dNum :: Num a) (f :: t -> a) (x :: t) (g :: t -> a) -> + @a $dNum (f x) (+ @a $dNum (g x) (fromInteger @a $dNum F5.f5g1)) -- RHS size: {terms: 4, types: 1, coercions: 0, joins: 0/0} diff --git a/testsuite/tests/arityanal/should_compile/Arity06.stderr b/testsuite/tests/arityanal/should_compile/Arity06.stderr index 88240eea387c..131d0331a9ba 100644 --- a/testsuite/tests/arityanal/should_compile/Arity06.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity06.stderr @@ -9,7 +9,7 @@ F6.f6f1 = 0 -- RHS size: {terms: 7, types: 6, coercions: 0, joins: 0/0} f6f :: forall {t1} {t2}. (t1 -> Integer -> t2) -> t1 -> t2 -[GblId, Arity=2, Str=<1C1(C1(L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)}] +[GblId, Arity=2, Str=<1C(1,C(1,L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=True)}] f6f = \ (@t) (@t1) (h :: t -> Integer -> t1) (x :: t) -> h x F6.f6f1 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} diff --git a/testsuite/tests/arityanal/should_compile/Arity08.stderr b/testsuite/tests/arityanal/should_compile/Arity08.stderr index 9885d5f158eb..22dcaf10fe2f 100644 --- a/testsuite/tests/arityanal/should_compile/Arity08.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity08.stderr @@ -4,7 +4,7 @@ Result size of Tidy Core = {terms: 24, types: 18, coercions: 0, joins: 0/0} -- RHS size: {terms: 20, types: 10, coercions: 0, joins: 0/0} f8f :: forall {p}. Num p => Bool -> p -> p -> p -[GblId, Arity=4, Str=<LP(SCS(C1(L)),A,MC1(C1(L)),A,A,A,A)><1L><L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [90 30 0 0] 140 0}] +[GblId, Arity=4, Str=<LP(SC(S,C(1,L)),A,MC(1,C(1,L)),A,A,A,A)><1L><L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [90 30 0 0] 140 0}] f8f = \ (@p) ($dNum :: Num p) (b :: Bool) (x :: p) (y :: p) -> case b of { diff --git a/testsuite/tests/arityanal/should_compile/Arity11.stderr b/testsuite/tests/arityanal/should_compile/Arity11.stderr index 82b162e53110..982f7ad58db0 100644 --- a/testsuite/tests/arityanal/should_compile/Arity11.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity11.stderr @@ -53,7 +53,7 @@ F11.fib1 = GHC.Num.Integer.IS 0# -- RHS size: {terms: 54, types: 27, coercions: 0, joins: 0/5} fib :: forall {t} {a}. (Eq t, Num t, Num a) => t -> a -[GblId, Arity=4, Str=<SP(SCS(C1(L)),A)><LP(A,LCL(C1(L)),A,A,A,A,L)><LP(LCS(C1(L)),A,A,A,A,A,MC1(L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 480 0}] +[GblId, Arity=4, Str=<SP(SC(S,C(1,L)),A)><LP(A,LC(L,C(1,L)),A,A,A,A,L)><LP(LC(S,C(1,L)),A,A,A,A,A,MC(1,L))><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 150 60 0] 480 0}] fib = \ (@t) (@a) ($dEq :: Eq t) ($dNum :: Num t) ($dNum1 :: Num a) (eta :: t) -> let { @@ -73,7 +73,7 @@ fib [LclId] lvl3 = fromInteger @t $dNum F11.fib1 } in letrec { - fib4 [Occ=LoopBreaker, Dmd=SCS(L)] :: t -> a + fib4 [Occ=LoopBreaker, Dmd=SC(S,L)] :: t -> a [LclId, Arity=1, Str=<L>, Unf=OtherCon []] fib4 = \ (ds :: t) -> diff --git a/testsuite/tests/arityanal/should_compile/Arity14.stderr b/testsuite/tests/arityanal/should_compile/Arity14.stderr index 6fccde58a1a5..1f08b32e9a67 100644 --- a/testsuite/tests/arityanal/should_compile/Arity14.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity14.stderr @@ -14,7 +14,7 @@ F14.f2 = GHC.Num.Integer.IS 1# -- RHS size: {terms: 36, types: 23, coercions: 0, joins: 0/3} f14 :: forall {t}. (Ord t, Num t) => t -> t -> t -> t -[GblId, Arity=4, Str=<SP(A,A,SCS(C1(L)),A,A,A,A,A)><LP(LCL(C1(L)),A,A,A,A,A,MC1(L))><L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 90 0 0] 310 0}] +[GblId, Arity=4, Str=<SP(A,A,SC(S,C(1,L)),A,A,A,A,A)><LP(LC(L,C(1,L)),A,A,A,A,A,MC(1,L))><L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 90 0 0] 310 0}] f14 = \ (@t) ($dOrd :: Ord t) ($dNum :: Num t) (eta :: t) (eta1 :: t) -> let { @@ -22,7 +22,7 @@ f14 [LclId] lvl = fromInteger @t $dNum F14.f2 } in letrec { - f3 [Occ=LoopBreaker, Dmd=SCS(C1(L))] :: t -> t -> t -> t + f3 [Occ=LoopBreaker, Dmd=SC(S,C(1,L))] :: t -> t -> t -> t [LclId, Arity=2, Str=<L><L>, Unf=OtherCon []] f3 = \ (n :: t) (x :: t) -> @@ -30,7 +30,7 @@ f14 False -> F14.f1 @t; True -> let { - v [Dmd=LCS(L)] :: t -> t + v [Dmd=LC(S,L)] :: t -> t [LclId] v = f3 n (+ @t $dNum x lvl) } in \ (y :: t) -> v (+ @t $dNum x y) diff --git a/testsuite/tests/arityanal/should_compile/Arity15.stderr b/testsuite/tests/arityanal/should_compile/Arity15.stderr index 689939ffefdd..59ef84cc6c49 100644 --- a/testsuite/tests/arityanal/should_compile/Arity15.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity15.stderr @@ -9,7 +9,7 @@ F15.f15f1 = 1 -- RHS size: {terms: 4, types: 3, coercions: 0, joins: 0/0} f15f :: forall {t}. (Integer -> t) -> t -[GblId, Arity=1, Str=<1C1(L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}] +[GblId, Arity=1, Str=<1C(1,L)>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=True)}] f15f = \ (@t) (h :: Integer -> t) -> h F15.f15f1 -- RHS size: {terms: 4, types: 1, coercions: 0, joins: 0/0} diff --git a/testsuite/tests/arityanal/should_compile/Arity16.stderr b/testsuite/tests/arityanal/should_compile/Arity16.stderr index 292f3808f7a2..2a495dd1f4f8 100644 --- a/testsuite/tests/arityanal/should_compile/Arity16.stderr +++ b/testsuite/tests/arityanal/should_compile/Arity16.stderr @@ -27,7 +27,7 @@ lvl1 = Control.Exception.Base.patError @GHC.Types.LiftedRep @() lvl Rec { -- RHS size: {terms: 31, types: 32, coercions: 0, joins: 0/0} zipWith2 [Occ=LoopBreaker] :: forall {t1} {t2} {a}. (t1 -> t2 -> a) -> [t1] -> [t2] -> [a] -[GblId, Arity=3, Str=<LCL(C1(L))><1L><1L>, Unf=OtherCon []] +[GblId, Arity=3, Str=<LC(L,C(1,L))><1L><1L>, Unf=OtherCon []] zipWith2 = \ (@t) (@t1) (@a) (f :: t -> t1 -> a) (ds :: [t]) (ds1 :: [t1]) -> case ds of { diff --git a/testsuite/tests/determinism/determ004/determ004.hs b/testsuite/tests/determinism/determ004/determ004.hs index 97d268f1fa27..12b74f282f73 100644 --- a/testsuite/tests/determinism/determ004/determ004.hs +++ b/testsuite/tests/determinism/determ004/determ004.hs @@ -46,7 +46,7 @@ $s$wsFoldr1_szbtK (Let1627448493XsSym4 x_azbOM m_azbFg ipv_szbwN ipv_szbwO)) [LclId, Arity=4, - Str=<L,U><L,U><L,U><C(S(C(S))),C(U(1*C1(U)))>] + Str=<L,U><L,U><L,U><C(S(C(S))),C(U(1*C(1,U)))>] $s$wsFoldr1_szbtK = \ (@ (m_azbFg :: a_afdP_azbON)) (@ (x_azbOM :: TyFun @@ -123,7 +123,7 @@ $s$wsFoldr1_szbtK = <a_afdP_azbON>_N <a_afdP_azbON>_N <Apply x_azbOM m_XzbGe>_N :: Sing (Apply x_azbOM m_XzbGe) ~R# R:Sing(->)f (Apply x_azbOM m_XzbGe)) - of wild_X3X { SLambda ds_XzbBr [Dmd=<C(S),1*C1(U)>] -> + of wild_X3X { SLambda ds_XzbBr [Dmd=<C(S),1*C(1,U)>] -> (ds_XzbBr @ (Foldr1 x_azbOM (ipv_XzbyV : ipv_XzbxR)) (($wsFoldr1_szbuc diff --git a/testsuite/tests/simplCore/should_compile/OpaqueNoSpecialise.stderr b/testsuite/tests/simplCore/should_compile/OpaqueNoSpecialise.stderr index a534137d149f..d5f5a410c69f 100644 --- a/testsuite/tests/simplCore/should_compile/OpaqueNoSpecialise.stderr +++ b/testsuite/tests/simplCore/should_compile/OpaqueNoSpecialise.stderr @@ -12,7 +12,7 @@ lvl = GHC.Num.Integer.IS 1# f [InlPrag=OPAQUE] :: forall {t}. Num t => t -> [t] [GblId, Arity=2, - Str=<LP(A,LCS(C1(L)),A,A,A,A,MC1(L))><L>, + Str=<LP(A,LC(S,C(1,L)),A,A,A,A,MC(1,L))><L>, Unf=OtherCon []] f = \ (@t) ($dNum :: Num t) (eta :: t) -> let { @@ -20,7 +20,7 @@ f = \ (@t) ($dNum :: Num t) (eta :: t) -> [LclId] lvl1 = fromInteger @t $dNum lvl } in letrec { - f1 [Occ=LoopBreaker, Dmd=SCS(L)] :: t -> [t] + f1 [Occ=LoopBreaker, Dmd=SC(S,L)] :: t -> [t] [LclId, Arity=1, Str=<L>, Unf=OtherCon []] f1 = \ (x :: t) -> GHC.Types.: @t x (f1 (- @t $dNum x lvl1)); } in f1 eta diff --git a/testsuite/tests/simplCore/should_compile/T13156.hs b/testsuite/tests/simplCore/should_compile/T13156.hs index 2ddfa2cefba9..5512787b1140 100644 --- a/testsuite/tests/simplCore/should_compile/T13156.hs +++ b/testsuite/tests/simplCore/should_compile/T13156.hs @@ -26,7 +26,7 @@ T13156.f [GblId, Arity=2, Caf=NoCafRefs, - Str=<C(S),1*C1(U)><L,U>, + Str=<C(S),1*C(1,U)><L,U>, Unf=OtherCon []] T13156.f = \ (@ p) diff --git a/testsuite/tests/simplCore/should_compile/T14152.stderr b/testsuite/tests/simplCore/should_compile/T14152.stderr index cc025625b941..4b68067c35d8 100644 --- a/testsuite/tests/simplCore/should_compile/T14152.stderr +++ b/testsuite/tests/simplCore/should_compile/T14152.stderr @@ -24,7 +24,7 @@ go :: forall t a. (Num a, Num t, Eq a, Eq t) => t -> a -> a [GblId, Arity=6, Caf=NoCafRefs, - Str=<L,U(C(C1(U)),A,C(C1(U)),A,A,A,1*C1(U))><L,U(A,C(C1(U)),A,A,A,A,C(U))><L,U(C(C1(U)),A)><S(C(C(S))L),U(C(C1(U)),A)><L,U><L,U>, + Str=<L,U(C(C(1,U)),A,C(C(1,U)),A,A,A,1*C(1,U))><L,U(A,C(C(1,U)),A,A,A,A,C(U))><L,U(C(C(1,U)),A)><S(C(C(S))L),U(C(C(1,U)),A)><L,U><L,U>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [150 150 30 60 0 0] 610 0}] diff --git a/testsuite/tests/simplCore/should_compile/T14152a.stderr b/testsuite/tests/simplCore/should_compile/T14152a.stderr index 0196c3695d09..606d3f4f67b0 100644 --- a/testsuite/tests/simplCore/should_compile/T14152a.stderr +++ b/testsuite/tests/simplCore/should_compile/T14152a.stderr @@ -124,7 +124,7 @@ T14152.go1 go :: forall t a. (Num a, Num t, Eq a, Eq t) => t -> a -> a [GblId, Arity=6, - Str=<L,U(C(C1(U)),A,C(C1(U)),A,A,A,1*C1(U))><L,U(A,C(C1(U)),A,A,A,A,C(U))><L,U(C(C1(U)),A)><S(C(C(S))L),U(C(C1(U)),A)><L,U><L,U>, + Str=<L,U(C(C(1,U)),A,C(C(1,U)),A,A,A,1*C(1,U))><L,U(A,C(C(1,U)),A,A,A,A,C(U))><L,U(C(C(1,U)),A)><S(C(C(S))L),U(C(C(1,U)),A)><L,U><L,U>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [120 120 30 60 0 0] 582 0}] @@ -156,7 +156,7 @@ go = case == @ t_a2l3 $dEq1_a2la ds_d2md lvl14_s2o2 of { False -> join { - $j_s2py [Dmd=<C(S),1*C1(U)>] :: Maybe a_a2i4 -> a_a2i4 + $j_s2py [Dmd=<C(S),1*C(1,U)>] :: Maybe a_a2i4 -> a_a2i4 [LclId[JoinId(1)], Arity=1, Str=<S,U>, Unf=OtherCon []] $j_s2py (thunk_s2nZ [OS=OneShot] :: Maybe a_a2i4) = let { diff --git a/testsuite/tests/simplCore/should_compile/T18013.stderr b/testsuite/tests/simplCore/should_compile/T18013.stderr index 719f70df19d7..76cfd792cc0c 100644 --- a/testsuite/tests/simplCore/should_compile/T18013.stderr +++ b/testsuite/tests/simplCore/should_compile/T18013.stderr @@ -138,7 +138,7 @@ mapMaybeRule [InlPrag=[2]] :: forall a b. Rule IO a b -> Rule IO (Maybe a) (Maybe b) [GblId, Arity=1, - Str=<1!P(L,LCS(C1(C1(P(L,1L)))))>, + Str=<1!P(L,LC(S,C(1,C(1,P(L,1L)))))>, Unf=Unf{Src=StableSystem, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False) diff --git a/testsuite/tests/simplCore/should_compile/T18355.stderr b/testsuite/tests/simplCore/should_compile/T18355.stderr index a21a492b6d85..62c4e1feec99 100644 --- a/testsuite/tests/simplCore/should_compile/T18355.stderr +++ b/testsuite/tests/simplCore/should_compile/T18355.stderr @@ -7,8 +7,16 @@ Result size of Tidy Core f :: forall {a}. Num a => a -> Bool -> a -> a [GblId, Arity=4, +<<<<<<< HEAD Str=<1P(MC1(C1(L)),MC1(C1(L)),A,A,A,A,A)><L><1L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, +||||||| parent of 75ae893f7c (Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231)) + Str=<S,1*U(1*C1(C1(U)),1*C1(C1(U)),A,A,A,A,A)><L,U><S,1*U><L,U>, + Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, +======= + Str=<S,1*U(1*C(1,C(1,U)),1*C(1,C(1,U)),A,A,A,A,A)><L,U><S,1*U><L,U>, + Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, +>>>>>>> 75ae893f7c (Demand: Format Call SubDemands `Cn(sd)` as `C(n,sd)` (#22231)) WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 0 70 0] 100 0}] f = \ (@a) diff --git a/testsuite/tests/simplCore/should_compile/T19890.stderr b/testsuite/tests/simplCore/should_compile/T19890.stderr index 9c9857edfc79..fc8f5b3aa482 100644 --- a/testsuite/tests/simplCore/should_compile/T19890.stderr +++ b/testsuite/tests/simplCore/should_compile/T19890.stderr @@ -14,7 +14,7 @@ T19890.foo1 [InlPrag=INLINABLE, Occ=LoopBreaker] :: forall {a}. Num a => Bool -> a -> a [GblId, Arity=3, - Str=<SP(SCS(C1(L)),A,A,A,A,A,L)><1L><L>, + Str=<SP(SC(S,C(1,L)),A,A,A,A,A,L)><1L><L>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [60 70 0] 230 0 Tmpl= \ (@a_aye) @@ -42,7 +42,7 @@ end Rec } foo :: forall a. Num a => Bool -> Wombat a [GblId, Arity=3, - Str=<SP(SCS(C1(L)),A,A,A,A,A,L)><1L><L>, + Str=<SP(SC(S,C(1,L)),A,A,A,A,A,L)><1L><L>, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=0,unsat_ok=True,boring_ok=True)}] diff --git a/testsuite/tests/simplCore/should_compile/T21694b.stderr b/testsuite/tests/simplCore/should_compile/T21694b.stderr index 2cd41cb17f0b..4d63a0913173 100644 --- a/testsuite/tests/simplCore/should_compile/T21694b.stderr +++ b/testsuite/tests/simplCore/should_compile/T21694b.stderr @@ -65,7 +65,7 @@ f = \ (@p_ax8) [LclId[JoinId(0)(Nothing)]] exit_X3 = (eta_B0, x_agu, eta1_B1) } in joinrec { - $wj_sM6 [InlPrag=[2], Occ=LoopBreaker, Dmd=SCS(!P(L,L,L))] + $wj_sM6 [InlPrag=[2], Occ=LoopBreaker, Dmd=SC(S,!P(L,L,L))] :: GHC.Prim.Int# -> (a_aL5, p_ax8, c_aL6) [LclId[JoinId(1)(Nothing)], Arity=1, Str=<1L>, Unf=OtherCon []] $wj_sM6 (ww_sM3 :: GHC.Prim.Int#) diff --git a/testsuite/tests/simplCore/should_compile/T21948.stderr b/testsuite/tests/simplCore/should_compile/T21948.stderr index 4f68cc588407..4928111b3eec 100644 --- a/testsuite/tests/simplCore/should_compile/T21948.stderr +++ b/testsuite/tests/simplCore/should_compile/T21948.stderr @@ -14,7 +14,7 @@ T21948.nf'1 -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) [GblId, Arity=5, - Str=<MC1(A)><MC1(L)><L><1!P(L)><L>, + Str=<MC(1,A)><MC(1,L)><L><1!P(L)><L>, Cpr=1(, 1), Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, @@ -91,7 +91,7 @@ T21948.nf'1 [LclId] lvl1_s11A = reduce_aBy lvl_s111 } in joinrec { - $wgo_s11i [InlPrag=[2], Occ=LoopBreaker, Dmd=SCS(C1(!P(L,L)))] + $wgo_s11i [InlPrag=[2], Occ=LoopBreaker, Dmd=SC(S,C(1,!P(L,L)))] :: GHC.Prim.Int64# -> GHC.Prim.State# GHC.Prim.RealWorld -> (# GHC.Prim.State# GHC.Prim.RealWorld, () #) @@ -114,7 +114,7 @@ T21948.nf'1 nf' :: forall b a. (b -> ()) -> (a -> b) -> a -> Int64 -> IO () [GblId, Arity=5, - Str=<MC1(A)><MC1(L)><L><1!P(L)><L>, + Str=<MC(1,A)><MC(1,L)><L><1!P(L)><L>, Cpr=1(, 1), Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, diff --git a/testsuite/tests/simplCore/should_compile/T21960.stderr b/testsuite/tests/simplCore/should_compile/T21960.stderr index aec9866e4672..c129d398eb65 100644 --- a/testsuite/tests/simplCore/should_compile/T21960.stderr +++ b/testsuite/tests/simplCore/should_compile/T21960.stderr @@ -11,7 +11,7 @@ encodeUtf8BuilderEscaped [InlPrag=INLINE (sat-args=1)] :: BP.BoundedPrim Word8 -> Text -> B.Builder [GblId, Arity=5, - Str=<M!P(L,LCS(C1(C1(!P(L,1L)))))><1!P(L,L,L)><1CL(C1(L))><1L><L>, + Str=<M!P(L,LC(S,C(1,C(1,!P(L,1L)))))><1!P(L,L,L)><1C(L,C(1,L))><1L><L>, Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=ALWAYS_IF(arity=1,unsat_ok=False,boring_ok=False) @@ -301,7 +301,7 @@ encodeUtf8BuilderEscaped case be_a1kE of { Data.ByteString.Builder.Prim.Internal.BP bx5_a27M ds1_a27N -> join { - $j_s28Z [Dmd=1C1(L)] + $j_s28Z [Dmd=1C(1,L)] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, B.BuildSignal r_a238 #) [LclId[JoinId(1)(Nothing)], Arity=1, Str=<1L>, Unf=OtherCon []] @@ -330,7 +330,7 @@ encodeUtf8BuilderEscaped :: GHC.Prim.State# GHC.Prim.RealWorld) -> letrec { $s$wouterLoop_s29Y [Occ=LoopBreaker, - Dmd=LCS(C1(C1(C1(!P(L,L)))))] + Dmd=LC(S,C(1,C(1,C(1,!P(L,L)))))] :: GHC.Prim.Addr# -> GHC.Prim.Addr# -> GHC.Prim.Int# @@ -396,7 +396,7 @@ encodeUtf8BuilderEscaped = GHC.Prim.-# iend_s27f sc2_s29U } in join { - $j3_s27P [Dmd=1C1(!P(L,L))] + $j3_s27P [Dmd=1C(1,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, @@ -415,7 +415,7 @@ encodeUtf8BuilderEscaped sc2_s29U y_a23f } in joinrec { $s$wgo_s2ai [Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -496,7 +496,7 @@ encodeUtf8BuilderEscaped joinrec { $wgo_Xk [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> Ptr Word8 @@ -641,7 +641,7 @@ encodeUtf8BuilderEscaped }; $wouterLoop_s28Y [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(L)))] + Dmd=SC(S,C(1,C(1,L)))] :: GHC.Prim.Int# -> B.BufferRange -> GHC.Prim.State# GHC.Prim.RealWorld @@ -709,7 +709,7 @@ encodeUtf8BuilderEscaped = GHC.Prim.-# iend_s27f ww_s28T } in join { - $j3_s27P [Dmd=1C1(!P(L,L))] + $j3_s27P [Dmd=1C(1,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, @@ -728,7 +728,7 @@ encodeUtf8BuilderEscaped ww_s28T y_a23f } in joinrec { $s$wgo_s29j [Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -808,7 +808,7 @@ encodeUtf8BuilderEscaped ipv1_a26M #) -> joinrec { $s$wgo1_s29t [Occ=LoopBreaker, - Dmd=LCS(C1(C1(!P(L,L))))] + Dmd=LC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -901,7 +901,7 @@ encodeUtf8BuilderEscaped }; $wgo_Xk [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> Ptr Word8 @@ -1055,7 +1055,7 @@ encodeUtf8BuilderEscaped [LclId] y1_s27t = GHC.Prim.-# iend_s27f bx1_d22N } in join { - $j2_s27P [Dmd=1C1(!P(L,L))] + $j2_s27P [Dmd=1C(1,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, B.BuildSignal r_a238 #) @@ -1066,7 +1066,7 @@ encodeUtf8BuilderEscaped [LclId] iendTmp_s27v = GHC.Prim.+# bx1_d22N y_a23f } in join { - exit_Xc [Dmd=LCS(C1(C1(!P(L,L))))] + exit_Xc [Dmd=LC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -1082,7 +1082,7 @@ encodeUtf8BuilderEscaped (ipv_s24F [OS=OneShot] :: GHC.Prim.Addr#) = letrec { $s$wouterLoop_s2bC [Occ=LoopBreaker, - Dmd=SCS(C1(C1(C1(!P(L,L)))))] + Dmd=SC(S,C(1,C(1,C(1,!P(L,L)))))] :: GHC.Prim.Addr# -> GHC.Prim.Addr# -> GHC.Prim.Int# @@ -1149,7 +1149,7 @@ encodeUtf8BuilderEscaped = GHC.Prim.-# iend_s27f sc2_s2by } in join { - $j4_Xn [Dmd=1C1(!P(L,L))] + $j4_Xn [Dmd=1C(1,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, @@ -1170,7 +1170,7 @@ encodeUtf8BuilderEscaped sc2_s2by y3_Xo } in joinrec { $s$wgo_s2bW [Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -1254,7 +1254,7 @@ encodeUtf8BuilderEscaped joinrec { $wgo_Xu [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> Ptr Word8 @@ -1400,7 +1400,7 @@ encodeUtf8BuilderEscaped }; $wouterLoop_s28Y [InlPrag=[2], Occ=LoopBreaker, - Dmd=LCS(C1(C1(L)))] + Dmd=LC(S,C(1,C(1,L)))] :: GHC.Prim.Int# -> B.BufferRange -> GHC.Prim.State# GHC.Prim.RealWorld @@ -1469,7 +1469,7 @@ encodeUtf8BuilderEscaped = GHC.Prim.-# iend_s27f ww1_s28T } in join { - $j4_Xn [Dmd=1C1(!P(L,L))] + $j4_Xn [Dmd=1C(1,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.State# GHC.Prim.RealWorld, @@ -1490,7 +1490,7 @@ encodeUtf8BuilderEscaped ww1_s28T y3_Xo } in joinrec { $s$wgo_s2b3 [Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -1573,7 +1573,7 @@ encodeUtf8BuilderEscaped ipv2_a26M #) -> joinrec { $s$wgo1_s2bd [Occ=LoopBreaker, - Dmd=LCS(C1(C1(!P(L,L))))] + Dmd=LC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# @@ -1666,7 +1666,7 @@ encodeUtf8BuilderEscaped }; $wgo_Xu [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> Ptr Word8 @@ -1810,7 +1810,7 @@ encodeUtf8BuilderEscaped $s$wouterLoop_s2bC ipv_s24F bx4_d22Q ww_s28F eta4_s28I } in joinrec { - $s$wgo_s2cO [Occ=LoopBreaker, Dmd=SCS(C1(C1(!P(L,L))))] + $s$wgo_s2cO [Occ=LoopBreaker, Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# -> GHC.Prim.Int# @@ -1860,7 +1860,7 @@ encodeUtf8BuilderEscaped { (# ipv_a26L, ipv1_a26M #) -> joinrec { $s$wgo1_s2cY [Occ=LoopBreaker, - Dmd=LCS(C1(C1(!P(L,L))))] + Dmd=LC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.State# GHC.Prim.RealWorld -> GHC.Prim.Addr# -> GHC.Prim.Int# @@ -1927,7 +1927,7 @@ encodeUtf8BuilderEscaped }; $wgo_Xd [InlPrag=[2], Occ=LoopBreaker, - Dmd=SCS(C1(C1(!P(L,L))))] + Dmd=SC(S,C(1,C(1,!P(L,L))))] :: GHC.Prim.Int# -> Ptr Word8 -> GHC.Prim.State# GHC.Prim.RealWorld diff --git a/testsuite/tests/simplCore/should_compile/T7785.stderr b/testsuite/tests/simplCore/should_compile/T7785.stderr index 504fdc1677a3..2f8bdf6bead4 100644 --- a/testsuite/tests/simplCore/should_compile/T7785.stderr +++ b/testsuite/tests/simplCore/should_compile/T7785.stderr @@ -75,7 +75,7 @@ shared f Int -> f Int [LclIdX, Arity=2, - Str=<UC1(CS(CS(U)))><U>, + Str=<UC(1,C(S,C(S,U)))><U>, RULES: "SPEC shared @[]" forall ($dMyFunctor_sHz :: MyFunctor []) (irred_sHA :: Domain [] Int). @@ -83,7 +83,7 @@ shared = $sshared_sHD] shared = \ (@(f_ayh :: * -> *)) - ($dMyFunctor_ayi [Dmd=UC1(CS(CS(U)))] :: MyFunctor f_ayh) + ($dMyFunctor_ayi [Dmd=UC(1,C(S,C(S,U)))] :: MyFunctor f_ayh) (irred_ayj :: Domain f_ayh Int) -> let { f_sHy :: f_ayh Int -> f_ayh Int diff --git a/testsuite/tests/stranal/should_compile/T18894.stderr b/testsuite/tests/stranal/should_compile/T18894.stderr index 93cb81244418..22c6f3b32d85 100644 --- a/testsuite/tests/stranal/should_compile/T18894.stderr +++ b/testsuite/tests/stranal/should_compile/T18894.stderr @@ -46,7 +46,7 @@ lvl :: Int lvl = GHC.Types.I# 0# -- RHS size: {terms: 42, types: 15, coercions: 0, joins: 0/1} -g2 [InlPrag=NOINLINE, Dmd=LCS(C1(!P(M!P(L),1!P(L))))] +g2 [InlPrag=NOINLINE, Dmd=LC(S,C(1,!P(M!P(L),1!P(L))))] :: Int -> Int -> (Int, Int) [LclId, Arity=2, @@ -147,7 +147,7 @@ lvl :: (Int, Int) lvl = (lvl, lvl) -- RHS size: {terms: 36, types: 10, coercions: 0, joins: 0/1} -g1 [InlPrag=NOINLINE, Dmd=LCL(!P(L,L))] :: Int -> (Int, Int) +g1 [InlPrag=NOINLINE, Dmd=LC(L,!P(L,L))] :: Int -> (Int, Int) [LclId, Arity=1, Str=<1!P(1L)>, @@ -264,7 +264,7 @@ lvl :: Int lvl = GHC.Types.I# 0# -- RHS size: {terms: 39, types: 17, coercions: 0, joins: 0/1} -$wg2 [InlPrag=NOINLINE, Dmd=LCS(C1(!P(M!P(L),1!P(L))))] +$wg2 [InlPrag=NOINLINE, Dmd=LC(S,C(1,!P(M!P(L),1!P(L))))] :: Int -> GHC.Prim.Int# -> (# Int, Int #) [LclId[StrictWorker([])], Arity=2, @@ -328,7 +328,7 @@ h2 } -- RHS size: {terms: 34, types: 14, coercions: 0, joins: 0/1} -$wg1 [InlPrag=NOINLINE, Dmd=LCL(!P(L,L))] +$wg1 [InlPrag=NOINLINE, Dmd=LC(L,!P(L,L))] :: GHC.Prim.Int# -> (# GHC.Prim.Int#, Int #) [LclId[StrictWorker([])], Arity=1, @@ -366,7 +366,7 @@ lvl :: (Int, Int) lvl = case $wg1 2# of { (# ww, ww #) -> (GHC.Types.I# ww, ww) } -- RHS size: {terms: 22, types: 16, coercions: 0, joins: 0/0} -$wh1 [InlPrag=[2], Dmd=LCS(!P(L))] :: GHC.Prim.Int# -> Int +$wh1 [InlPrag=[2], Dmd=LC(S,!P(L))] :: GHC.Prim.Int# -> Int [LclId[StrictWorker([])], Arity=1, Str=<1L>, diff --git a/testsuite/tests/stranal/should_compile/T18894b.stderr b/testsuite/tests/stranal/should_compile/T18894b.stderr index d9d950769b75..aee02bf18cc4 100644 --- a/testsuite/tests/stranal/should_compile/T18894b.stderr +++ b/testsuite/tests/stranal/should_compile/T18894b.stderr @@ -38,7 +38,7 @@ expensive (case n of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 1#) }, case n of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 2#) }) -- RHS size: {terms: 20, types: 11, coercions: 0, joins: 0/0} -eta [InlPrag=NOINLINE, Dmd=UCU(CS(U))] :: Int -> Int -> Int +eta [InlPrag=NOINLINE, Dmd=UCU(C(S,U))] :: Int -> Int -> Int [LclId, Arity=1, Str=<UP(U)>, @@ -130,7 +130,7 @@ $wexpensive case w of { GHC.Types.I# x -> GHC.Types.I# (GHC.Prim.+# x 2#) } #) -- RHS size: {terms: 19, types: 12, coercions: 0, joins: 0/0} -eta [InlPrag=NOINLINE, Dmd=UCU(CS(U))] :: Int -> Int -> Int +eta [InlPrag=NOINLINE, Dmd=UCU(C(S,U))] :: Int -> Int -> Int [LclId, Arity=2, Str=<MP(U)><SP(U)>, diff --git a/testsuite/tests/stranal/should_compile/T18903.stderr b/testsuite/tests/stranal/should_compile/T18903.stderr index 8110312a8bb2..38298db8c46a 100644 --- a/testsuite/tests/stranal/should_compile/T18903.stderr +++ b/testsuite/tests/stranal/should_compile/T18903.stderr @@ -56,7 +56,7 @@ h :: Int -> Int h = \ (m :: Int) -> case m of wild { GHC.Types.I# ds -> let { - $wg [InlPrag=NOINLINE, Dmd=MC1(!P(M!P(L),1!P(L)))] + $wg [InlPrag=NOINLINE, Dmd=MC(1,!P(M!P(L),1!P(L)))] :: GHC.Prim.Int# -> (# Int, Int #) [LclId, Arity=1, Str=<1L>, Unf=OtherCon []] $wg diff --git a/testsuite/tests/stranal/should_compile/T20817.stderr b/testsuite/tests/stranal/should_compile/T20817.stderr index c113c3c2d193..eb8e103c8f1a 100644 --- a/testsuite/tests/stranal/should_compile/T20817.stderr +++ b/testsuite/tests/stranal/should_compile/T20817.stderr @@ -234,7 +234,7 @@ Rec { -- RHS size: {terms: 34, types: 36, coercions: 0, joins: 0/0} $wg [InlPrag=[2], Occ=LoopBreaker, - Dmd=LCS(C1(C1(C1(C1(C1(C1(L)))))))] + Dmd=LC(S,C(1,C(1,C(1,C(1,C(1,C(1,L)))))))] :: forall {a} {b} {c} {d} {e} {t} {t} {t}. Bool -> a -> b -> c -> t -> t -> t -> (# a, b, c, t, t, t #) [LclId[StrictWorker([])], diff --git a/testsuite/tests/stranal/should_run/T21717b.hs b/testsuite/tests/stranal/should_run/T21717b.hs index ed614422156e..80b3ed00399d 100644 --- a/testsuite/tests/stranal/should_run/T21717b.hs +++ b/testsuite/tests/stranal/should_run/T21717b.hs @@ -2,7 +2,7 @@ import System.Environment import GHC.Exts g :: (Int -> (Int, Int)) -> Int --- Should *not* infer strictness SCS(P(SL,SL)) for h +-- Should *not* infer strictness SC(S,P(SL,SL)) for h -- Otherwise `main` could use CbV on the error exprs below g h = fst (h 0) + snd (h 1) {-# NOINLINE g #-} diff --git a/testsuite/tests/stranal/should_run/T9254.hs b/testsuite/tests/stranal/should_run/T9254.hs index 279eb5c1ec15..ae1837ba0e9b 100644 --- a/testsuite/tests/stranal/should_run/T9254.hs +++ b/testsuite/tests/stranal/should_run/T9254.hs @@ -5,7 +5,7 @@ import GHC.Exts f :: (() -> (# Int#, () #)) -> () {-# NOINLINE f #-} -- Strictness signature was (7.8.2) --- <C(S(LS)), 1*C1(U(A,1*U()))> +-- <C(S(LS)), 1*C(1,U(A,1*U()))> -- I.e. calls k, but discards first component of result f k = case k () of (# _, r #) -> r diff --git a/testsuite/tests/stranal/sigs/T16859.stderr b/testsuite/tests/stranal/sigs/T16859.stderr index afd96a800024..9f7c3c9e5da9 100644 --- a/testsuite/tests/stranal/sigs/T16859.stderr +++ b/testsuite/tests/stranal/sigs/T16859.stderr @@ -1,7 +1,7 @@ ==================== Strictness signatures ==================== T16859.bar: <1!A><L> -T16859.baz: <1L><1!P(L)><1C1(L)> +T16859.baz: <1L><1!P(L)><1C(1,L)> T16859.buz: <1!P(L,L)> T16859.foo: <1L><L> T16859.mkInternalName: <1!P(L)><1L><1L> @@ -27,7 +27,7 @@ T16859.n_uniq: 1 ==================== Strictness signatures ==================== T16859.bar: <1!A><L> -T16859.baz: <1L><1!P(L)><1C1(L)> +T16859.baz: <1L><1!P(L)><1C(1,L)> T16859.buz: <1!P(L,L)> T16859.foo: <1L><L> T16859.mkInternalName: <1!P(L)><1L><1L> diff --git a/testsuite/tests/stranal/sigs/T18957.stderr b/testsuite/tests/stranal/sigs/T18957.stderr index 04937d4028eb..94044e754bce 100644 --- a/testsuite/tests/stranal/sigs/T18957.stderr +++ b/testsuite/tests/stranal/sigs/T18957.stderr @@ -1,9 +1,9 @@ ==================== Strictness signatures ==================== -T18957.g: <MC1(L)><1L> -T18957.h1: <SCM(L)><1L> -T18957.h2: <1CM(L)><1L> -T18957.h3: <LCS(L)><1L> +T18957.g: <MC(1,L)><1L> +T18957.h1: <SC(M,L)><1L> +T18957.h2: <1C(M,L)><1L> +T18957.h3: <LC(S,L)><1L> T18957.seq': <1A><1L> @@ -18,10 +18,10 @@ T18957.seq': ==================== Strictness signatures ==================== -T18957.g: <MC1(L)><1L> -T18957.h1: <SCM(L)><1L> -T18957.h2: <1CM(L)><1L> -T18957.h3: <LCS(L)><1L> +T18957.g: <MC(1,L)><1L> +T18957.h1: <SC(M,L)><1L> +T18957.h2: <1C(M,L)><1L> +T18957.h3: <LC(S,L)><1L> T18957.seq': <1A><1L> diff --git a/testsuite/tests/stranal/sigs/T19871.stderr b/testsuite/tests/stranal/sigs/T19871.stderr index 13e67a28058d..41f557d08aab 100644 --- a/testsuite/tests/stranal/sigs/T19871.stderr +++ b/testsuite/tests/stranal/sigs/T19871.stderr @@ -14,7 +14,7 @@ T19871.f6: <1!P(A,A,A,A,A,1L,A,A,A,A,A,A)> T19871.f7: <1!P(A,A,A,A,A,A,1L,A,A,A,A,A)> T19871.f8: <1!P(A,A,A,A,A,A,A,1L,A,A,A,A)> T19871.f9: <1!P(A,A,A,A,A,A,A,A,1L,A,A,A)> -T19871.guarded: <MC1(L)><1P(SL,L,L,L,L,L,L,L,L,L,L,L)> +T19871.guarded: <MC(1,L)><1P(SL,L,L,L,L,L,L,L,L,L,L,L)> T19871.sumIO: <1!P(1L)><1!P(L)><L> T19871.update: <1P(SL,L,L,L,L,L,L,L,L,L,L,L)> @@ -56,7 +56,7 @@ T19871.f6: <1!P(A,A,A,A,A,1L,A,A,A,A,A,A)> T19871.f7: <1!P(A,A,A,A,A,A,1L,A,A,A,A,A)> T19871.f8: <1!P(A,A,A,A,A,A,A,1L,A,A,A,A)> T19871.f9: <1!P(A,A,A,A,A,A,A,A,1L,A,A,A)> -T19871.guarded: <MC1(L)><1P(SL,L,L,L,L,L,L,L,L,L,L,L)> +T19871.guarded: <MC(1,L)><1P(SL,L,L,L,L,L,L,L,L,L,L,L)> T19871.sumIO: <1!P(1L)><1!P(L)><L> T19871.update: <1P(SL,L,L,L,L,L,L,L,L,L,L,L)> diff --git a/testsuite/tests/stranal/sigs/T20746.stderr b/testsuite/tests/stranal/sigs/T20746.stderr index 65c3e5e29628..109bff9198a8 100644 --- a/testsuite/tests/stranal/sigs/T20746.stderr +++ b/testsuite/tests/stranal/sigs/T20746.stderr @@ -12,7 +12,7 @@ Foo.foogle: 1 ==================== Strictness signatures ==================== -Foo.f: <MP(A,1C1(L),A)><L> +Foo.f: <MP(A,1C(1,L),A)><L> Foo.foogle: <L><L> diff --git a/testsuite/tests/stranal/sigs/T21081.hs b/testsuite/tests/stranal/sigs/T21081.hs index e07ec410bc8c..540e9af5caff 100644 --- a/testsuite/tests/stranal/sigs/T21081.hs +++ b/testsuite/tests/stranal/sigs/T21081.hs @@ -11,7 +11,7 @@ f pr = (case pr of (a,b) -> a /= b, True) g :: Int -> (Bool, Bool) g x = let y = let z = odd x in (z,z) in f y --- | Should put demand `LCS(C1(L))` on `f`, telling us that whenever `myfoldl` +-- | Should put demand `LC(S,C(1,L))` on `f`, telling us that whenever `myfoldl` -- evaluates `f`, it will also call it at least once (`S`) and then always call -- it with a second argument (`1`). -- This in turn allows us to eta-reduce `(\a b -> f a b)` to `f` (not tested, @@ -20,7 +20,7 @@ myfoldl :: (a -> b -> a) -> a -> [b] -> a myfoldl f z [] = z myfoldl f !z (x:xs) = myfoldl (\a b -> f a b) (f z x) xs --- | Should put demand `LCL(C1(L))` on `f` +-- | Should put demand `LC(L,C(1,L))` on `f` blah :: (Int -> Int -> Int) -> Int -> Int blah f 0 = 0 blah f 1 = f `seq` 1 diff --git a/testsuite/tests/stranal/sigs/T21081.stderr b/testsuite/tests/stranal/sigs/T21081.stderr index 7cf5f7cdd889..e6d2f2c30988 100644 --- a/testsuite/tests/stranal/sigs/T21081.stderr +++ b/testsuite/tests/stranal/sigs/T21081.stderr @@ -1,6 +1,6 @@ ==================== Strictness signatures ==================== -T21081.blah: <LCL(C1(L))><1!P(1L)> +T21081.blah: <LC(L,C(1,L))><1!P(1L)> T21081.blurg: <S!P(SL)> T21081.blurg2: <S!P(SL)> T21081.call1: <MP(1L,A)> @@ -9,7 +9,7 @@ T21081.call3: <LP(ML,A)> T21081.call4: <MP(1L,A)><1A> T21081.call5: <MP(1L,A)><MA> T21081.call6: <MP(1L,A)><MP(1L,A)><1L> -T21081.do_blah: <LCS(C1(L))> +T21081.do_blah: <LC(S,C(1,L))> T21081.f: <MP(SL,SL)> T21081.fst': <1!P(1L,A)> T21081.g: <ML> @@ -17,7 +17,7 @@ T21081.h: <MP(ML,ML)><1!P(1L)> T21081.h2: <L><S!P(SL)> T21081.i: <1L><1L><MP(ML,ML)> T21081.j: <S!P(1L,1L)> -T21081.myfoldl: <LCS(C1(L))><1L><1L> +T21081.myfoldl: <LC(S,C(1,L))><1L><1L> T21081.snd': <1!P(A,1L)> @@ -46,7 +46,7 @@ T21081.snd': ==================== Strictness signatures ==================== -T21081.blah: <LCL(C1(L))><1!P(1L)> +T21081.blah: <LC(L,C(1,L))><1!P(1L)> T21081.blurg: <1!P(SL)> T21081.blurg2: <1!P(SL)> T21081.call1: <MP(1L,A)> @@ -55,7 +55,7 @@ T21081.call3: <LP(ML,A)> T21081.call4: <MP(1L,A)><1A> T21081.call5: <MP(1L,A)><MA> T21081.call6: <MP(1L,A)><MP(1L,A)><1L> -T21081.do_blah: <LCS(C1(L))> +T21081.do_blah: <LC(S,C(1,L))> T21081.f: <MP(SL,SL)> T21081.fst': <1!P(1L,A)> T21081.g: <ML> @@ -63,7 +63,7 @@ T21081.h: <MP(ML,ML)><1!P(1L)> T21081.h2: <L><1!P(SL)> T21081.i: <1L><1L><MP(ML,ML)> T21081.j: <1!P(1L,1L)> -T21081.myfoldl: <LCS(C1(L))><1L><1L> +T21081.myfoldl: <LC(S,C(1,L))><1L><1L> T21081.snd': <1!P(A,1L)> diff --git a/testsuite/tests/stranal/sigs/T21119.stderr b/testsuite/tests/stranal/sigs/T21119.stderr index c20b876677c2..1c27b4c9a408 100644 --- a/testsuite/tests/stranal/sigs/T21119.stderr +++ b/testsuite/tests/stranal/sigs/T21119.stderr @@ -4,8 +4,8 @@ T21119.$fMyShow(,): <1!A> T21119.$fMyShowInt: <1!A> T21119.get: <1!P(1!P(L),1!P(L))><1!P(L)><1L> T21119.getIO: <1P(1L,ML)><1L><ML><L> -T21119.indexError: <1C1(L)><1!B><S!S><S>b -T21119.throwIndexError: <MC1(L)><MA><L><L><L>x +T21119.indexError: <1C(1,L)><1!B><S!S><S>b +T21119.throwIndexError: <MC(1,L)><MA><L><L><L>x @@ -24,7 +24,7 @@ T21119.$fMyShow(,): <1!A> T21119.$fMyShowInt: <1!A> T21119.get: <1!P(1!P(L),1!P(L))><1!P(L)><1L> T21119.getIO: <1P(1L,ML)><1L><ML><L> -T21119.indexError: <1C1(L)><1!B><S!S><S>b -T21119.throwIndexError: <MC1(L)><MA><L><L><L>x +T21119.indexError: <1C(1,L)><1!B><S!S><S>b +T21119.throwIndexError: <MC(1,L)><MA><L><L><L>x diff --git a/testsuite/tests/stranal/sigs/T21717.stderr b/testsuite/tests/stranal/sigs/T21717.stderr index 1dd0856f7b65..b97119153194 100644 --- a/testsuite/tests/stranal/sigs/T21717.stderr +++ b/testsuite/tests/stranal/sigs/T21717.stderr @@ -1,6 +1,6 @@ ==================== Strictness signatures ==================== -T21717.g: <SCS(P(ML,ML))> +T21717.g: <SC(S,P(ML,ML))> @@ -10,6 +10,6 @@ T21717.g: 1 ==================== Strictness signatures ==================== -T21717.g: <SCS(P(ML,ML))> +T21717.g: <SC(S,P(ML,ML))> diff --git a/testsuite/tests/stranal/sigs/T21888.stderr b/testsuite/tests/stranal/sigs/T21888.stderr index 26681355f0d9..d52d0c7d78f0 100644 --- a/testsuite/tests/stranal/sigs/T21888.stderr +++ b/testsuite/tests/stranal/sigs/T21888.stderr @@ -1,11 +1,11 @@ ==================== Strictness signatures ==================== Data.MemoTrie.$fHasTrie(): <L> -Data.MemoTrie.$fHasTrie(,): <1C1(L)><LCS(L)><L> +Data.MemoTrie.$fHasTrie(,): <1C(1,L)><LC(S,L)><L> Data.MemoTrie.$fHasTrieBool: <1!P(L,L)> -Data.MemoTrie.$fHasTrieEither: <1C1(L)><1C1(L)><1!P(L,L)> +Data.MemoTrie.$fHasTrieEither: <1C(1,L)><1C(1,L)><1!P(L,L)> Data.MemoTrie.$fHasTrieInteger: <1!P(1!P(S,1!P(1!P(S,1L),1!P(S,1L))),1!P(S,1!P(1!P(S,1L),1!P(S,1L))))>b -Data.MemoTrie.$fHasTrieList: <SCS(L)><1!P(L,L)> +Data.MemoTrie.$fHasTrieList: <SC(S,L)><1!P(L,L)> @@ -21,10 +21,10 @@ Data.MemoTrie.$fHasTrieList: ==================== Strictness signatures ==================== Data.MemoTrie.$fHasTrie(): <L> -Data.MemoTrie.$fHasTrie(,): <1C1(L)><LCS(L)><L> +Data.MemoTrie.$fHasTrie(,): <1C(1,L)><LC(S,L)><L> Data.MemoTrie.$fHasTrieBool: <1!P(L,L)> -Data.MemoTrie.$fHasTrieEither: <1C1(L)><1C1(L)><1!P(L,L)> +Data.MemoTrie.$fHasTrieEither: <1C(1,L)><1C(1,L)><1!P(L,L)> Data.MemoTrie.$fHasTrieInteger: <1!P(1!P(B,1!P(1!P(B,1!P(L,L)),1!P(B,1!P(L,L)))),1!P(B,1!P(1!B,1!B)))>b -Data.MemoTrie.$fHasTrieList: <SCS(L)><1!P(L,L)> +Data.MemoTrie.$fHasTrieList: <SC(S,L)><1!P(L,L)> diff --git a/testsuite/tests/stranal/sigs/T5075.stderr b/testsuite/tests/stranal/sigs/T5075.stderr index 4cebcf85ae1d..a3eea5d2cdec 100644 --- a/testsuite/tests/stranal/sigs/T5075.stderr +++ b/testsuite/tests/stranal/sigs/T5075.stderr @@ -1,6 +1,6 @@ ==================== Strictness signatures ==================== -T5075.f: <SP(A,A,SCS(C1(L)),A,A,A,A,A)><LP(A,A,LCS(C1(L)),A,A,A,L)><L> +T5075.f: <SP(A,A,SC(S,C(1,L)),A,A,A,A,A)><LP(A,A,LC(S,C(1,L)),A,A,A,L)><L> T5075.g: <1L><S!P(L)> T5075.h: <S!P(L)> @@ -14,7 +14,7 @@ T5075.h: ==================== Strictness signatures ==================== -T5075.f: <SP(A,A,SCS(C1(L)),A,A,A,A,A)><LP(A,A,LCS(C1(L)),A,A,A,L)><L> +T5075.f: <SP(A,A,SC(S,C(1,L)),A,A,A,A,A)><LP(A,A,LC(S,C(1,L)),A,A,A,L)><L> T5075.g: <1L><S!P(L)> T5075.h: <1!P(L)> diff --git a/testsuite/tests/stranal/sigs/UnsatFun.stderr b/testsuite/tests/stranal/sigs/UnsatFun.stderr index cb606f5c0235..c6f131d8cb06 100644 --- a/testsuite/tests/stranal/sigs/UnsatFun.stderr +++ b/testsuite/tests/stranal/sigs/UnsatFun.stderr @@ -4,9 +4,9 @@ UnsatFun.f: <1!P(S)><B>b UnsatFun.g: <1!P(S)>b UnsatFun.g': <MS> UnsatFun.g3: <A> -UnsatFun.h: <1C1(L)> -UnsatFun.h2: <1L><MC1(L)> -UnsatFun.h3: <1C1(A)> +UnsatFun.h: <1C(1,L)> +UnsatFun.h2: <1L><MC(1,L)> +UnsatFun.h3: <1C(1,A)> @@ -26,8 +26,8 @@ UnsatFun.f: <1!P(S)><B>b UnsatFun.g: <1!P(S)>b UnsatFun.g': <MS> UnsatFun.g3: <A> -UnsatFun.h: <1C1(L)> -UnsatFun.h2: <1L><MC1(L)> -UnsatFun.h3: <1C1(A)> +UnsatFun.h: <1C(1,L)> +UnsatFun.h2: <1L><MC(1,L)> +UnsatFun.h3: <1C(1,A)> -- GitLab