[Git][ghc/ghc][wip/cpr-expandable-unfoldings] CprAnal: Don't attach CPR sigs to expandable bindings (#18154)

Sebastian Graf gitlab at gitlab.haskell.org
Wed May 6 17:16:04 UTC 2020



Sebastian Graf pushed to branch wip/cpr-expandable-unfoldings at Glasgow Haskell Compiler / GHC


Commits:
8bea8699 by Sebastian Graf at 2020-05-06T19:15:56+02:00
CprAnal: Don't attach CPR sigs to expandable bindings (#18154)

Instead, look through expandable unfoldings in `cprTransform`.
See the new Note [CPR for expandable unfoldings]:

```
GHC generates a lot of TyCon and KindRep bindings, one for each new data
declaration. Attaching CPR signatures to each of them is quite wasteful.
In general, DataCon application bindings
  * Never get WW'd, so their CPR signature should be irrelevant after analysis
  * Would need to be inlined to see their CPR
  * Recording (Nested!) CPR on them blows up interface file sizes
But we can't just stop giving DataCon application bindings the CPR property,
for example
  fac 0 = 1
  fac n = n * fac (n-1)
fac certainly has the CPR property and should be WW'd! But FloatOut will
transform the first clause to
  lvl = 1
  fac 0 = lvl
If lvl doesn't have the CPR property, fac won't either. So instead we keep on
looking through *expandable* unfoldings for these arity 0 bindings.
```

Fixes #18154.

- - - - -


29 changed files:

- compiler/GHC/Core/Opt/CprAnal.hs
- testsuite/tests/numeric/should_compile/T14170.stdout
- testsuite/tests/numeric/should_compile/T14465.stdout
- testsuite/tests/numeric/should_compile/T7116.stdout
- testsuite/tests/simplCore/should_compile/T13143.stderr
- testsuite/tests/simplCore/should_compile/T13543.stderr
- testsuite/tests/simplCore/should_compile/T18013.stderr
- testsuite/tests/simplCore/should_compile/T3717.stderr
- testsuite/tests/simplCore/should_compile/T3772.stdout
- testsuite/tests/simplCore/should_compile/T4908.stderr
- testsuite/tests/simplCore/should_compile/T4930.stderr
- testsuite/tests/simplCore/should_compile/T7360.stderr
- testsuite/tests/simplCore/should_compile/noinline01.stderr
- testsuite/tests/simplCore/should_compile/par01.stderr
- testsuite/tests/simplCore/should_compile/spec-inline.stderr
- testsuite/tests/stranal/should_compile/T10694.stderr
- testsuite/tests/stranal/sigs/BottomFromInnerLambda.stderr
- testsuite/tests/stranal/sigs/CaseBinderCPR.stderr
- testsuite/tests/stranal/sigs/DmdAnalGADTs.hs
- testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr
- testsuite/tests/stranal/sigs/HyperStrUse.stderr
- testsuite/tests/stranal/sigs/NewtypeArity.stderr
- testsuite/tests/stranal/sigs/StrAnalExample.stderr
- testsuite/tests/stranal/sigs/T12370.stderr
- testsuite/tests/stranal/sigs/T17932.stderr
- testsuite/tests/stranal/sigs/T5075.stderr
- testsuite/tests/stranal/sigs/T8569.stderr
- testsuite/tests/stranal/sigs/T8598.stderr
- testsuite/tests/stranal/sigs/UnsatFun.stderr


Changes:

=====================================
compiler/GHC/Core/Opt/CprAnal.hs
=====================================
@@ -231,9 +231,14 @@ cprTransform env id
     sig
   where
     sig
-      | isGlobalId id                   -- imported function or data con worker
+      -- See Note [CPR for expandable unfoldings]
+      | Just rhs <- lookupExpandableUnfolding id
+      = fst $ cprAnal env rhs
+      -- Imported function or data con worker
+      | isGlobalId id
       = getCprSig (idCprInfo id)
-      | Just sig <- lookupSigEnv env id -- local let-bound
+      -- Local let-bound
+      | Just sig <- lookupSigEnv env id
       = getCprSig sig
       | otherwise
       = topCprType
@@ -303,6 +308,8 @@ cprAnalBind top_lvl env id rhs
       | stays_thunk = trimCprTy rhs_ty
       -- See Note [CPR for sum types]
       | returns_sum = trimCprTy rhs_ty
+      -- See Note [CPR for expandable unfoldings]
+      | will_expand = topCprType
       | otherwise   = rhs_ty
     -- See Note [Arity trimming for CPR signatures]
     sig             = mkCprSigForArity (idArity id) rhs_ty'
@@ -316,6 +323,19 @@ cprAnalBind top_lvl env id rhs
     (_, ret_ty) = splitPiTys (idType id)
     not_a_prod  = isNothing (deepSplitProductType_maybe (ae_fam_envs env) ret_ty)
     returns_sum = not (isTopLevel top_lvl) && not_a_prod
+    -- See Note [CPR for expandable unfoldings]
+    will_expand = isJust (lookupExpandableUnfolding id)
+
+lookupExpandableUnfolding :: Id -> Maybe CoreExpr
+lookupExpandableUnfolding id
+  | idArity id == 0 = expandUnfolding_maybe (cprIdUnfolding id)
+  | otherwise       = Nothing
+
+cprIdUnfolding :: IdUnfoldingFun
+cprIdUnfolding id
+  -- There will only be phase 0 Simplifier runs after CprAnal
+  | isActiveIn 0 (idInlineActivation id) = idUnfolding id
+  | otherwise                            = noUnfolding
 
 {- Note [Arity trimming for CPR signatures]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@@ -626,6 +646,28 @@ fac won't have the CPR property here when we trim every thunk! But the
 assumption is that error cases are rarely entered and we are diverging anyway,
 so WW doesn't hurt.
 
+Should we also trim CPR on DataCon bindings?
+See Note [CPR for expandable unfoldings]!
+
+Note [CPR for expandable unfoldings]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+GHC generates a lot of TyCon and KindRep bindings, one for each new data
+declaration. Attaching CPR signatures to each of them is quite wasteful.
+In general, DataCon application bindings
+  * Never get WW'd, so their CPR signature should be irrelevant after analysis
+  * Would need to be inlined to see their CPR
+  * Recording (Nested!) CPR on them blows up interface file sizes
+But we can't just stop giving DataCon application bindings the CPR property,
+for example
+  fac 0 = 1
+  fac n = n * fac (n-1)
+fac certainly has the CPR property and should be WW'd! But FloatOut will
+transform the first clause to
+  lvl = 1
+  fac 0 = lvl
+If lvl doesn't have the CPR property, fac won't either. So instead we keep on
+looking through *expandable* unfoldings for these arity 0 bindings.
+
 Note [CPR examples]
 ~~~~~~~~~~~~~~~~~~~~
 Here are some examples (stranal/should_compile/T10482a) of the


=====================================
testsuite/tests/numeric/should_compile/T14170.stdout
=====================================
@@ -13,7 +13,6 @@ NatVal.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 NatVal.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 NatVal.$trModule3 = GHC.Types.TrNameS NatVal.$trModule4
@@ -28,7 +27,6 @@ NatVal.$trModule2 = "NatVal"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 NatVal.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 NatVal.$trModule1 = GHC.Types.TrNameS NatVal.$trModule2
@@ -36,7 +34,6 @@ NatVal.$trModule1 = GHC.Types.TrNameS NatVal.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 NatVal.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 NatVal.$trModule


=====================================
testsuite/tests/numeric/should_compile/T14465.stdout
=====================================
@@ -20,7 +20,6 @@ M.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 M.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 M.$trModule3 = GHC.Types.TrNameS M.$trModule4
@@ -35,7 +34,6 @@ M.$trModule2 = "M"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 M.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 M.$trModule1 = GHC.Types.TrNameS M.$trModule2
@@ -43,7 +41,6 @@ M.$trModule1 = GHC.Types.TrNameS M.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 M.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 M.$trModule = GHC.Types.Module M.$trModule3 M.$trModule1


=====================================
testsuite/tests/numeric/should_compile/T7116.stdout
=====================================
@@ -13,7 +13,6 @@ T7116.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7116.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7116.$trModule3 = GHC.Types.TrNameS T7116.$trModule4
@@ -28,7 +27,6 @@ T7116.$trModule2 = "T7116"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7116.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7116.$trModule1 = GHC.Types.TrNameS T7116.$trModule2
@@ -36,7 +34,6 @@ T7116.$trModule1 = GHC.Types.TrNameS T7116.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T7116.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T7116.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T13143.stderr
=====================================
@@ -33,7 +33,6 @@ T13143.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T13143.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T13143.$trModule3 = GHC.Types.TrNameS T13143.$trModule4
@@ -48,7 +47,6 @@ T13143.$trModule2 = "T13143"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T13143.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T13143.$trModule1 = GHC.Types.TrNameS T13143.$trModule2
@@ -56,7 +54,6 @@ T13143.$trModule1 = GHC.Types.TrNameS T13143.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T13143.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T13143.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T13543.stderr
=====================================
@@ -7,7 +7,7 @@ Foo.g: <S(SS),1*U(1*U(U),1*U(U))>
 
 
 ==================== Cpr signatures ====================
-Foo.$trModule: m1
+Foo.$trModule:
 Foo.f: m1
 Foo.g: m1
 


=====================================
testsuite/tests/simplCore/should_compile/T18013.stderr
=====================================
@@ -177,7 +177,6 @@ T18013.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T18013.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T18013.$trModule3 = GHC.Types.TrNameS T18013.$trModule4
@@ -192,7 +191,6 @@ T18013.$trModule2 = "T18013"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T18013.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T18013.$trModule1 = GHC.Types.TrNameS T18013.$trModule2
@@ -200,7 +198,6 @@ T18013.$trModule1 = GHC.Types.TrNameS T18013.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T18013.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T18013.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T3717.stderr
=====================================
@@ -13,7 +13,6 @@ T3717.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T3717.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T3717.$trModule3 = GHC.Types.TrNameS T3717.$trModule4
@@ -28,7 +27,6 @@ T3717.$trModule2 = "T3717"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T3717.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T3717.$trModule1 = GHC.Types.TrNameS T3717.$trModule2
@@ -36,7 +34,6 @@ T3717.$trModule1 = GHC.Types.TrNameS T3717.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T3717.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T3717.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T3772.stdout
=====================================
@@ -13,7 +13,6 @@ T3772.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T3772.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T3772.$trModule3 = GHC.Types.TrNameS T3772.$trModule4
@@ -28,7 +27,6 @@ T3772.$trModule2 = "T3772"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T3772.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T3772.$trModule1 = GHC.Types.TrNameS T3772.$trModule2
@@ -36,7 +34,6 @@ T3772.$trModule1 = GHC.Types.TrNameS T3772.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T3772.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T3772.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T4908.stderr
=====================================
@@ -13,7 +13,6 @@ T4908.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T4908.$trModule3 :: TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T4908.$trModule3 = GHC.Types.TrNameS T4908.$trModule4
@@ -28,7 +27,6 @@ T4908.$trModule2 = "T4908"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T4908.$trModule1 :: TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T4908.$trModule1 = GHC.Types.TrNameS T4908.$trModule2
@@ -36,7 +34,6 @@ T4908.$trModule1 = GHC.Types.TrNameS T4908.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T4908.$trModule :: Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T4908.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T4930.stderr
=====================================
@@ -13,7 +13,6 @@ T4930.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T4930.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T4930.$trModule3 = GHC.Types.TrNameS T4930.$trModule4
@@ -28,7 +27,6 @@ T4930.$trModule2 = "T4930"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T4930.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T4930.$trModule1 = GHC.Types.TrNameS T4930.$trModule2
@@ -36,7 +34,6 @@ T4930.$trModule1 = GHC.Types.TrNameS T4930.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T4930.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T4930.$trModule


=====================================
testsuite/tests/simplCore/should_compile/T7360.stderr
=====================================
@@ -64,7 +64,6 @@ T7360.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$trModule3 = GHC.Types.TrNameS T7360.$trModule4
@@ -79,7 +78,6 @@ T7360.$trModule2 = "T7360"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$trModule1 = GHC.Types.TrNameS T7360.$trModule2
@@ -87,7 +85,6 @@ T7360.$trModule1 = GHC.Types.TrNameS T7360.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 T7360.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 T7360.$trModule
@@ -110,7 +107,6 @@ T7360.$tcFoo2 = "Foo"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$tcFoo1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$tcFoo1 = GHC.Types.TrNameS T7360.$tcFoo2
@@ -118,7 +114,6 @@ T7360.$tcFoo1 = GHC.Types.TrNameS T7360.$tcFoo2
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T7360.$tcFoo :: GHC.Types.TyCon
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
 T7360.$tcFoo
@@ -147,7 +142,6 @@ T7360.$tc'Foo6 = "'Foo1"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo5 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$tc'Foo5 = GHC.Types.TrNameS T7360.$tc'Foo6
@@ -155,7 +149,6 @@ T7360.$tc'Foo5 = GHC.Types.TrNameS T7360.$tc'Foo6
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo1 :: GHC.Types.TyCon
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
 T7360.$tc'Foo1
@@ -177,7 +170,6 @@ T7360.$tc'Foo8 = "'Foo2"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo7 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$tc'Foo7 = GHC.Types.TrNameS T7360.$tc'Foo8
@@ -185,7 +177,6 @@ T7360.$tc'Foo7 = GHC.Types.TrNameS T7360.$tc'Foo8
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo2 :: GHC.Types.TyCon
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
 T7360.$tc'Foo2
@@ -212,7 +203,6 @@ T7360.$tc'Foo11 = "'Foo3"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo10 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T7360.$tc'Foo10 = GHC.Types.TrNameS T7360.$tc'Foo11
@@ -220,7 +210,6 @@ T7360.$tc'Foo10 = GHC.Types.TrNameS T7360.$tc'Foo11
 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
 T7360.$tc'Foo3 :: GHC.Types.TyCon
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
 T7360.$tc'Foo3


=====================================
testsuite/tests/simplCore/should_compile/noinline01.stderr
=====================================
@@ -14,7 +14,7 @@ Noinline01.$trModule4 :: GHC.Prim.Addr#
     "main"#;
 
 Noinline01.$trModule3 :: GHC.Types.TrName
-[GblId, Cpr=m1, Unf=OtherCon []] =
+[GblId, Unf=OtherCon []] =
     CCS_DONT_CARE GHC.Types.TrNameS! [Noinline01.$trModule4];
 
 Noinline01.$trModule2 :: GHC.Prim.Addr#
@@ -22,11 +22,11 @@ Noinline01.$trModule2 :: GHC.Prim.Addr#
     "Noinline01"#;
 
 Noinline01.$trModule1 :: GHC.Types.TrName
-[GblId, Cpr=m1, Unf=OtherCon []] =
+[GblId, Unf=OtherCon []] =
     CCS_DONT_CARE GHC.Types.TrNameS! [Noinline01.$trModule2];
 
 Noinline01.$trModule :: GHC.Types.Module
-[GblId, Cpr=m1, Unf=OtherCon []] =
+[GblId, Unf=OtherCon []] =
     CCS_DONT_CARE GHC.Types.Module! [Noinline01.$trModule3
                                      Noinline01.$trModule1];
 


=====================================
testsuite/tests/simplCore/should_compile/par01.stderr
=====================================
@@ -21,7 +21,7 @@ Par01.$trModule4 = "main"#
 
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 Par01.$trModule3 :: GHC.Types.TrName
-[GblId, Cpr=m1, Unf=OtherCon []]
+[GblId, Unf=OtherCon []]
 Par01.$trModule3 = GHC.Types.TrNameS Par01.$trModule4
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
@@ -31,12 +31,12 @@ Par01.$trModule2 = "Par01"#
 
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 Par01.$trModule1 :: GHC.Types.TrName
-[GblId, Cpr=m1, Unf=OtherCon []]
+[GblId, Unf=OtherCon []]
 Par01.$trModule1 = GHC.Types.TrNameS Par01.$trModule2
 
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 Par01.$trModule :: GHC.Types.Module
-[GblId, Cpr=m1, Unf=OtherCon []]
+[GblId, Unf=OtherCon []]
 Par01.$trModule
   = GHC.Types.Module Par01.$trModule3 Par01.$trModule1
 


=====================================
testsuite/tests/simplCore/should_compile/spec-inline.stderr
=====================================
@@ -13,7 +13,6 @@ Roman.$trModule4 = "main"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 Roman.$trModule3 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 Roman.$trModule3 = GHC.Types.TrNameS Roman.$trModule4
@@ -28,7 +27,6 @@ Roman.$trModule2 = "Roman"#
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 Roman.$trModule1 :: GHC.Types.TrName
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 Roman.$trModule1 = GHC.Types.TrNameS Roman.$trModule2
@@ -36,7 +34,6 @@ Roman.$trModule1 = GHC.Types.TrNameS Roman.$trModule2
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
 Roman.$trModule :: GHC.Types.Module
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
 Roman.$trModule
@@ -132,7 +129,6 @@ Roman.foo_go
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 Roman.foo2 :: Int
 [GblId,
- Cpr=m1,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 Roman.foo2 = GHC.Types.I# 6#
@@ -140,7 +136,6 @@ Roman.foo2 = GHC.Types.I# 6#
 -- RHS size: {terms: 2, types: 1, coercions: 0, joins: 0/0}
 Roman.foo1 :: Maybe Int
 [GblId,
- Cpr=m2,
  Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
          WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 Roman.foo1 = GHC.Maybe.Just @Int Roman.foo2


=====================================
testsuite/tests/stranal/should_compile/T10694.stderr
=====================================
@@ -6,26 +6,26 @@ Result size of Tidy Core = {terms: 74, types: 65, coercions: 0, joins: 0/4}
 T10694.$wpm [InlPrag=NOINLINE] :: Int -> Int -> (# Int, Int #)
 [GblId, Arity=2, Str=<L,U(U)><L,U(U)>, Unf=OtherCon []]
 T10694.$wpm
-  = \ (w_s1vj :: Int) (w1_s1vk :: Int) ->
+  = \ (w_s1v1 :: Int) (w1_s1v2 :: Int) ->
       let {
-        l_s1uR :: Int
+        l_s1uz :: Int
         [LclId]
-        l_s1uR
-          = case w_s1vj of { GHC.Types.I# x_aJ9 -> case w1_s1vk of { GHC.Types.I# y_aJc -> GHC.Types.I# (GHC.Prim.+# x_aJ9 y_aJc) } } } in
+        l_s1uz
+          = case w_s1v1 of { GHC.Types.I# x_aJ0 -> case w1_s1v2 of { GHC.Types.I# y_aJ3 -> GHC.Types.I# (GHC.Prim.+# x_aJ0 y_aJ3) } } } in
       let {
-        l1_s1uS :: Int
+        l1_s1uA :: Int
         [LclId]
-        l1_s1uS
-          = case w_s1vj of { GHC.Types.I# x_aJh -> case w1_s1vk of { GHC.Types.I# y_aJk -> GHC.Types.I# (GHC.Prim.-# x_aJh y_aJk) } } } in
+        l1_s1uA
+          = case w_s1v1 of { GHC.Types.I# x_aJ8 -> case w1_s1v2 of { GHC.Types.I# y_aJb -> GHC.Types.I# (GHC.Prim.-# x_aJ8 y_aJb) } } } in
       let {
-        l2_s1uT :: [Int]
+        l2_s1uB :: [Int]
         [LclId, Unf=OtherCon []]
-        l2_s1uT = GHC.Types.: @Int l1_s1uS (GHC.Types.[] @Int) } in
+        l2_s1uB = GHC.Types.: @Int l1_s1uA (GHC.Types.[] @Int) } in
       let {
-        l3_sJv :: [Int]
+        l3_sJm :: [Int]
         [LclId, Unf=OtherCon []]
-        l3_sJv = GHC.Types.: @Int l_s1uR l2_s1uT } in
-      (# GHC.List.$w!! @Int l3_sJv 0#, GHC.List.$w!! @Int l3_sJv 1# #)
+        l3_sJm = GHC.Types.: @Int l_s1uz l2_s1uB } in
+      (# GHC.List.$w!! @Int l3_sJm 0#, GHC.List.$w!! @Int l3_sJm 1# #)
 
 -- RHS size: {terms: 10, types: 11, coercions: 0, joins: 0/0}
 pm [InlPrag=NOUSERINLINE[0]] :: Int -> Int -> (Int, Int)
@@ -35,9 +35,9 @@ pm [InlPrag=NOUSERINLINE[0]] :: Int -> Int -> (Int, Int)
  Cpr=m1,
  Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
-         Tmpl= \ (w_s1vj [Occ=Once] :: Int) (w1_s1vk [Occ=Once] :: Int) ->
-                 case T10694.$wpm w_s1vj w1_s1vk of { (# ww1_s1vp [Occ=Once], ww2_s1vq [Occ=Once] #) -> (ww1_s1vp, ww2_s1vq) }}]
-pm = \ (w_s1vj :: Int) (w1_s1vk :: Int) -> case T10694.$wpm w_s1vj w1_s1vk of { (# ww1_s1vp, ww2_s1vq #) -> (ww1_s1vp, ww2_s1vq) }
+         Tmpl= \ (w_s1v1 [Occ=Once] :: Int) (w1_s1v2 [Occ=Once] :: Int) ->
+                 case T10694.$wpm w_s1v1 w1_s1v2 of { (# ww1_s1v7 [Occ=Once], ww2_s1v8 [Occ=Once] #) -> (ww1_s1v7, ww2_s1v8) }}]
+pm = \ (w_s1v1 :: Int) (w1_s1v2 :: Int) -> case T10694.$wpm w_s1v1 w1_s1v2 of { (# ww1_s1v7, ww2_s1v8 #) -> (ww1_s1v7, ww2_s1v8) }
 
 -- RHS size: {terms: 8, types: 9, coercions: 0, joins: 0/0}
 m :: Int -> Int -> Int
@@ -46,9 +46,9 @@ m :: Int -> Int -> Int
  Str=<L,U(U)><L,U(U)>,
  Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
          Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
-         Tmpl= \ (x_awt [Occ=Once] :: Int) (y_awu [Occ=Once] :: Int) ->
-                 case pm x_awt y_awu of { (_ [Occ=Dead], mr_aww [Occ=Once]) -> mr_aww }}]
-m = \ (x_awt :: Int) (y_awu :: Int) -> case T10694.$wpm x_awt y_awu of { (# ww1_s1vp, ww2_s1vq #) -> ww2_s1vq }
+         Tmpl= \ (x_awo [Occ=Once] :: Int) (y_awp [Occ=Once] :: Int) ->
+                 case pm x_awo y_awp of { (_ [Occ=Dead], mr_awr [Occ=Once]) -> mr_awr }}]
+m = \ (x_awo :: Int) (y_awp :: Int) -> case T10694.$wpm x_awo y_awp of { (# ww1_s1v7, ww2_s1v8 #) -> ww2_s1v8 }
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
 T10694.$trModule4 :: GHC.Prim.Addr#
@@ -57,9 +57,7 @@ T10694.$trModule4 = "main"#
 
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T10694.$trModule3 :: GHC.Types.TrName
-[GblId,
- Cpr=m1,
- Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T10694.$trModule3 = GHC.Types.TrNameS T10694.$trModule4
 
 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
@@ -69,17 +67,13 @@ T10694.$trModule2 = "T10694"#
 
 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
 T10694.$trModule1 :: GHC.Types.TrName
-[GblId,
- Cpr=m1,
- Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
 T10694.$trModule1 = GHC.Types.TrNameS T10694.$trModule2
 
 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
-T10694.$trModule :: GHC.Unit.Module
-[GblId,
- Cpr=m1,
- Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
-T10694.$trModule = GHC.Unit.Module T10694.$trModule3 T10694.$trModule1
+T10694.$trModule :: GHC.Types.Module
+[GblId, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+T10694.$trModule = GHC.Types.Module T10694.$trModule3 T10694.$trModule1
 
 
 


=====================================
testsuite/tests/stranal/sigs/BottomFromInnerLambda.stderr
=====================================
@@ -7,7 +7,7 @@ BottomFromInnerLambda.f: <S(S),1*U(U)>
 
 
 ==================== Cpr signatures ====================
-BottomFromInnerLambda.$trModule: m1
+BottomFromInnerLambda.$trModule:
 BottomFromInnerLambda.expensive: m1
 BottomFromInnerLambda.f:
 


=====================================
testsuite/tests/stranal/sigs/CaseBinderCPR.stderr
=====================================
@@ -6,7 +6,7 @@ CaseBinderCPR.f_list_cmp: <L,C(C1(U(U)))><S,1*U><S,1*U>
 
 
 ==================== Cpr signatures ====================
-CaseBinderCPR.$trModule: m1
+CaseBinderCPR.$trModule:
 CaseBinderCPR.f_list_cmp: m1
 
 


=====================================
testsuite/tests/stranal/sigs/DmdAnalGADTs.hs
=====================================
@@ -7,11 +7,13 @@ data D a where
     A :: D Int
     B :: D (Int -> Int)
 
+-- Doesn't have the CPR property anymore (#18154), but an expandable unfolding.
+-- The point of this test is that f' has the CPR property.
 hasCPR :: Int
 hasCPR = 1
 
 hasStrSig :: Int -> Int
-hasStrSig x = x
+hasStrSig x = x + 1
 
 diverges :: Int
 diverges = diverges


=====================================
testsuite/tests/stranal/sigs/DmdAnalGADTs.stderr
=====================================
@@ -9,21 +9,21 @@ DmdAnalGADTs.f: <S,1*U>
 DmdAnalGADTs.f': <S,1*U>
 DmdAnalGADTs.g: <S,1*U>
 DmdAnalGADTs.hasCPR:
-DmdAnalGADTs.hasStrSig: <S,1*U>
+DmdAnalGADTs.hasStrSig: <S,1*U(U)>
 
 
 
 ==================== Cpr signatures ====================
-DmdAnalGADTs.$tc'A: m1
-DmdAnalGADTs.$tc'B: m1
-DmdAnalGADTs.$tcD: m1
-DmdAnalGADTs.$trModule: m1
+DmdAnalGADTs.$tc'A:
+DmdAnalGADTs.$tc'B:
+DmdAnalGADTs.$tcD:
+DmdAnalGADTs.$trModule:
 DmdAnalGADTs.diverges: b
 DmdAnalGADTs.f:
 DmdAnalGADTs.f': m1
 DmdAnalGADTs.g:
-DmdAnalGADTs.hasCPR: m1
-DmdAnalGADTs.hasStrSig:
+DmdAnalGADTs.hasCPR:
+DmdAnalGADTs.hasStrSig: m1
 
 
 
@@ -37,6 +37,6 @@ DmdAnalGADTs.f: <S,1*U>
 DmdAnalGADTs.f': <S,1*U>
 DmdAnalGADTs.g: <S,1*U>
 DmdAnalGADTs.hasCPR:
-DmdAnalGADTs.hasStrSig: <S,1*U>
+DmdAnalGADTs.hasStrSig: <S,1*U(U)>
 
 


=====================================
testsuite/tests/stranal/sigs/HyperStrUse.stderr
=====================================
@@ -6,7 +6,7 @@ HyperStrUse.f: <S(SL),1*U(1*U(U),A)><S,1*U>
 
 
 ==================== Cpr signatures ====================
-HyperStrUse.$trModule: m1
+HyperStrUse.$trModule:
 HyperStrUse.f: m1
 
 


=====================================
testsuite/tests/stranal/sigs/NewtypeArity.stderr
=====================================
@@ -9,9 +9,9 @@ Test.t2: <S,1*U(U)><S,1*U(U)>
 
 
 ==================== Cpr signatures ====================
-Test.$tc'MkT: m1
-Test.$tcT: m1
-Test.$trModule: m1
+Test.$tc'MkT:
+Test.$tcT:
+Test.$trModule:
 Test.t: m1
 Test.t2: m1
 


=====================================
testsuite/tests/stranal/sigs/StrAnalExample.stderr
=====================================
@@ -6,7 +6,7 @@ StrAnalExample.foo: <S,1*U>
 
 
 ==================== Cpr signatures ====================
-StrAnalExample.$trModule: m1
+StrAnalExample.$trModule:
 StrAnalExample.foo:
 
 


=====================================
testsuite/tests/stranal/sigs/T12370.stderr
=====================================
@@ -7,7 +7,7 @@ T12370.foo: <S(SS),1*U(1*U(U),1*U(U))>
 
 
 ==================== Cpr signatures ====================
-T12370.$trModule: m1
+T12370.$trModule:
 T12370.bar: m1
 T12370.foo: m1
 


=====================================
testsuite/tests/stranal/sigs/T17932.stderr
=====================================
@@ -10,11 +10,11 @@ T17932.flags: <S(SS),1*U(1*U,1*U)>
 
 
 ==================== Cpr signatures ====================
-T17932.$tc'Options: m1
-T17932.$tc'X: m1
-T17932.$tcOptions: m1
-T17932.$tcX: m1
-T17932.$trModule: m1
+T17932.$tc'Options:
+T17932.$tc'X:
+T17932.$tcOptions:
+T17932.$tcX:
+T17932.$trModule:
 T17932.flags:
 
 


=====================================
testsuite/tests/stranal/sigs/T5075.stderr
=====================================
@@ -6,7 +6,7 @@ T5075.loop: <S(LLC(C(S))LLLLL),U(A,A,C(C1(U)),A,A,A,A,A)><L,U(A,A,C(C1(U)),A,A,A
 
 
 ==================== Cpr signatures ====================
-T5075.$trModule: m1
+T5075.$trModule:
 T5075.loop:
 
 


=====================================
testsuite/tests/stranal/sigs/T8569.stderr
=====================================
@@ -9,10 +9,10 @@ T8569.addUp: <S,1*U><L,U>
 
 
 ==================== Cpr signatures ====================
-T8569.$tc'Rdata: m1
-T8569.$tc'Rint: m1
-T8569.$tcRep: m1
-T8569.$trModule: m1
+T8569.$tc'Rdata:
+T8569.$tc'Rint:
+T8569.$tcRep:
+T8569.$trModule:
 T8569.addUp:
 
 


=====================================
testsuite/tests/stranal/sigs/T8598.stderr
=====================================
@@ -6,7 +6,7 @@ T8598.fun: <S,1*U(U)>
 
 
 ==================== Cpr signatures ====================
-T8598.$trModule: m1
+T8598.$trModule:
 T8598.fun: m1
 
 


=====================================
testsuite/tests/stranal/sigs/UnsatFun.stderr
=====================================
@@ -12,7 +12,7 @@ UnsatFun.h3: <C(S),1*C1(U)>
 
 
 ==================== Cpr signatures ====================
-UnsatFun.$trModule: m1
+UnsatFun.$trModule:
 UnsatFun.f: b
 UnsatFun.g:
 UnsatFun.g':



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8bea8699437788e4616ff2a5bf2d605e101ed755

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/8bea8699437788e4616ff2a5bf2d605e101ed755
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200506/10b939e7/attachment-0001.html>


More information about the ghc-commits mailing list