summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoachim Breitner <mail@joachim-breitner.de>2017-09-10 16:10:37 +0100
committerJoachim Breitner <mail@joachim-breitner.de>2017-09-12 11:01:10 -0400
commitfe04f3783b662c52c4a0ff36b2d62a7a575998a5 (patch)
tree3a49d515bc700562621bb0d97a74a89bd0d174fb
parentfe35b85a8cc72582e0f98a3059be00a9a2318a4a (diff)
downloadhaskell-fe04f3783b662c52c4a0ff36b2d62a7a575998a5.tar.gz
Allow CSE'ing of work-wrapped bindings (#14186)
the worker/wrapper creates an artificial INLINE pragma, which caused CSE to not do its work. We now recognize such artificial pragmas by using `NoUserInline` instead of `Inline` as the `InlineSpec`. Differential Revision: https://phabricator.haskell.org/D3939
-rw-r--r--compiler/basicTypes/BasicTypes.hs26
-rw-r--r--compiler/deSugar/DsBinds.hs8
-rw-r--r--compiler/deSugar/DsMeta.hs2
-rw-r--r--compiler/hsSyn/Convert.hs2
-rw-r--r--compiler/hsSyn/HsBinds.hs4
-rw-r--r--compiler/parser/Parser.y2
-rw-r--r--compiler/simplCore/CSE.hs10
-rw-r--r--compiler/specialise/Specialise.hs2
-rw-r--r--compiler/stranal/WorkWrap.hs6
-rw-r--r--compiler/typecheck/TcSigs.hs2
-rw-r--r--compiler/utils/Binary.hs4
-rw-r--r--testsuite/tests/roles/should_compile/Roles1.stderr45
-rw-r--r--testsuite/tests/roles/should_compile/Roles14.stderr15
-rw-r--r--testsuite/tests/roles/should_compile/Roles2.stderr16
-rw-r--r--testsuite/tests/roles/should_compile/Roles3.stderr30
-rw-r--r--testsuite/tests/roles/should_compile/Roles4.stderr23
-rw-r--r--testsuite/tests/roles/should_compile/T8958.stderr27
-rw-r--r--testsuite/tests/simplCore/should_compile/T13143.stderr6
-rw-r--r--testsuite/tests/simplCore/should_compile/T14186.stderr122
-rw-r--r--testsuite/tests/simplCore/should_compile/T3717.stderr30
-rw-r--r--testsuite/tests/simplCore/should_compile/T3772.stdout2
-rw-r--r--testsuite/tests/simplCore/should_compile/T4908.stderr61
-rw-r--r--testsuite/tests/simplCore/should_compile/T4930.stderr4
-rw-r--r--testsuite/tests/simplCore/should_compile/T7360.stderr4
-rw-r--r--testsuite/tests/simplCore/should_compile/T7865.stdout2
-rw-r--r--testsuite/tests/simplCore/should_compile/all.T2
-rw-r--r--testsuite/tests/simplCore/should_compile/spec-inline.stderr6
-rw-r--r--testsuite/tests/stranal/should_compile/T10482.stderr264
-rw-r--r--testsuite/tests/stranal/should_compile/T10482a.stderr490
-rw-r--r--testsuite/tests/th/TH_Roles2.stderr8
30 files changed, 1024 insertions, 201 deletions
diff --git a/compiler/basicTypes/BasicTypes.hs b/compiler/basicTypes/BasicTypes.hs
index c6ffaad0d4..3e556a165b 100644
--- a/compiler/basicTypes/BasicTypes.hs
+++ b/compiler/basicTypes/BasicTypes.hs
@@ -85,7 +85,7 @@ module BasicTypes(
isNeverActive, isAlwaysActive, isEarlyActive,
RuleMatchInfo(..), isConLike, isFunLike,
- InlineSpec(..), isEmptyInlineSpec,
+ InlineSpec(..), noUserInlineSpec,
InlinePragma(..), defaultInlinePragma, alwaysInlinePragma,
neverInlinePragma, dfunInlinePragma,
isDefaultInlinePragma,
@@ -1221,8 +1221,8 @@ data InlineSpec -- What the user's INLINE pragma looked like
= Inline
| Inlinable
| NoInline
- | EmptyInlineSpec -- Used in a place-holder InlinePragma in SpecPrag or IdInfo,
- -- where there isn't any real inline pragma at all
+ | NoUserInline -- Used when the pragma did not come from the user,
+ -- e.g. in `defaultInlinePragma` or when created by CSE
deriving( Eq, Data, Show )
-- Show needed for Lexer.x
@@ -1232,7 +1232,7 @@ This data type mirrors what you can write in an INLINE or NOINLINE pragma in
the source program.
If you write nothing at all, you get defaultInlinePragma:
- inl_inline = EmptyInlineSpec
+ inl_inline = NoUserInline
inl_act = AlwaysActive
inl_rule = FunLike
@@ -1305,16 +1305,16 @@ isFunLike :: RuleMatchInfo -> Bool
isFunLike FunLike = True
isFunLike _ = False
-isEmptyInlineSpec :: InlineSpec -> Bool
-isEmptyInlineSpec EmptyInlineSpec = True
-isEmptyInlineSpec _ = False
+noUserInlineSpec :: InlineSpec -> Bool
+noUserInlineSpec NoUserInline = True
+noUserInlineSpec _ = False
defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma
:: InlinePragma
defaultInlinePragma = InlinePragma { inl_src = SourceText "{-# INLINE"
, inl_act = AlwaysActive
, inl_rule = FunLike
- , inl_inline = EmptyInlineSpec
+ , inl_inline = NoUserInline
, inl_sat = Nothing }
alwaysInlinePragma = defaultInlinePragma { inl_inline = Inline }
@@ -1334,7 +1334,7 @@ isDefaultInlinePragma :: InlinePragma -> Bool
isDefaultInlinePragma (InlinePragma { inl_act = activation
, inl_rule = match_info
, inl_inline = inline })
- = isEmptyInlineSpec inline && isAlwaysActive activation && isFunLike match_info
+ = noUserInlineSpec inline && isAlwaysActive activation && isFunLike match_info
isInlinePragma :: InlinePragma -> Bool
isInlinePragma prag = case inl_inline prag of
@@ -1379,10 +1379,10 @@ instance Outputable RuleMatchInfo where
ppr FunLike = text "FUNLIKE"
instance Outputable InlineSpec where
- ppr Inline = text "INLINE"
- ppr NoInline = text "NOINLINE"
- ppr Inlinable = text "INLINABLE"
- ppr EmptyInlineSpec = empty
+ ppr Inline = text "INLINE"
+ ppr NoInline = text "NOINLINE"
+ ppr Inlinable = text "INLINABLE"
+ ppr NoUserInline = text "NOUSERINLINE" -- what is better?
instance Outputable InlinePragma where
ppr = pprInline
diff --git a/compiler/deSugar/DsBinds.hs b/compiler/deSugar/DsBinds.hs
index 2b39eeb7a2..d704f7ba08 100644
--- a/compiler/deSugar/DsBinds.hs
+++ b/compiler/deSugar/DsBinds.hs
@@ -362,10 +362,10 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs
| otherwise
= case inlinePragmaSpec inline_prag of
- EmptyInlineSpec -> (gbl_id, rhs)
- NoInline -> (gbl_id, rhs)
- Inlinable -> (gbl_id `setIdUnfolding` inlinable_unf, rhs)
- Inline -> inline_pair
+ NoUserInline -> (gbl_id, rhs)
+ NoInline -> (gbl_id, rhs)
+ Inlinable -> (gbl_id `setIdUnfolding` inlinable_unf, rhs)
+ Inline -> inline_pair
where
inline_prag = idInlinePragma gbl_id
diff --git a/compiler/deSugar/DsMeta.hs b/compiler/deSugar/DsMeta.hs
index 5e630e56ac..bcdee68edf 100644
--- a/compiler/deSugar/DsMeta.hs
+++ b/compiler/deSugar/DsMeta.hs
@@ -805,7 +805,7 @@ rep_specialise nm ty ispec loc
; ty1 <- repHsSigType ty
; phases <- repPhases $ inl_act ispec
; let inline = inl_inline ispec
- ; pragma <- if isEmptyInlineSpec inline
+ ; pragma <- if noUserInlineSpec inline
then -- SPECIALISE
repPragSpec nm1 ty1 phases
else -- SPECIALISE INLINE
diff --git a/compiler/hsSyn/Convert.hs b/compiler/hsSyn/Convert.hs
index a9df2b2554..727a04adca 100644
--- a/compiler/hsSyn/Convert.hs
+++ b/compiler/hsSyn/Convert.hs
@@ -660,7 +660,7 @@ cvtPragmaD (SpecialiseP nm ty inline phases)
; let (inline', dflt,srcText) = case inline of
Just inline1 -> (cvtInline inline1, dfltActivation inline1,
src inline1)
- Nothing -> (EmptyInlineSpec, AlwaysActive,
+ Nothing -> (NoUserInline, AlwaysActive,
"{-# SPECIALISE")
; let ip = InlinePragma { inl_src = SourceText srcText
, inl_inline = inline'
diff --git a/compiler/hsSyn/HsBinds.hs b/compiler/hsSyn/HsBinds.hs
index 85c002b481..089e2440f6 100644
--- a/compiler/hsSyn/HsBinds.hs
+++ b/compiler/hsSyn/HsBinds.hs
@@ -1069,8 +1069,8 @@ ppr_sig (SpecSig var ty inl@(InlinePragma { inl_inline = spec }))
(interpp'SP ty) inl)
where
pragmaSrc = case spec of
- EmptyInlineSpec -> "{-# SPECIALISE"
- _ -> "{-# SPECIALISE_INLINE"
+ NoUserInline -> "{-# SPECIALISE"
+ _ -> "{-# SPECIALISE_INLINE"
ppr_sig (InlineSig var inl)
= pragSrcBrackets (inl_src inl) "{-# INLINE" (pprInline inl
<+> pprPrefixOcc (unLoc var))
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index e3deb31bd5..a4507fc233 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -2311,7 +2311,7 @@ sigdecl :: { LHsDecl GhcPs }
| '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}'
{% ams (
let inl_prag = mkInlinePragma (getSPEC_PRAGs $1)
- (EmptyInlineSpec, FunLike) (snd $2)
+ (NoUserInline, FunLike) (snd $2)
in sLL $1 $> $ SigD (SpecSig $3 (fromOL $5) inl_prag))
(mo $1:mu AnnDcolon $4:mc $6:(fst $2)) }
diff --git a/compiler/simplCore/CSE.hs b/compiler/simplCore/CSE.hs
index ffbcdb4877..53d7836d68 100644
--- a/compiler/simplCore/CSE.hs
+++ b/compiler/simplCore/CSE.hs
@@ -24,7 +24,8 @@ import Type ( tyConAppArgs )
import CoreSyn
import Outputable
import BasicTypes ( TopLevelFlag(..), isTopLevel
- , isAlwaysActive, isAnyInlinePragma )
+ , isAlwaysActive, isAnyInlinePragma,
+ inlinePragmaSpec, noUserInlineSpec )
import TrieMap
import Util ( filterOut )
import Data.List ( mapAccumL )
@@ -205,6 +206,10 @@ is small). The conclusion here is this:
might replace <rhs> by 'bar', and then later be unable to see that it
really was <rhs>.
+An except to the rule is when the INLINE pragma is not from the user, e.g. from
+WorkWrap (see Note [Wrapper activation]). We can tell because noUserInlineSpec
+is then true.
+
Note that we do not (currently) do CSE on the unfolding stored inside
an Id, even if is a 'stable' unfolding. That means that when an
unfolding happens, it is always faithful to what the stable unfolding
@@ -386,7 +391,8 @@ addBinding env in_id out_id rhs'
_ -> False
noCSE :: InId -> Bool
-noCSE id = not (isAlwaysActive (idInlineActivation id))
+noCSE id = not (isAlwaysActive (idInlineActivation id)) &&
+ not (noUserInlineSpec (inlinePragmaSpec (idInlinePragma id)))
-- See Note [CSE for INLINE and NOINLINE]
|| isAnyInlinePragma (idInlinePragma id)
-- See Note [CSE for stable unfoldings]
diff --git a/compiler/specialise/Specialise.hs b/compiler/specialise/Specialise.hs
index dfbb16a9cb..83f1ed78bb 100644
--- a/compiler/specialise/Specialise.hs
+++ b/compiler/specialise/Specialise.hs
@@ -1341,7 +1341,7 @@ specCalls mb_mod env existing_rules calls_for_me fn rhs
-- See Note [Specialising imported functions] in OccurAnal
| InlinePragma { inl_inline = Inlinable } <- inl_prag
- = (inl_prag { inl_inline = EmptyInlineSpec }, noUnfolding)
+ = (inl_prag { inl_inline = NoUserInline }, noUnfolding)
| otherwise
= (inl_prag, specUnfolding poly_tyvars spec_app
diff --git a/compiler/stranal/WorkWrap.hs b/compiler/stranal/WorkWrap.hs
index 9d741f5f4c..630ec11442 100644
--- a/compiler/stranal/WorkWrap.hs
+++ b/compiler/stranal/WorkWrap.hs
@@ -374,6 +374,10 @@ it appears in the first place in the defining module.
At one stage I tried making the wrapper inlining always-active, and
that had a very bad effect on nofib/imaginary/x2n1; a wrapper was
inlined before the specialisation fired.
+
+The use an inl_inline of NoUserInline to distinguish this pragma from one
+that was given by the user. In particular, CSE will not happen if there is a
+user-specified pragma, but should happen for w/w’ed things (#14186).
-}
tryWW :: DynFlags
@@ -521,7 +525,7 @@ splitFun dflags fam_envs fn_id fn_info wrap_dmds res_info rhs
wrap_act = ActiveAfter NoSourceText 0
wrap_rhs = wrap_fn work_id
wrap_prag = InlinePragma { inl_src = SourceText "{-# INLINE"
- , inl_inline = Inline
+ , inl_inline = NoUserInline
, inl_sat = Nothing
, inl_act = wrap_act
, inl_rule = rule_match_info }
diff --git a/compiler/typecheck/TcSigs.hs b/compiler/typecheck/TcSigs.hs
index 3ff93b6bfa..f3331ac237 100644
--- a/compiler/typecheck/TcSigs.hs
+++ b/compiler/typecheck/TcSigs.hs
@@ -540,7 +540,7 @@ addInlinePrags poly_id prags_for_me
warn_multiple_inlines inl1@(L loc prag1) (inl2@(L _ prag2) : inls)
| inlinePragmaActivation prag1 == inlinePragmaActivation prag2
- , isEmptyInlineSpec (inlinePragmaSpec prag1)
+ , noUserInlineSpec (inlinePragmaSpec prag1)
= -- Tiresome: inl1 is put there by virtue of being in a hs-boot loop
-- and inl2 is a user NOINLINE pragma; we don't want to complain
warn_multiple_inlines inl2 inls
diff --git a/compiler/utils/Binary.hs b/compiler/utils/Binary.hs
index 2859033814..9254e97985 100644
--- a/compiler/utils/Binary.hs
+++ b/compiler/utils/Binary.hs
@@ -1031,14 +1031,14 @@ instance Binary RuleMatchInfo where
else return FunLike
instance Binary InlineSpec where
- put_ bh EmptyInlineSpec = putByte bh 0
+ put_ bh NoUserInline = putByte bh 0
put_ bh Inline = putByte bh 1
put_ bh Inlinable = putByte bh 2
put_ bh NoInline = putByte bh 3
get bh = do h <- getByte bh
case h of
- 0 -> return EmptyInlineSpec
+ 0 -> return NoUserInline
1 -> return Inline
2 -> return Inlinable
_ -> return NoInline
diff --git a/testsuite/tests/roles/should_compile/Roles1.stderr b/testsuite/tests/roles/should_compile/Roles1.stderr
index dd2f16d463..4b9b553b68 100644
--- a/testsuite/tests/roles/should_compile/Roles1.stderr
+++ b/testsuite/tests/roles/should_compile/Roles1.stderr
@@ -22,7 +22,7 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
Roles1.$tcT7
@@ -137,36 +137,37 @@ Roles1.$tc'K1
(GHC.Types.TrNameS "'K1"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 2
-$krep [InlPrag=[~]] = GHC.Types.KindRepApp $krep $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 1
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 1
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 2
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepApp $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepFun $krep GHC.Types.krep$*Arr*
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep GHC.Types.krep$*
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun $krep GHC.Types.krep$*
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepFun GHC.Types.krep$*Arr* GHC.Types.krep$*Arr*
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
Roles1.$tcT7 ((:) $krep ((:) $krep ((:) $krep [])))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT6 ((:) $krep ((:) $krep []))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT4 ((:) $krep ((:) $krep []))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT3 ((:) $krep ((:) $krep []))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT5 ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT2 ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles1.$tcT1 ((:) $krep [])
Roles1.$trModule
= GHC.Types.Module
diff --git a/testsuite/tests/roles/should_compile/Roles14.stderr b/testsuite/tests/roles/should_compile/Roles14.stderr
index 432d936d9e..de25f649ea 100644
--- a/testsuite/tests/roles/should_compile/Roles14.stderr
+++ b/testsuite/tests/roles/should_compile/Roles14.stderr
@@ -9,7 +9,7 @@ COERCION AXIOMS
axiom Roles12.N:C2 :: C2 a = a -> a -- Defined at Roles14.hs:6:1
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
Roles12.$tcC2
@@ -28,13 +28,14 @@ Roles12.$tc'C:C2
(GHC.Types.TrNameS "'C:C2"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun GHC.Types.krep$* $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint []
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles12.$tcC2 ((:) $krep [])
Roles12.$trModule
= GHC.Types.Module
diff --git a/testsuite/tests/roles/should_compile/Roles2.stderr b/testsuite/tests/roles/should_compile/Roles2.stderr
index 6f77024162..591691f365 100644
--- a/testsuite/tests/roles/should_compile/Roles2.stderr
+++ b/testsuite/tests/roles/should_compile/Roles2.stderr
@@ -8,7 +8,7 @@ TYPE CONSTRUCTORS
COERCION AXIOMS
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
Roles2.$tcT2
@@ -43,16 +43,16 @@ Roles2.$tc'K1
(GHC.Types.TrNameS "'K1"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Ptr.$tcFunPtr ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles2.$tcT2 ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Types.$tcIO ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles2.$tcT1 ((:) $krep [])
Roles2.$trModule
= GHC.Types.Module
diff --git a/testsuite/tests/roles/should_compile/Roles3.stderr b/testsuite/tests/roles/should_compile/Roles3.stderr
index 4a9299772d..67146c7662 100644
--- a/testsuite/tests/roles/should_compile/Roles3.stderr
+++ b/testsuite/tests/roles/should_compile/Roles3.stderr
@@ -30,7 +30,7 @@ COERCION AXIOMS
C4 a b = a -> F4 b -> F4 b -- Defined at Roles3.hs:18:1
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
Roles3.$tcC4
@@ -81,24 +81,26 @@ Roles3.$tc'C:C1
(GHC.Types.TrNameS "'C:C1"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 1
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun GHC.Types.krep$* $krep
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun GHC.Types.krep$* $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint []
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
Data.Type.Equality.$tc~
((:) GHC.Types.krep$* ((:) $krep ((:) $krep [])))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles3.$tcC2 ((:) $krep ((:) $krep []))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles3.$tcC1 ((:) $krep [])
Roles3.$trModule
= GHC.Types.Module
diff --git a/testsuite/tests/roles/should_compile/Roles4.stderr b/testsuite/tests/roles/should_compile/Roles4.stderr
index 7a61af6f5a..4f7598c7fd 100644
--- a/testsuite/tests/roles/should_compile/Roles4.stderr
+++ b/testsuite/tests/roles/should_compile/Roles4.stderr
@@ -15,7 +15,7 @@ COERCION AXIOMS
C3 a = a -> Syn1 a -- Defined at Roles4.hs:11:1
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
Roles4.$tcC3
@@ -50,19 +50,20 @@ Roles4.$tc'C:C1
(GHC.Types.TrNameS "'C:C1"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun GHC.Types.krep$* $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Types.$tc[] ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint []
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles4.$tcC3 ((:) $krep [])
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp Roles4.$tcC1 ((:) $krep [])
Roles4.$trModule
= GHC.Types.Module
diff --git a/testsuite/tests/roles/should_compile/T8958.stderr b/testsuite/tests/roles/should_compile/T8958.stderr
index 117cea60b4..2e83e30199 100644
--- a/testsuite/tests/roles/should_compile/T8958.stderr
+++ b/testsuite/tests/roles/should_compile/T8958.stderr
@@ -17,7 +17,7 @@ INSTANCES
instance [incoherent] Nominal a -- Defined at T8958.hs:7:10
Dependent modules: []
Dependent packages: [base-4.10.0.0, ghc-prim-0.5.1.0,
- integer-gmp-1.0.0.1]
+ integer-gmp-1.0.1.0]
==================== Typechecker ====================
T8958.$tcMap
@@ -68,32 +68,33 @@ T8958.$tc'C:Nominal
(GHC.Types.TrNameS "'C:Nominal"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 1
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepFun GHC.Types.krep$* $krep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 1
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepFun $krep $krep
+$krep [InlPrag=NOUSERINLINE[~]]
+ = GHC.Types.KindRepFun GHC.Types.krep$* $krep
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
GHC.Tuple.$tc(,)
((:) @ GHC.Types.KindRep
$krep ((:) @ GHC.Types.KindRep $krep [] @ GHC.Types.KindRep))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
T8958.$tcMap
((:) @ GHC.Types.KindRep
$krep ((:) @ GHC.Types.KindRep $krep [] @ GHC.Types.KindRep))
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
GHC.Types.$tc[]
((:) @ GHC.Types.KindRep $krep [] @ GHC.Types.KindRep)
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
GHC.Types.$tcConstraint [] @ GHC.Types.KindRep
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
T8958.$tcRepresentational
((:) @ GHC.Types.KindRep $krep [] @ GHC.Types.KindRep)
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepTyConApp
T8958.$tcNominal
((:) @ GHC.Types.KindRep $krep [] @ GHC.Types.KindRep)
@@ -103,7 +104,7 @@ T8958.$trModule
AbsBinds [a] []
{Exports: [T8958.$fRepresentationala <= $dRepresentational
wrap: <>]
- Exported types: T8958.$fRepresentationala [InlPrag=CONLIKE]
+ Exported types: T8958.$fRepresentationala [InlPrag=NOUSERINLINE CONLIKE]
:: forall a. Representational a
[LclIdX[DFunId],
Unf=DFun: \ (@ a) -> T8958.C:Representational TYPE: a]
@@ -112,7 +113,7 @@ AbsBinds [a] []
AbsBinds [a] []
{Exports: [T8958.$fNominala <= $dNominal
wrap: <>]
- Exported types: T8958.$fNominala [InlPrag=CONLIKE]
+ Exported types: T8958.$fNominala [InlPrag=NOUSERINLINE CONLIKE]
:: forall a. Nominal a
[LclIdX[DFunId], Unf=DFun: \ (@ a) -> T8958.C:Nominal TYPE: a]
Binds: $dNominal = T8958.C:Nominal @ a
diff --git a/testsuite/tests/simplCore/should_compile/T13143.stderr b/testsuite/tests/simplCore/should_compile/T13143.stderr
index c9cdd95bc2..9ac62ad090 100644
--- a/testsuite/tests/simplCore/should_compile/T13143.stderr
+++ b/testsuite/tests/simplCore/should_compile/T13143.stderr
@@ -12,7 +12,7 @@ T13143.$wf = \ (@ a) _ [Occ=Dead] -> T13143.$wf @ a GHC.Prim.void#
end Rec }
-- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0}
-f [InlPrag=INLINE[0]] :: forall a. Int -> a
+f [InlPrag=NOUSERINLINE[0]] :: forall a. Int -> a
[GblId,
Arity=1,
Caf=NoCafRefs,
@@ -74,7 +74,7 @@ lvl = T13143.$wf @ Int GHC.Prim.void#
Rec {
-- RHS size: {terms: 28, types: 7, coercions: 0, joins: 0/0}
-T13143.$wg [InlPrag=[0], Occ=LoopBreaker]
+T13143.$wg [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker]
:: Bool -> Bool -> GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=3, Str=<S,1*U><S,1*U><S,U>]
T13143.$wg
@@ -94,7 +94,7 @@ T13143.$wg
end Rec }
-- RHS size: {terms: 14, types: 6, coercions: 0, joins: 0/0}
-g [InlPrag=INLINE[0]] :: Bool -> Bool -> Int -> Int
+g [InlPrag=NOUSERINLINE[0]] :: Bool -> Bool -> Int -> Int
[GblId,
Arity=3,
Str=<S,1*U><S,1*U><S(S),1*U(U)>m,
diff --git a/testsuite/tests/simplCore/should_compile/T14186.stderr b/testsuite/tests/simplCore/should_compile/T14186.stderr
index ccc9bd9791..17ccc2c07d 100644
--- a/testsuite/tests/simplCore/should_compile/T14186.stderr
+++ b/testsuite/tests/simplCore/should_compile/T14186.stderr
@@ -1,57 +1,119 @@
==================== Tidy Core ====================
Result size of Tidy Core
- = {terms: 52, types: 99, coercions: 0, joins: 0/0}
+ = {terms: 36, types: 68, coercions: 0, joins: 0/0}
--- RHS size: {terms: 18, types: 29, coercions: 0, joins: 0/0}
-foo
+-- RHS size: {terms: 19, types: 27, coercions: 0, joins: 0/0}
+foo [InlPrag=[0]]
:: forall t1 b t2.
(t1 -> b) -> (t2 -> t1) -> (t2, [t2]) -> (b, [b])
-[GblId, Arity=3]
+[GblId,
+ Arity=3,
+ Caf=NoCafRefs,
+ Str=<L,C(U)><L,C(U)><S,1*U(U,1*U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (@ t_sZi)
+ (@ b_sZj)
+ (@ t1_sZk)
+ (w_sZl :: t_sZi -> b_sZj)
+ (w1_sZm :: t1_sZk -> t_sZi)
+ (w2_sZn [Occ=Once!] :: (t1_sZk, [t1_sZk])) ->
+ case w2_sZn of { (ww1_sZq [Occ=Once], ww2_sZr [Occ=Once]) ->
+ (w_sZl (w1_sZm ww1_sZq),
+ map
+ @ t1_sZk
+ @ b_sZj
+ (\ (x_aXa [Occ=Once] :: t1_sZk) -> w_sZl (w1_sZm x_aXa))
+ ww2_sZr)
+ }}]
foo
- = \ (@ t_aUk)
- (@ b_aUs)
- (@ t1_aUo)
- (f_apH :: t_aUk -> b_aUs)
- (g_apI :: t1_aUo -> t_aUk)
- (ds_dVH :: (t1_aUo, [t1_aUo])) ->
- case ds_dVH of { (x_apJ, xs_apK) ->
- (f_apH (g_apI x_apJ),
+ = \ (@ t_sZi)
+ (@ b_sZj)
+ (@ t1_sZk)
+ (w_sZl :: t_sZi -> b_sZj)
+ (w1_sZm :: t1_sZk -> t_sZi)
+ (w2_sZn :: (t1_sZk, [t1_sZk])) ->
+ case w2_sZn of { (ww1_sZq, ww2_sZr) ->
+ (w_sZl (w1_sZm ww1_sZq),
map
- @ t1_aUo @ b_aUs (. @ t_aUk @ b_aUs @ t1_aUo f_apH g_apI) xs_apK)
+ @ t1_sZk
+ @ b_sZj
+ (\ (x_aXa :: t1_sZk) -> w_sZl (w1_sZm x_aXa))
+ ww2_sZr)
}
--- RHS size: {terms: 18, types: 29, coercions: 0, joins: 0/0}
-bar
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+bar [InlPrag=[0]]
:: forall t1 b t2.
(t1 -> b) -> (t2 -> t1) -> (t2, [t2]) -> (b, [b])
-[GblId, Arity=3]
+[GblId,
+ Arity=3,
+ Caf=NoCafRefs,
+ Str=<L,C(U)><L,C(U)><S,1*U(U,1*U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=3,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (@ t_sZx)
+ (@ b_sZy)
+ (@ t1_sZz)
+ (w_sZA :: t_sZx -> b_sZy)
+ (w1_sZB :: t1_sZz -> t_sZx)
+ (w2_sZC [Occ=Once!] :: (t1_sZz, [t1_sZz])) ->
+ case w2_sZC of { (ww1_sZF [Occ=Once], ww2_sZG [Occ=Once]) ->
+ (w_sZA (w1_sZB ww1_sZF),
+ map
+ @ t1_sZz
+ @ b_sZy
+ (\ (x_aXa [Occ=Once] :: t1_sZz) -> w_sZA (w1_sZB x_aXa))
+ ww2_sZG)
+ }}]
bar = foo
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
-$trModule1_rVy :: GHC.Prim.Addr#
-[GblId, Caf=NoCafRefs]
-$trModule1_rVy = "main"#
+T14186.$trModule4 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T14186.$trModule4 = "main"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
-$trModule2_rVX :: GHC.Types.TrName
-[GblId, Caf=NoCafRefs]
-$trModule2_rVX = GHC.Types.TrNameS $trModule1_rVy
+T14186.$trModule3 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T14186.$trModule3 = GHC.Types.TrNameS T14186.$trModule4
-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
-$trModule3_rVY :: GHC.Prim.Addr#
-[GblId, Caf=NoCafRefs]
-$trModule3_rVY = "T14186"#
+T14186.$trModule2 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+T14186.$trModule2 = "T14186"#
-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
-$trModule4_rVZ :: GHC.Types.TrName
-[GblId, Caf=NoCafRefs]
-$trModule4_rVZ = GHC.Types.TrNameS $trModule3_rVY
+T14186.$trModule1 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T14186.$trModule1 = GHC.Types.TrNameS T14186.$trModule2
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
T14186.$trModule :: GHC.Types.Module
-[GblId, Caf=NoCafRefs]
-T14186.$trModule = GHC.Types.Module $trModule2_rVX $trModule4_rVZ
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
+ WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+T14186.$trModule
+ = GHC.Types.Module T14186.$trModule3 T14186.$trModule1
diff --git a/testsuite/tests/simplCore/should_compile/T3717.stderr b/testsuite/tests/simplCore/should_compile/T3717.stderr
index 9bcc4f31ac..35b4fa8dbd 100644
--- a/testsuite/tests/simplCore/should_compile/T3717.stderr
+++ b/testsuite/tests/simplCore/should_compile/T3717.stderr
@@ -44,24 +44,24 @@ T3717.$trModule :: GHC.Types.Module
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
-T3717.$trModule =
- GHC.Types.Module T3717.$trModule3 T3717.$trModule1
+T3717.$trModule
+ = GHC.Types.Module T3717.$trModule3 T3717.$trModule1
Rec {
-- RHS size: {terms: 10, types: 2, coercions: 0, joins: 0/0}
-T3717.$wfoo [InlPrag=[0], Occ=LoopBreaker]
+T3717.$wfoo [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker]
:: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=1, Caf=NoCafRefs, Str=<S,1*U>]
-T3717.$wfoo =
- \ (ww :: GHC.Prim.Int#) ->
- case ww of ds {
- __DEFAULT -> T3717.$wfoo (GHC.Prim.-# ds 1#);
- 0# -> 0#
- }
+T3717.$wfoo
+ = \ (ww :: GHC.Prim.Int#) ->
+ case ww of ds {
+ __DEFAULT -> T3717.$wfoo (GHC.Prim.-# ds 1#);
+ 0# -> 0#
+ }
end Rec }
-- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0}
-foo [InlPrag=INLINE[0]] :: Int -> Int
+foo [InlPrag=NOUSERINLINE[0]] :: Int -> Int
[GblId,
Arity=1,
Caf=NoCafRefs,
@@ -73,11 +73,11 @@ foo [InlPrag=INLINE[0]] :: Int -> Int
case w of { GHC.Types.I# ww1 [Occ=Once] ->
case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
}}]
-foo =
- \ (w :: Int) ->
- case w of { GHC.Types.I# ww1 ->
- case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
- }
+foo
+ = \ (w :: Int) ->
+ case w of { GHC.Types.I# ww1 ->
+ case T3717.$wfoo ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
+ }
diff --git a/testsuite/tests/simplCore/should_compile/T3772.stdout b/testsuite/tests/simplCore/should_compile/T3772.stdout
index a4ab97da38..409db79c93 100644
--- a/testsuite/tests/simplCore/should_compile/T3772.stdout
+++ b/testsuite/tests/simplCore/should_compile/T3772.stdout
@@ -70,7 +70,7 @@ T3772.$wfoo
}
-- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0}
-foo [InlPrag=INLINE[0]] :: Int -> ()
+foo [InlPrag=NOUSERINLINE[0]] :: Int -> ()
[GblId,
Arity=1,
Caf=NoCafRefs,
diff --git a/testsuite/tests/simplCore/should_compile/T4908.stderr b/testsuite/tests/simplCore/should_compile/T4908.stderr
index 185b9b3529..2f805f074a 100644
--- a/testsuite/tests/simplCore/should_compile/T4908.stderr
+++ b/testsuite/tests/simplCore/should_compile/T4908.stderr
@@ -44,50 +44,50 @@ T4908.$trModule :: Module
Str=m,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
-T4908.$trModule =
- GHC.Types.Module T4908.$trModule3 T4908.$trModule1
+T4908.$trModule
+ = GHC.Types.Module T4908.$trModule3 T4908.$trModule1
Rec {
-- RHS size: {terms: 19, types: 5, coercions: 0, joins: 0/0}
T4908.f_$s$wf [Occ=LoopBreaker] :: Int -> Int# -> Int# -> Bool
[GblId, Arity=3, Caf=NoCafRefs, Str=<L,A><L,1*U><S,1*U>]
-T4908.f_$s$wf =
- \ (sc :: Int) (sc1 :: Int#) (sc2 :: Int#) ->
- case sc2 of ds {
- __DEFAULT ->
- case sc1 of ds1 {
- __DEFAULT -> T4908.f_$s$wf sc ds1 (-# ds 1#);
- 0# -> GHC.Types.True
- };
- 0# -> GHC.Types.True
- }
+T4908.f_$s$wf
+ = \ (sc :: Int) (sc1 :: Int#) (sc2 :: Int#) ->
+ case sc2 of ds {
+ __DEFAULT ->
+ case sc1 of ds1 {
+ __DEFAULT -> T4908.f_$s$wf sc ds1 (-# ds 1#);
+ 0# -> GHC.Types.True
+ };
+ 0# -> GHC.Types.True
+ }
end Rec }
-- RHS size: {terms: 24, types: 13, coercions: 0, joins: 0/0}
-T4908.$wf [InlPrag=[0]] :: Int# -> (Int, Int) -> Bool
+T4908.$wf [InlPrag=NOUSERINLINE[0]] :: Int# -> (Int, Int) -> Bool
[GblId,
Arity=2,
Caf=NoCafRefs,
Str=<S,1*U><L,1*U(A,1*U(1*U))>,
Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 20] 101 20}]
-T4908.$wf =
- \ (ww :: Int#) (w :: (Int, Int)) ->
- case ww of ds {
- __DEFAULT ->
- case w of { (a, b) ->
- case b of { I# ds1 ->
- case ds1 of ds2 {
- __DEFAULT -> T4908.f_$s$wf a ds2 (-# ds 1#);
- 0# -> GHC.Types.True
- }
- }
- };
- 0# -> GHC.Types.True
- }
+T4908.$wf
+ = \ (ww :: Int#) (w :: (Int, Int)) ->
+ case ww of ds {
+ __DEFAULT ->
+ case w of { (a, b) ->
+ case b of { I# ds1 ->
+ case ds1 of ds2 {
+ __DEFAULT -> T4908.f_$s$wf a ds2 (-# ds 1#);
+ 0# -> GHC.Types.True
+ }
+ }
+ };
+ 0# -> GHC.Types.True
+ }
-- RHS size: {terms: 8, types: 6, coercions: 0, joins: 0/0}
-f [InlPrag=INLINE[0]] :: Int -> (Int, Int) -> Bool
+f [InlPrag=NOUSERINLINE[0]] :: Int -> (Int, Int) -> Bool
[GblId,
Arity=2,
Caf=NoCafRefs,
@@ -97,9 +97,8 @@ f [InlPrag=INLINE[0]] :: Int -> (Int, Int) -> Bool
Guidance=ALWAYS_IF(arity=2,unsat_ok=True,boring_ok=False)
Tmpl= \ (w [Occ=Once!] :: Int) (w1 [Occ=Once] :: (Int, Int)) ->
case w of { I# ww1 [Occ=Once] -> T4908.$wf ww1 w1 }}]
-f =
- \ (w :: Int) (w1 :: (Int, Int)) ->
- case w of { I# ww1 -> T4908.$wf ww1 w1 }
+f = \ (w :: Int) (w1 :: (Int, Int)) ->
+ case w of { I# ww1 -> T4908.$wf ww1 w1 }
------ Local rules for imported ids --------
diff --git a/testsuite/tests/simplCore/should_compile/T4930.stderr b/testsuite/tests/simplCore/should_compile/T4930.stderr
index 4d569485b3..2e5416303a 100644
--- a/testsuite/tests/simplCore/should_compile/T4930.stderr
+++ b/testsuite/tests/simplCore/should_compile/T4930.stderr
@@ -49,7 +49,7 @@ T4930.$trModule
Rec {
-- RHS size: {terms: 17, types: 3, coercions: 0, joins: 0/0}
-T4930.$wfoo [InlPrag=[0], Occ=LoopBreaker]
+T4930.$wfoo [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker]
:: GHC.Prim.Int# -> GHC.Prim.Int#
[GblId, Arity=1, Caf=NoCafRefs, Str=<S,U>]
T4930.$wfoo
@@ -61,7 +61,7 @@ T4930.$wfoo
end Rec }
-- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0}
-foo [InlPrag=INLINE[0]] :: Int -> Int
+foo [InlPrag=NOUSERINLINE[0]] :: Int -> Int
[GblId,
Arity=1,
Caf=NoCafRefs,
diff --git a/testsuite/tests/simplCore/should_compile/T7360.stderr b/testsuite/tests/simplCore/should_compile/T7360.stderr
index 118ebbe886..cf86246e45 100644
--- a/testsuite/tests/simplCore/should_compile/T7360.stderr
+++ b/testsuite/tests/simplCore/should_compile/T7360.stderr
@@ -160,7 +160,7 @@ T7360.$tcFoo
GHC.Types.krep$*
-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
-T7360.$tc'Foo4 [InlPrag=[~]] :: GHC.Types.KindRep
+T7360.$tc'Foo4 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m1]
T7360.$tc'Foo4
= GHC.Types.KindRepTyConApp
@@ -233,7 +233,7 @@ T7360.$tc'Foo2
T7360.$tc'Foo4
-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
-T7360.$tc'Foo9 [InlPrag=[~]] :: GHC.Types.KindRep
+T7360.$tc'Foo9 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
[GblId, Caf=NoCafRefs, Str=m4]
T7360.$tc'Foo9 = GHC.Types.KindRepFun $krep T7360.$tc'Foo4
diff --git a/testsuite/tests/simplCore/should_compile/T7865.stdout b/testsuite/tests/simplCore/should_compile/T7865.stdout
index 5cf005071d..7ea5449fbe 100644
--- a/testsuite/tests/simplCore/should_compile/T7865.stdout
+++ b/testsuite/tests/simplCore/should_compile/T7865.stdout
@@ -1,6 +1,6 @@
T7865.$wexpensive [InlPrag=NOINLINE]
T7865.$wexpensive
-expensive [InlPrag=INLINE[0]] :: Int -> Int
+expensive [InlPrag=NOUSERINLINE[0]] :: Int -> Int
case T7865.$wexpensive ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
expensive
case T7865.$wexpensive ww1 of ww2 { __DEFAULT -> GHC.Types.I# ww2 }
diff --git a/testsuite/tests/simplCore/should_compile/all.T b/testsuite/tests/simplCore/should_compile/all.T
index 3eae1ff956..a692007ff0 100644
--- a/testsuite/tests/simplCore/should_compile/all.T
+++ b/testsuite/tests/simplCore/should_compile/all.T
@@ -273,4 +273,4 @@ test('T13708', normal, compile, [''])
# thunk should inline here, so check whether or not it appears in the Core
test('T14137', [ check_errmsg(r'thunk') ], compile, ['-dsuppress-uniques -ddump-simpl'])
# bar and foo should CSEd here, so check for that in the Core
-test('T14186', [ only_ways(['optasm']), check_errmsg(r'bar = foo'), expect_broken(14186) ], compile, ['-ddump-simpl'])
+test('T14186', [ only_ways(['optasm']), check_errmsg(r'bar = foo') ], compile, ['-ddump-simpl'])
diff --git a/testsuite/tests/simplCore/should_compile/spec-inline.stderr b/testsuite/tests/simplCore/should_compile/spec-inline.stderr
index 53b315dc9c..8caba3df72 100644
--- a/testsuite/tests/simplCore/should_compile/spec-inline.stderr
+++ b/testsuite/tests/simplCore/should_compile/spec-inline.stderr
@@ -90,7 +90,8 @@ Roman.foo_$s$wgo
end Rec }
-- RHS size: {terms: 71, types: 19, coercions: 0, joins: 0/1}
-Roman.$wgo [InlPrag=[0]] :: Maybe Int -> Maybe Int -> GHC.Prim.Int#
+Roman.$wgo [InlPrag=NOUSERINLINE[0]]
+ :: Maybe Int -> Maybe Int -> GHC.Prim.Int#
[GblId,
Arity=2,
Str=<S,1*U><S,1*U>,
@@ -134,7 +135,8 @@ Roman.$wgo
}
-- RHS size: {terms: 9, types: 5, coercions: 0, joins: 0/0}
-Roman.foo_go [InlPrag=INLINE[0]] :: Maybe Int -> Maybe Int -> Int
+Roman.foo_go [InlPrag=NOUSERINLINE[0]]
+ :: Maybe Int -> Maybe Int -> Int
[GblId,
Arity=2,
Str=<S,1*U><S,1*U>m,
diff --git a/testsuite/tests/stranal/should_compile/T10482.stderr b/testsuite/tests/stranal/should_compile/T10482.stderr
index 7f8789d5f4..7900f0d5fc 100644
--- a/testsuite/tests/stranal/should_compile/T10482.stderr
+++ b/testsuite/tests/stranal/should_compile/T10482.stderr
@@ -1 +1,263 @@
-T10482.$wfoo [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 171, types: 116, coercions: 15, joins: 0/0}
+
+-- RHS size: {terms: 13, types: 14, coercions: 4, joins: 0/0}
+T10482.$WFooPair [InlPrag=INLINE[2]] :: forall a b. Foo a -> Foo b -> Foo (a, b)
+[GblId[DataConWrapper],
+ Arity=2,
+ Caf=NoCafRefs,
+ Str=<S,U><S,U>m,
+ 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= \ (@ a_aWY) (@ b_aWZ) (dt_a2p0 [Occ=Once] :: Foo a_aWY[sk:1]) (dt_a2p1 [Occ=Once] :: Foo b_aWZ[sk:1]) ->
+ (case dt_a2p0 of dt_X2p5 { __DEFAULT -> case dt_a2p1 of dt_X2p7 { __DEFAULT -> T10482.FooPair @ a_aWY @ b_aWZ dt_X2p5 dt_X2p7 } })
+ `cast` (Sym (T10482.D:R:Foo(,)0[0] <a_aWY>_N <b_aWZ>_N) :: (T10482.R:Foo(,) a_aWY b_aWZ :: *) ~R# (Foo (a_aWY, b_aWZ) :: *))}]
+T10482.$WFooPair
+ = \ (@ a_aWY) (@ b_aWZ) (dt_a2p0 [Occ=Once] :: Foo a_aWY[sk:1]) (dt_a2p1 [Occ=Once] :: Foo b_aWZ[sk:1]) ->
+ (case dt_a2p0 of dt_X2p5 { __DEFAULT -> case dt_a2p1 of dt_X2p7 { __DEFAULT -> T10482.FooPair @ a_aWY @ b_aWZ dt_X2p5 dt_X2p7 } })
+ `cast` (Sym (T10482.D:R:Foo(,)0[0] <a_aWY>_N <b_aWZ>_N) :: (T10482.R:Foo(,) a_aWY b_aWZ :: *) ~R# (Foo (a_aWY, b_aWZ) :: *))
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T10482.$trModule4 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T10482.$trModule4 = "main"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T10482.$trModule3 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T10482.$trModule3 = GHC.Types.TrNameS T10482.$trModule4
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T10482.$trModule2 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+T10482.$trModule2 = "T10482"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T10482.$trModule1 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T10482.$trModule1 = GHC.Types.TrNameS T10482.$trModule2
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T10482.$trModule :: GHC.Types.Module
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+T10482.$trModule = GHC.Types.Module T10482.$trModule3 T10482.$trModule1
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep_r2Pm :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep_r2Pm = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+$krep1_r2Pn :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep1_r2Pn = GHC.Types.KindRepVar 1#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+$krep2_r2Po :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep2_r2Po = GHC.Types.KindRepVar 0#
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep3_r2Pp :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep3_r2Pp = GHC.Types.: @ GHC.Types.KindRep $krep1_r2Pn (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep4_r2Pq :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep4_r2Pq = GHC.Types.: @ GHC.Types.KindRep $krep2_r2Po $krep3_r2Pp
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep5_r2Pr :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep5_r2Pr = GHC.Types.KindRepTyConApp GHC.Tuple.$tc(,) $krep4_r2Pq
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T10482.$tcFoo2 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T10482.$tcFoo2 = "Foo"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T10482.$tcFoo1 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T10482.$tcFoo1 = GHC.Types.TrNameS T10482.$tcFoo2
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+T10482.$tcFoo :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+T10482.$tcFoo = GHC.Types.TyCon 3311038889639791302## 7944995683507700778## T10482.$trModule T10482.$tcFoo1 0# GHC.Types.krep$*Arr*
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep6_r2Ps :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep6_r2Ps = GHC.Types.: @ GHC.Types.KindRep $krep2_r2Po (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep7_r2Pt :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep7_r2Pt = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep6_r2Ps
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep8_r2Pu :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep8_r2Pu = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep3_r2Pp
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep9_r2Pv :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep9_r2Pv = GHC.Types.: @ GHC.Types.KindRep $krep5_r2Pr (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep10_r2Pw :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep10_r2Pw = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep9_r2Pv
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep11_r2Px :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+$krep11_r2Px = GHC.Types.KindRepFun $krep8_r2Pu $krep10_r2Pw
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'FooPair1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+T10482.$tc'FooPair1 = GHC.Types.KindRepFun $krep7_r2Pt $krep11_r2Px
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep12_r2Py :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep12_r2Py = GHC.Types.: @ GHC.Types.KindRep $krep_r2Pm (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep13_r2Pz :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep13_r2Pz = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep12_r2Py
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'Foo1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+T10482.$tc'Foo1 = GHC.Types.KindRepFun $krep_r2Pm $krep13_r2Pz
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'FooPair3 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+T10482.$tc'FooPair3 = "'FooPair"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'FooPair2 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T10482.$tc'FooPair2 = GHC.Types.TrNameS T10482.$tc'FooPair3
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'FooPair :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+T10482.$tc'FooPair
+ = GHC.Types.TyCon 5329411373903054066## 1455261321638291317## T10482.$trModule T10482.$tc'FooPair2 2# T10482.$tc'FooPair1
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'Foo3 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+T10482.$tc'Foo3 = "'Foo"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'Foo2 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+T10482.$tc'Foo2 = GHC.Types.TrNameS T10482.$tc'Foo3
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+T10482.$tc'Foo :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+T10482.$tc'Foo = GHC.Types.TyCon 5096937192618987042## 15136671864408054946## T10482.$trModule T10482.$tc'Foo2 0# T10482.$tc'Foo1
+
+Rec {
+-- RHS size: {terms: 19, types: 4, coercions: 0, joins: 0/0}
+T10482.$wfoo [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=2, Caf=NoCafRefs, Str=<L,1*U><S,1*U>]
+T10482.$wfoo
+ = \ (ww_s2NS :: GHC.Prim.Int#) (ww1_s2O0 :: GHC.Prim.Int#) ->
+ case ww1_s2O0 of wild_X1r {
+ __DEFAULT ->
+ case GHC.Prim.remInt# wild_X1r 2# of {
+ __DEFAULT -> ww_s2NS;
+ 0# -> T10482.$wfoo ww_s2NS (GHC.Prim.-# wild_X1r 1#)
+ };
+ 0# -> 0#
+ }
+end Rec }
+
+-- RHS size: {terms: 21, types: 30, coercions: 11, joins: 0/0}
+foo [InlPrag=NOUSERINLINE[0]] :: Foo ((Int, Int), Int) -> Int -> Int
+[GblId,
+ Arity=2,
+ Caf=NoCafRefs,
+ Str=<S(S(S(S)L)L),1*U(U(U(1*U),A),A)><S(S),1*U(1*U)>m,
+ 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_s2NI [Occ=Once] :: Foo ((Int, Int), Int)) (w1_s2NJ [Occ=Once!] :: Int) ->
+ case w_s2NI
+ `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N <Int>_N :: (Foo ((Int, Int), Int) :: *) ~R# (T10482.R:Foo(,) (Int, Int) Int :: *))
+ of
+ { FooPair ww1_s2NM [Occ=Once] _ [Occ=Dead] ->
+ case ww1_s2NM `cast` (T10482.D:R:Foo(,)0[0] <Int>_N <Int>_N :: (Foo (Int, Int) :: *) ~R# (T10482.R:Foo(,) Int Int :: *)) of
+ { FooPair ww4_s2NP [Occ=Once] _ [Occ=Dead] ->
+ case ww4_s2NP `cast` (T10482.D:R:FooInt0[0] ; T10482.N:R:FooInt[0] :: (Foo Int :: *) ~R# (Int :: *)) of
+ { GHC.Types.I# ww7_s2NS [Occ=Once] ->
+ case w1_s2NJ of { GHC.Types.I# ww9_s2O0 [Occ=Once] ->
+ case T10482.$wfoo ww7_s2NS ww9_s2O0 of ww10_s2O4 { __DEFAULT -> GHC.Types.I# ww10_s2O4 }
+ }
+ }
+ }
+ }}]
+foo
+ = \ (w_s2NI :: Foo ((Int, Int), Int)) (w1_s2NJ :: Int) ->
+ case w_s2NI
+ `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N <Int>_N :: (Foo ((Int, Int), Int) :: *) ~R# (T10482.R:Foo(,) (Int, Int) Int :: *))
+ of
+ { FooPair ww1_s2NM ww2_s2NW ->
+ case ww1_s2NM `cast` (T10482.D:R:Foo(,)0[0] <Int>_N <Int>_N :: (Foo (Int, Int) :: *) ~R# (T10482.R:Foo(,) Int Int :: *)) of
+ { FooPair ww4_s2OE ww5_s2OF ->
+ case ww4_s2OE `cast` (T10482.D:R:FooInt0[0] ; T10482.N:R:FooInt[0] :: (Foo Int :: *) ~R# (Int :: *)) of { GHC.Types.I# ww7_s2OI ->
+ case w1_s2NJ of { GHC.Types.I# ww9_s2O0 -> case T10482.$wfoo ww7_s2OI ww9_s2O0 of ww10_s2O4 { __DEFAULT -> GHC.Types.I# ww10_s2O4 } }
+ }
+ }
+ }
+
+
+
diff --git a/testsuite/tests/stranal/should_compile/T10482a.stderr b/testsuite/tests/stranal/should_compile/T10482a.stderr
index d26b45fe1a..341fe67258 100644
--- a/testsuite/tests/stranal/should_compile/T10482a.stderr
+++ b/testsuite/tests/stranal/should_compile/T10482a.stderr
@@ -1,4 +1,486 @@
-Foo.$wf4 [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
-Foo.$wf2 [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
-Foo.$wf1 [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
-Foo.$wf3 [InlPrag=[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+
+==================== Tidy Core ====================
+Result size of Tidy Core = {terms: 353, types: 155, coercions: 3, joins: 0/0}
+
+-- RHS size: {terms: 9, types: 8, coercions: 0, joins: 0/0}
+Foo.$WMkT4 [InlPrag=INLINE[2]] :: forall a. Foo a -> Int -> T4 a
+[GblId[DataConWrapper],
+ Arity=2,
+ Caf=NoCafRefs,
+ Str=<S,U><L,U>m,
+ 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= \ (@ a_atD) (dt_a21t [Occ=Once] :: Foo a_atD[sk:1]) (dt_a21u [Occ=Once] :: Int) ->
+ case dt_a21t of dt_X21x { __DEFAULT -> Foo.MkT4 @ a_atD dt_X21x dt_a21u }}]
+Foo.$WMkT4
+ = \ (@ a_atD) (dt_a21t [Occ=Once] :: Foo a_atD[sk:1]) (dt_a21u [Occ=Once] :: Int) ->
+ case dt_a21t of dt_X21x { __DEFAULT -> Foo.MkT4 @ a_atD dt_X21x dt_a21u }
+
+-- RHS size: {terms: 8, types: 3, coercions: 0, joins: 0/0}
+Foo.$WMkT2 [InlPrag=INLINE[2]] :: Int -> Int -> T2
+[GblId[DataConWrapper],
+ Arity=2,
+ Caf=NoCafRefs,
+ Str=<S,U><L,U>m,
+ 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= \ (dt_a20k [Occ=Once] :: Int) (dt_a20l [Occ=Once] :: Int) ->
+ case dt_a20k of dt_X20n { __DEFAULT -> Foo.MkT2 dt_X20n dt_a20l }}]
+Foo.$WMkT2
+ = \ (dt_a20k [Occ=Once] :: Int) (dt_a20l [Occ=Once] :: Int) -> case dt_a20k of dt_X20n { __DEFAULT -> Foo.MkT2 dt_X20n dt_a20l }
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$trModule4 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$trModule4 = "main"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$trModule3 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$trModule3 = GHC.Types.TrNameS Foo.$trModule4
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$trModule2 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$trModule2 = "Foo"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$trModule1 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$trModule1 = GHC.Types.TrNameS Foo.$trModule2
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+Foo.$trModule :: GHC.Types.Module
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}]
+Foo.$trModule = GHC.Types.Module Foo.$trModule3 Foo.$trModule1
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep_r2nI :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep_r2nI = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+$krep1_r2nJ :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep1_r2nJ = GHC.Types.KindRepVar 0#
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT5 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$tcT5 = "T2"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT1 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tcT1 = GHC.Types.TrNameS Foo.$tcT5
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT2 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tcT2 = GHC.Types.TyCon 12492463661685256209## 1082997131366389398## Foo.$trModule Foo.$tcT1 0# GHC.Types.krep$*
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep2_r2nK :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep2_r2nK = GHC.Types.KindRepTyConApp Foo.$tcT2 (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep3_r2nL :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+$krep3_r2nL = GHC.Types.KindRepFun $krep_r2nI $krep2_r2nK
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+Foo.$tc'MkT1 = GHC.Types.KindRepFun $krep_r2nI $krep3_r2nL
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT6 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+Foo.$tc'MkT6 = "'MkT2"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT5 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tc'MkT5 = GHC.Types.TrNameS Foo.$tc'MkT6
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT2 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tc'MkT2 = GHC.Types.TyCon 5707542518475997625## 9584804394183763875## Foo.$trModule Foo.$tc'MkT5 0# Foo.$tc'MkT1
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT7 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$tcT7 = "T3"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT6 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tcT6 = GHC.Types.TrNameS Foo.$tcT7
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT3 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tcT3 = GHC.Types.TyCon 8915518733037212359## 16476420519216613869## Foo.$trModule Foo.$tcT6 0# GHC.Types.krep$*
+
+-- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0}
+$krep4_r2nM :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep4_r2nM = GHC.Types.KindRepTyConApp Foo.$tcT3 (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep5_r2nN :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+$krep5_r2nN = GHC.Types.KindRepFun $krep_r2nI $krep4_r2nM
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT7 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+Foo.$tc'MkT7 = GHC.Types.KindRepFun $krep_r2nI $krep5_r2nN
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT9 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+Foo.$tc'MkT9 = "'MkT3"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT8 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tc'MkT8 = GHC.Types.TrNameS Foo.$tc'MkT9
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT3 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tc'MkT3 = GHC.Types.TyCon 7218783144619306039## 13236146459150723629## Foo.$trModule Foo.$tc'MkT8 0# Foo.$tc'MkT7
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcFoo :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tcFoo = GHC.Types.TyCon 11236787750777559483## 2472662601374496863## Foo.$trModule Foo.$trModule1 0# GHC.Types.krep$*Arr*
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep6_r2nO :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep6_r2nO = GHC.Types.: @ GHC.Types.KindRep $krep1_r2nJ (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep7_r2nP :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep7_r2nP = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep6_r2nO
+
+-- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0}
+$krep8_r2nQ :: [GHC.Types.KindRep]
+[GblId, Caf=NoCafRefs, Str=m2]
+$krep8_r2nQ = GHC.Types.: @ GHC.Types.KindRep $krep_r2nI (GHC.Types.[] @ GHC.Types.KindRep)
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep9_r2nR :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep9_r2nR = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep8_r2nQ
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'Foo1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+Foo.$tc'Foo1 = GHC.Types.KindRepFun $krep_r2nI $krep9_r2nR
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'Foo3 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$tc'Foo3 = "'Foo"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'Foo2 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tc'Foo2 = GHC.Types.TrNameS Foo.$tc'Foo3
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'Foo :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tc'Foo = GHC.Types.TyCon 10641757595611461765## 13961773224584044648## Foo.$trModule Foo.$tc'Foo2 0# Foo.$tc'Foo1
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT9 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 20 0}]
+Foo.$tcT9 = "T4"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT8 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tcT8 = GHC.Types.TrNameS Foo.$tcT9
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tcT4 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tcT4 = GHC.Types.TyCon 15961711399118996930## 13694522307176382499## Foo.$trModule Foo.$tcT8 0# GHC.Types.krep$*Arr*
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep10_r2nS :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m1]
+$krep10_r2nS = GHC.Types.KindRepTyConApp Foo.$tcT4 $krep6_r2nO
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+$krep11_r2nT :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+$krep11_r2nT = GHC.Types.KindRepFun $krep_r2nI $krep10_r2nS
+
+-- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT10 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep
+[GblId, Caf=NoCafRefs, Str=m4]
+Foo.$tc'MkT10 = GHC.Types.KindRepFun $krep7_r2nP $krep11_r2nT
+
+-- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT12 :: GHC.Prim.Addr#
+[GblId,
+ Caf=NoCafRefs,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 30 0}]
+Foo.$tc'MkT12 = "'MkT4"#
+
+-- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT11 :: GHC.Types.TrName
+[GblId,
+ Caf=NoCafRefs,
+ Str=m1,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}]
+Foo.$tc'MkT11 = GHC.Types.TrNameS Foo.$tc'MkT12
+
+-- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0}
+Foo.$tc'MkT4 :: GHC.Types.TyCon
+[GblId,
+ Caf=NoCafRefs,
+ Str=m,
+ Unf=Unf{Src=<vanilla>, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}]
+Foo.$tc'MkT4 = GHC.Types.TyCon 6077781708614236332## 14823286043222481570## Foo.$trModule Foo.$tc'MkT11 1# Foo.$tc'MkT10
+
+Rec {
+-- RHS size: {terms: 14, types: 3, coercions: 0, joins: 0/0}
+Foo.$wf4 [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=2, Caf=NoCafRefs, Str=<S,1*U><S,U>]
+Foo.$wf4
+ = \ (ww_s2iK :: GHC.Prim.Int#) (ww1_s2iP :: GHC.Prim.Int#) ->
+ case GHC.Prim.># ww1_s2iP 0# of {
+ __DEFAULT -> ww_s2iK;
+ 1# -> Foo.$wf4 ww_s2iK (GHC.Prim.-# ww1_s2iP 1#)
+ }
+end Rec }
+
+-- RHS size: {terms: 17, types: 12, coercions: 3, joins: 0/0}
+f4 [InlPrag=NOUSERINLINE[0]] :: T4 Int -> Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=<S(S(S)S(S)),1*U(U(1*U),1*U(U))>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (w_s2iE [Occ=Once!] :: T4 Int) ->
+ case w_s2iE of { MkT4 ww1_s2iH [Occ=Once] ww2_s2iM [Occ=Once!] ->
+ case ww1_s2iH `cast` (Foo.D:R:FooInt0[0] ; Foo.N:R:FooInt[0] :: (Foo Int :: *) ~R# (Int :: *)) of
+ { GHC.Types.I# ww4_s2iK [Occ=Once] ->
+ case ww2_s2iM of { GHC.Types.I# ww6_s2iP [Occ=Once] ->
+ case Foo.$wf4 ww4_s2iK ww6_s2iP of ww7_s2iU { __DEFAULT -> GHC.Types.I# ww7_s2iU }
+ }
+ }
+ }}]
+f4
+ = \ (w_s2iE :: T4 Int) ->
+ case w_s2iE of { MkT4 ww1_s2iH ww2_s2iM ->
+ case ww1_s2iH `cast` (Foo.D:R:FooInt0[0] ; Foo.N:R:FooInt[0] :: (Foo Int :: *) ~R# (Int :: *)) of { GHC.Types.I# ww4_s2lV ->
+ case ww2_s2iM of { GHC.Types.I# ww6_s2iP -> case Foo.$wf4 ww4_s2lV ww6_s2iP of ww7_s2iU { __DEFAULT -> GHC.Types.I# ww7_s2iU } }
+ }
+ }
+
+Rec {
+-- RHS size: {terms: 21, types: 4, coercions: 0, joins: 0/0}
+Foo.$wf2 [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=2, Caf=NoCafRefs, Str=<L,1*U><S,U>]
+Foo.$wf2
+ = \ (ww_s2j2 :: GHC.Prim.Int#) (ww1_s2j7 :: GHC.Prim.Int#) ->
+ case GHC.Prim.># ww1_s2j7 0# of {
+ __DEFAULT ->
+ case GHC.Prim.># ww1_s2j7 1# of {
+ __DEFAULT -> ww_s2j2;
+ 1# -> 1#
+ };
+ 1# -> Foo.$wf2 ww_s2j2 (GHC.Prim.-# ww1_s2j7 1#)
+ }
+end Rec }
+
+-- RHS size: {terms: 17, types: 9, coercions: 0, joins: 0/0}
+f2 [InlPrag=NOUSERINLINE[0]] :: T2 -> Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=<S(S(S)S(S)),1*U(U(1*U),1*U(U))>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (w_s2iW [Occ=Once!] :: T2) ->
+ case w_s2iW of { MkT2 ww1_s2iZ [Occ=Once!] ww2_s2j4 [Occ=Once!] ->
+ case ww1_s2iZ of { GHC.Types.I# ww4_s2j2 [Occ=Once] ->
+ case ww2_s2j4 of { GHC.Types.I# ww6_s2j7 [Occ=Once] ->
+ case Foo.$wf2 ww4_s2j2 ww6_s2j7 of ww7_s2jc { __DEFAULT -> GHC.Types.I# ww7_s2jc }
+ }
+ }
+ }}]
+f2
+ = \ (w_s2iW :: T2) ->
+ case w_s2iW of { MkT2 ww1_s2iZ ww2_s2j4 ->
+ case ww1_s2iZ of { GHC.Types.I# ww4_s2lY ->
+ case ww2_s2j4 of { GHC.Types.I# ww6_s2j7 -> case Foo.$wf2 ww4_s2lY ww6_s2j7 of ww7_s2jc { __DEFAULT -> GHC.Types.I# ww7_s2jc } }
+ }
+ }
+
+Rec {
+-- RHS size: {terms: 15, types: 4, coercions: 0, joins: 0/0}
+Foo.$wh [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> Bool
+[GblId, Arity=2, Caf=NoCafRefs, Str=<S,1*U><S,U>]
+Foo.$wh
+ = \ (ww_s2ji :: GHC.Prim.Int#) (ww1_s2jm :: GHC.Prim.Int#) ->
+ case ww_s2ji of ds_X2fq {
+ __DEFAULT -> Foo.$wh (GHC.Prim.-# ds_X2fq 1#) ww1_s2jm;
+ 0# -> GHC.Prim.tagToEnum# @ Bool (GHC.Prim.># ww1_s2jm 0#)
+ }
+end Rec }
+
+-- RHS size: {terms: 11, types: 6, coercions: 0, joins: 0/0}
+h [InlPrag=NOUSERINLINE[0]] :: Int -> Int -> Bool
+[GblId,
+ Arity=2,
+ Caf=NoCafRefs,
+ Str=<S(S),1*U(1*U)><S(S),1*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= \ (w_s2je [Occ=Once!] :: Int) (w1_s2jf [Occ=Once!] :: Int) ->
+ case w_s2je of { GHC.Types.I# ww1_s2ji [Occ=Once] ->
+ case w1_s2jf of { GHC.Types.I# ww3_s2jm [Occ=Once] -> Foo.$wh ww1_s2ji ww3_s2jm }
+ }}]
+h = \ (w_s2je :: Int) (w1_s2jf :: Int) ->
+ case w_s2je of { GHC.Types.I# ww1_s2ji -> case w1_s2jf of { GHC.Types.I# ww3_s2jm -> Foo.$wh ww1_s2ji ww3_s2jm } }
+
+Rec {
+-- RHS size: {terms: 12, types: 2, coercions: 0, joins: 0/0}
+Foo.$wf1 [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=1, Caf=NoCafRefs, Str=<S,U>]
+Foo.$wf1
+ = \ (ww_s2js :: GHC.Prim.Int#) ->
+ case Foo.$wh ww_s2js ww_s2js of {
+ False -> Foo.$wf1 (GHC.Prim.-# ww_s2js 1#);
+ True -> ww_s2js
+ }
+end Rec }
+
+-- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0}
+f1 [InlPrag=NOUSERINLINE[0]] :: Int -> Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=<S(S),1*U(U)>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (w_s2jp [Occ=Once!] :: Int) ->
+ case w_s2jp of { GHC.Types.I# ww1_s2js [Occ=Once] -> case Foo.$wf1 ww1_s2js of ww2_s2jw { __DEFAULT -> GHC.Types.I# ww2_s2jw } }}]
+f1
+ = \ (w_s2jp :: Int) ->
+ case w_s2jp of { GHC.Types.I# ww1_s2js -> case Foo.$wf1 ww1_s2js of ww2_s2jw { __DEFAULT -> GHC.Types.I# ww2_s2jw } }
+
+Rec {
+-- RHS size: {terms: 14, types: 3, coercions: 0, joins: 0/0}
+Foo.$wf3 [InlPrag=NOUSERINLINE[0], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int#
+[GblId, Arity=2, Caf=NoCafRefs, Str=<S,U><S,U>]
+Foo.$wf3
+ = \ (ww_s2jE :: GHC.Prim.Int#) (ww1_s2jJ :: GHC.Prim.Int#) ->
+ case Foo.$wh ww_s2jE ww1_s2jJ of {
+ False -> ww_s2jE;
+ True -> Foo.$wf3 ww_s2jE (GHC.Prim.-# ww1_s2jJ 1#)
+ }
+end Rec }
+
+-- RHS size: {terms: 17, types: 9, coercions: 0, joins: 0/0}
+f3 [InlPrag=NOUSERINLINE[0]] :: T3 -> Int
+[GblId,
+ Arity=1,
+ Caf=NoCafRefs,
+ Str=<S(S(S)S(S)),1*U(1*U(U),1*U(U))>m,
+ Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True,
+ Guidance=ALWAYS_IF(arity=1,unsat_ok=True,boring_ok=False)
+ Tmpl= \ (w_s2jy [Occ=Once!] :: T3) ->
+ case w_s2jy of { MkT3 ww1_s2jB [Occ=Once!] ww2_s2jG [Occ=Once!] ->
+ case ww1_s2jB of { GHC.Types.I# ww4_s2jE [Occ=Once] ->
+ case ww2_s2jG of { GHC.Types.I# ww6_s2jJ [Occ=Once] ->
+ case Foo.$wf3 ww4_s2jE ww6_s2jJ of ww7_s2jO { __DEFAULT -> GHC.Types.I# ww7_s2jO }
+ }
+ }
+ }}]
+f3
+ = \ (w_s2jy :: T3) ->
+ case w_s2jy of { MkT3 ww1_s2jB ww2_s2jG ->
+ case ww1_s2jB of { GHC.Types.I# ww4_s2jE ->
+ case ww2_s2jG of { GHC.Types.I# ww6_s2jJ -> case Foo.$wf3 ww4_s2jE ww6_s2jJ of ww7_s2jO { __DEFAULT -> GHC.Types.I# ww7_s2jO } }
+ }
+ }
+
+
+
diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr
index 8d52da408c..9e910ccead 100644
--- a/testsuite/tests/th/TH_Roles2.stderr
+++ b/testsuite/tests/th/TH_Roles2.stderr
@@ -4,8 +4,8 @@ TYPE CONSTRUCTORS
data T (a :: k)
COERCION AXIOMS
Dependent modules: []
-Dependent packages: [array-0.5.1.2, base-4.10.0.0, deepseq-1.4.3.0,
- ghc-boot-th-8.1, ghc-prim-0.5.0.0, integer-gmp-1.0.0.1,
+Dependent packages: [array-0.5.2.0, base-4.10.0.0, deepseq-1.4.3.0,
+ ghc-boot-th-8.3, ghc-prim-0.5.1.0, integer-gmp-1.0.1.0,
pretty-1.1.3.3, template-haskell-2.12.0.0]
==================== Typechecker ====================
@@ -17,8 +17,8 @@ TH_Roles2.$tcT
(GHC.Types.TrNameS "T"#)
1
$krep
-$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0
-$krep [InlPrag=[~]]
+$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0
+$krep [InlPrag=NOUSERINLINE[~]]
= GHC.Types.KindRepFun $krep GHC.Types.krep$*
TH_Roles2.$trModule
= GHC.Types.Module