From a2f637e0df06973e6a7c33034c3bd94251766da5 Mon Sep 17 00:00:00 2001 From: Simon Peyton Jones Date: Thu, 8 Oct 2020 13:01:47 +0100 Subject: Fix some missed opportunities for preInlineUnconditionally There are two signficant changes here: * Ticket #18815 showed that we were missing some opportunities for preInlineUnconditionally. The one-line fix is in the code for GHC.Core.Opt.Simplify.Utils.preInlineUnconditionally, which now switches off only for INLINE pragmas. I expanded Note [Stable unfoldings and preInlineUnconditionally] to explain. * When doing this I discovered a way in which preInlineUnconditionally was occasionally /too/ eager. It's all explained in Note [Occurrences in stable unfoldings] in GHC.Core.Opt.OccurAnal, and the one-line change adding markAllMany to occAnalUnfolding. I also got confused about what NoUserInline meant, so I've renamed it to NoUserInlinePrag, and changed its pretty-printing slightly. That led to soem error messate wibbling, and touches quite a few files, but there is no change in functionality. I did a nofib run. As expected, no significant changes. Program Size Allocs ---------------------------------------- sphere -0.0% -0.4% ---------------------------------------- Min -0.0% -0.4% Max -0.0% +0.0% Geometric Mean -0.0% -0.0% I'm allowing a max-residency increase for T10370, which seems very irreproducible. (See comments on !4241.) There is always sampling error for max-residency measurements; and in any case the change shows up on some platforms but not others. Metric Increase: T10370 --- compiler/GHC/Core/Opt/OccurAnal.hs | 30 +- compiler/GHC/Core/Opt/Simplify.hs | 2 +- compiler/GHC/Core/Opt/Simplify/Utils.hs | 20 +- compiler/GHC/Core/Opt/Specialise.hs | 2 +- compiler/GHC/Core/Opt/WorkWrap.hs | 20 +- compiler/GHC/Hs/Binds.hs | 4 +- compiler/GHC/HsToCore/Binds.hs | 8 +- compiler/GHC/HsToCore/Quote.hs | 8 +- compiler/GHC/Parser.y | 2 +- compiler/GHC/ThToHs.hs | 2 +- compiler/GHC/Types/Basic.hs | 26 +- compiler/GHC/Utils/Binary.hs | 10 +- testsuite/tests/roles/should_compile/Roles1.stderr | 45 ++- .../tests/roles/should_compile/Roles14.stderr | 15 +- testsuite/tests/roles/should_compile/Roles2.stderr | 16 +- testsuite/tests/roles/should_compile/Roles3.stderr | 30 +- testsuite/tests/roles/should_compile/Roles4.stderr | 23 +- testsuite/tests/roles/should_compile/T8958.stderr | 27 +- testsuite/tests/simplCore/should_compile/Makefile | 11 + .../tests/simplCore/should_compile/T13143.stderr | 6 +- testsuite/tests/simplCore/should_compile/T18815.hs | 6 + .../tests/simplCore/should_compile/T3717.stderr | 4 +- .../tests/simplCore/should_compile/T3772.stdout | 2 +- .../tests/simplCore/should_compile/T4908.stderr | 4 +- .../tests/simplCore/should_compile/T4930.stderr | 4 +- .../tests/simplCore/should_compile/T7360.stderr | 4 +- .../tests/simplCore/should_compile/T7865.stdout | 2 +- testsuite/tests/simplCore/should_compile/all.T | 2 + .../simplCore/should_compile/spec-inline.stderr | 6 +- .../tests/stranal/should_compile/T10482.stderr | 200 ++++++------- .../tests/stranal/should_compile/T10482a.stderr | 323 +++++++++------------ .../tests/stranal/should_compile/T16029.stdout | 4 +- testsuite/tests/th/TH_Roles2.stderr | 11 +- 33 files changed, 436 insertions(+), 443 deletions(-) create mode 100644 testsuite/tests/simplCore/should_compile/T18815.hs diff --git a/compiler/GHC/Core/Opt/OccurAnal.hs b/compiler/GHC/Core/Opt/OccurAnal.hs index 97d38c8bd1..a746e4feb8 100644 --- a/compiler/GHC/Core/Opt/OccurAnal.hs +++ b/compiler/GHC/Core/Opt/OccurAnal.hs @@ -1693,14 +1693,16 @@ occAnalUnfolding :: OccEnv occAnalUnfolding env is_rec mb_join_arity unf = case unf of unf@(CoreUnfolding { uf_tmpl = rhs, uf_src = src }) - | isStableSource src -> (usage, unf') - | otherwise -> (emptyDetails, unf) - where -- For non-Stable unfoldings we leave them undisturbed, but + | isStableSource src -> (markAllMany usage, unf') + -- markAllMany: see Note [Occurrences in stable unfoldings] + | otherwise -> (emptyDetails, unf) + -- For non-Stable unfoldings we leave them undisturbed, but -- don't count their usage because the simplifier will discard them. -- We leave them undisturbed because nodeScore uses their size info -- to guide its decisions. It's ok to leave un-substituted -- expressions in the tree because all the variables that were in -- scope remain in scope; there is no cloning etc. + where (usage, rhs') = occAnalRhs env is_rec mb_join_arity rhs unf' | noBinderSwaps env = unf -- Note [Unfoldings and rules] @@ -1759,6 +1761,28 @@ the FloatIn pass knows to float into join point RHSs; and the simplifier does not float things out of join point RHSs. But it's a simple, cheap thing to do. See #14137. +Note [Occurrences in stable unfoldings] +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +Consider + f p = BIG + {-# INLINE g #-} + g y = not (f y) +where this is the /only/ occurrence of 'f'. So 'g' will get a stable +unfolding. Now suppose that g's RHS gets optimised (perhaps by a rule +or inlining f) so that it doesn't mention 'f' any more. Now the last +remaining call to f is in g's Stable unfolding. But, even though there +is only one syntactic occurrence of f, we do /not/ want to do +preinlineUnconditionally here! + +The INLINE pragma says "inline exactly this RHS"; perhaps the +programmer wants to expose that 'not', say. If we inline f that will make +the Stable unfoldign big, and that wasn't what the programmer wanted. + +Another way to think about it: if we inlined g as-is into multiple +call sites, now there's be multiple calls to f. + +Bottom line: treat all occurrences in a stable unfolding as "Many". + Note [Unfoldings and rules] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ Generally unfoldings and rules are already occurrence-analysed, so we diff --git a/compiler/GHC/Core/Opt/Simplify.hs b/compiler/GHC/Core/Opt/Simplify.hs index 96d9cfc61e..4ba4b0a797 100644 --- a/compiler/GHC/Core/Opt/Simplify.hs +++ b/compiler/GHC/Core/Opt/Simplify.hs @@ -549,7 +549,7 @@ mkCastWrapperInlinePrag :: InlinePragma -> InlinePragma -- See Note [Cast wrappers] mkCastWrapperInlinePrag (InlinePragma { inl_act = act, inl_rule = rule_info }) = InlinePragma { inl_src = SourceText "{-# INLINE" - , inl_inline = NoUserInline -- See Note [Wrapper NoUserInline] + , inl_inline = NoUserInlinePrag -- See Note [Wrapper NoUserInline] , inl_sat = Nothing -- in GHC.Core.Opt.WorkWrap , inl_act = wrap_act -- See Note [Wrapper activation] , inl_rule = rule_info } -- in GHC.Core.Opt.WorkWrap diff --git a/compiler/GHC/Core/Opt/Simplify/Utils.hs b/compiler/GHC/Core/Opt/Simplify/Utils.hs index 41ef2291e0..347542b446 100644 --- a/compiler/GHC/Core/Opt/Simplify/Utils.hs +++ b/compiler/GHC/Core/Opt/Simplify/Utils.hs @@ -1190,7 +1190,7 @@ However, as usual for Gentle mode, do not inline things that are inactive in the initial stages. See Note [Gentle mode]. Note [Stable unfoldings and preInlineUnconditionally] -~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ +~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Surprisingly, do not pre-inline-unconditionally Ids with INLINE pragmas! Example @@ -1210,10 +1210,18 @@ the application is saturated for exactly this reason; and we don't want PreInlineUnconditionally to second-guess it. A live example is #3736. c.f. Note [Stable unfoldings and postInlineUnconditionally] -NB: if the pragma is INLINEABLE, then we don't want to behave in -this special way -- an INLINEABLE pragma just says to GHC "inline this -if you like". But if there is a unique occurrence, we want to inline -the stable unfolding, not the RHS. +NB: this only applies for INLINE things. Do /not/ switch off +preInlineUnconditionally for + +* INLINABLE. It just says to GHC "inline this if you like". If there + is a unique occurrence, we want to inline the stable unfolding, not + the RHS. + +* NONLINE[n] just switches off inlining until phase n. We should + respect that, but after phase n, just behave as usual. + +* NoUserInlinePrag. There is no pragma at all. This ends up on wrappers. + (See #18815.) Note [Top-level bottoming Ids] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ @@ -1247,7 +1255,7 @@ preInlineUnconditionally env top_lvl bndr rhs rhs_env | not (isStableUnfolding unf) = Just (extend_subst_with rhs) -- Note [Stable unfoldings and preInlineUnconditionally] - | isInlinablePragma inline_prag + | not (isInlinePragma inline_prag) , Just inl <- maybeUnfoldingTemplate unf = Just (extend_subst_with inl) | otherwise = Nothing where diff --git a/compiler/GHC/Core/Opt/Specialise.hs b/compiler/GHC/Core/Opt/Specialise.hs index 57c49cd5c9..14a1e0cda9 100644 --- a/compiler/GHC/Core/Opt/Specialise.hs +++ b/compiler/GHC/Core/Opt/Specialise.hs @@ -1524,7 +1524,7 @@ specCalls spec_imp env existing_rules calls_for_me fn rhs -- See Note [Specialising imported functions] in "GHC.Core.Opt.OccurAnal" | InlinePragma { inl_inline = Inlinable } <- inl_prag - = (inl_prag { inl_inline = NoUserInline }, noUnfolding) + = (inl_prag { inl_inline = NoUserInlinePrag }, noUnfolding) | otherwise = (inl_prag, specUnfolding simpl_opts spec_bndrs (`mkApps` spec_args) diff --git a/compiler/GHC/Core/Opt/WorkWrap.hs b/compiler/GHC/Core/Opt/WorkWrap.hs index 97af84ee68..4994875772 100644 --- a/compiler/GHC/Core/Opt/WorkWrap.hs +++ b/compiler/GHC/Core/Opt/WorkWrap.hs @@ -446,13 +446,19 @@ Conclusion: - Otherwise inline wrapper in phase 2. That allows the 'gentle' simplification pass to apply specialisation rules - -Note [Wrapper NoUserInline] +Note [Wrapper NoUserInlinePrag] ~~~~~~~~~~~~~~~~~~~~~~~~~~~ -The use an inl_inline of NoUserInline on the wrapper distinguishes -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). +We use NoUserInlinePrag on the wrapper, to say that there is no +user-specified inline pragma. (The worker inherits that; see Note +[Worker-wrapper for INLINABLE functions].) The wrapper has no pragma +given by the user. + +(Historical note: we used to give the wrapper an INLINE pragma, but +CSE will not happen if there is a user-specified pragma, but should +happen for w/w’ed things (#14186). We don't need a pragma, because +everything we needs is expressed by (a) the stable unfolding and (b) +the inl_act activation.) + -} tryWW :: DynFlags @@ -678,7 +684,7 @@ splitFun dflags fam_envs fn_id fn_info wrap_dmds div cpr rhs mkStrWrapperInlinePrag :: InlinePragma -> InlinePragma mkStrWrapperInlinePrag (InlinePragma { inl_act = act, inl_rule = rule_info }) = InlinePragma { inl_src = SourceText "{-# INLINE" - , inl_inline = NoUserInline -- See Note [Wrapper NoUserInline] + , inl_inline = NoUserInlinePrag -- See Note [Wrapper NoUserInline] , inl_sat = Nothing , inl_act = wrap_act , inl_rule = rule_info } -- RuleMatchInfo is (and must be) unaffected diff --git a/compiler/GHC/Hs/Binds.hs b/compiler/GHC/Hs/Binds.hs index a2d46d35ed..f5e973053a 100644 --- a/compiler/GHC/Hs/Binds.hs +++ b/compiler/GHC/Hs/Binds.hs @@ -1160,8 +1160,8 @@ ppr_sig (SpecSig _ var ty inl@(InlinePragma { inl_inline = spec })) (interpp'SP ty) inl) where pragmaSrc = case spec of - NoUserInline -> "{-# SPECIALISE" - _ -> "{-# SPECIALISE_INLINE" + NoUserInlinePrag -> "{-# SPECIALISE" + _ -> "{-# SPECIALISE_INLINE" ppr_sig (InlineSig _ var inl) = pragSrcBrackets (inl_src inl) "{-# INLINE" (pprInline inl <+> pprPrefixOcc (unLoc var)) diff --git a/compiler/GHC/HsToCore/Binds.hs b/compiler/GHC/HsToCore/Binds.hs index f1140afae1..f647f2ebbf 100644 --- a/compiler/GHC/HsToCore/Binds.hs +++ b/compiler/GHC/HsToCore/Binds.hs @@ -384,10 +384,10 @@ makeCorePair dflags gbl_id is_default_method dict_arity rhs | otherwise = case inlinePragmaSpec inline_prag of - NoUserInline -> (gbl_id, rhs) - NoInline -> (gbl_id, rhs) - Inlinable -> (gbl_id `setIdUnfolding` inlinable_unf, rhs) - Inline -> inline_pair + NoUserInlinePrag -> (gbl_id, rhs) + NoInline -> (gbl_id, rhs) + Inlinable -> (gbl_id `setIdUnfolding` inlinable_unf, rhs) + Inline -> inline_pair where simpl_opts = initSimpleOpts dflags diff --git a/compiler/GHC/HsToCore/Quote.hs b/compiler/GHC/HsToCore/Quote.hs index 264fbd26f9..ada90cab6b 100644 --- a/compiler/GHC/HsToCore/Quote.hs +++ b/compiler/GHC/HsToCore/Quote.hs @@ -1108,10 +1108,10 @@ rep_specialiseInst ty loc ; return [(loc, pragma)] } repInline :: InlineSpec -> MetaM (Core TH.Inline) -repInline NoInline = dataCon noInlineDataConName -repInline Inline = dataCon inlineDataConName -repInline Inlinable = dataCon inlinableDataConName -repInline NoUserInline = notHandled "NOUSERINLINE" empty +repInline NoInline = dataCon noInlineDataConName +repInline Inline = dataCon inlineDataConName +repInline Inlinable = dataCon inlinableDataConName +repInline NoUserInlinePrag = notHandled "NOUSERINLINE" empty repRuleMatch :: RuleMatchInfo -> MetaM (Core TH.RuleMatch) repRuleMatch ConLike = dataCon conLikeDataConName diff --git a/compiler/GHC/Parser.y b/compiler/GHC/Parser.y index b8a777a8fe..b688b86310 100644 --- a/compiler/GHC/Parser.y +++ b/compiler/GHC/Parser.y @@ -2513,7 +2513,7 @@ sigdecl :: { LHsDecl GhcPs } | '{-# SPECIALISE' activation qvar '::' sigtypes1 '#-}' {% ams ( let inl_prag = mkInlinePragma (getSPEC_PRAGs $1) - (NoUserInline, FunLike) (snd $2) + (NoUserInlinePrag, FunLike) (snd $2) in sLL $1 $> $ SigD noExtField (SpecSig noExtField $3 (fromOL $5) inl_prag)) (mo $1:mu AnnDcolon $4:mc $6:(fst $2)) } diff --git a/compiler/GHC/ThToHs.hs b/compiler/GHC/ThToHs.hs index 3f093dd8b8..792b3614c3 100644 --- a/compiler/GHC/ThToHs.hs +++ b/compiler/GHC/ThToHs.hs @@ -761,7 +761,7 @@ cvtPragmaD (SpecialiseP nm ty inline phases) ; let (inline', dflt,srcText) = case inline of Just inline1 -> (cvtInline inline1, dfltActivation inline1, src inline1) - Nothing -> (NoUserInline, AlwaysActive, + Nothing -> (NoUserInlinePrag, AlwaysActive, "{-# SPECIALISE") ; let ip = InlinePragma { inl_src = SourceText srcText , inl_inline = inline' diff --git a/compiler/GHC/Types/Basic.hs b/compiler/GHC/Types/Basic.hs index 0abf8282de..5942f24d56 100644 --- a/compiler/GHC/Types/Basic.hs +++ b/compiler/GHC/Types/Basic.hs @@ -1467,11 +1467,11 @@ data RuleMatchInfo = ConLike -- See Note [CONLIKE pragma] -- | Inline Specification data InlineSpec -- What the user's INLINE pragma looked like - = Inline -- User wrote INLINE - | Inlinable -- User wrote INLINABLE - | NoInline -- User wrote NOINLINE - | NoUserInline -- User did not write any of INLINE/INLINABLE/NOINLINE - -- e.g. in `defaultInlinePragma` or when created by CSE + = Inline -- User wrote INLINE + | Inlinable -- User wrote INLINABLE + | NoInline -- User wrote NOINLINE + | NoUserInlinePrag -- User did not write any of INLINE/INLINABLE/NOINLINE + -- e.g. in `defaultInlinePragma` or when created by CSE deriving( Eq, Data, Show ) -- Show needed for GHC.Parser.Lexer @@ -1481,7 +1481,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 = NoUserInline + inl_inline = NoUserInlinePrag inl_act = AlwaysActive inl_rule = FunLike @@ -1555,15 +1555,15 @@ isFunLike FunLike = True isFunLike _ = False noUserInlineSpec :: InlineSpec -> Bool -noUserInlineSpec NoUserInline = True -noUserInlineSpec _ = False +noUserInlineSpec NoUserInlinePrag = True +noUserInlineSpec _ = False defaultInlinePragma, alwaysInlinePragma, neverInlinePragma, dfunInlinePragma :: InlinePragma defaultInlinePragma = InlinePragma { inl_src = SourceText "{-# INLINE" , inl_act = AlwaysActive , inl_rule = FunLike - , inl_inline = NoUserInline + , inl_inline = NoUserInlinePrag , inl_sat = Nothing } alwaysInlinePragma = defaultInlinePragma { inl_inline = Inline } @@ -1629,10 +1629,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 NoUserInline = text "NOUSERINLINE" -- what is better? + ppr Inline = text "INLINE" + ppr NoInline = text "NOINLINE" + ppr Inlinable = text "INLINABLE" + ppr NoUserInlinePrag = empty instance Outputable InlinePragma where ppr = pprInline diff --git a/compiler/GHC/Utils/Binary.hs b/compiler/GHC/Utils/Binary.hs index d4afa624cf..2975ab2d0d 100644 --- a/compiler/GHC/Utils/Binary.hs +++ b/compiler/GHC/Utils/Binary.hs @@ -1311,14 +1311,14 @@ instance Binary RuleMatchInfo where else return FunLike instance Binary InlineSpec where - put_ bh NoUserInline = putByte bh 0 - put_ bh Inline = putByte bh 1 - put_ bh Inlinable = putByte bh 2 - put_ bh NoInline = putByte bh 3 + put_ bh NoUserInlinePrag = 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 NoUserInline + 0 -> return NoUserInlinePrag 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 548a2c32f2..4305b2f737 100644 --- a/testsuite/tests/roles/should_compile/Roles1.stderr +++ b/testsuite/tests/roles/should_compile/Roles1.stderr @@ -20,7 +20,7 @@ DATA CONSTRUCTORS K2 :: forall a. a -> T2 a K1 :: forall a. a -> T1 a Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles1.$tcT7 @@ -79,37 +79,36 @@ Roles1.$tc'K1 = GHC.Types.TyCon 1265606750138351672## 7033043930969109074## Roles1.$trModule (GHC.Types.TrNameS "'K1"#) 1 $krep -$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[~]] +$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=[~]] = GHC.Types.KindRepFun $krep GHC.Types.krep$*Arr* -$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[~]] +$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=[~]] = GHC.Types.KindRepFun GHC.Types.krep$*Arr* GHC.Types.krep$*Arr* -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT7 ((:) $krep ((:) $krep ((:) $krep []))) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT6 ((:) $krep ((:) $krep [])) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT4 ((:) $krep ((:) $krep [])) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT3 ((:) $krep ((:) $krep [])) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT5 ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles1.$tcT2 ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = 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 569c66a6e2..461f4c1318 100644 --- a/testsuite/tests/roles/should_compile/Roles14.stderr +++ b/testsuite/tests/roles/should_compile/Roles14.stderr @@ -6,7 +6,7 @@ TYPE CONSTRUCTORS COERCION AXIOMS axiom Roles12.N:C2 :: C2 a = a -> a Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles12.$tcC2 @@ -17,14 +17,13 @@ Roles12.$tc'C:C2 = GHC.Types.TyCon 7087988437584478859## 11477953550142401435## Roles12.$trModule (GHC.Types.TrNameS "'C:C2"#) 1 $krep -$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[~]] +$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=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint [] -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = 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 f6edcbd6af..f9a13b3236 100644 --- a/testsuite/tests/roles/should_compile/Roles2.stderr +++ b/testsuite/tests/roles/should_compile/Roles2.stderr @@ -6,7 +6,7 @@ DATA CONSTRUCTORS K2 :: forall a. FunPtr a -> T2 a K1 :: forall a. IO a -> T1 a Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles2.$tcT2 @@ -25,16 +25,16 @@ Roles2.$tc'K1 = GHC.Types.TyCon 16530009231990968394## 11761390951471299534## Roles2.$trModule (GHC.Types.TrNameS "'K1"#) 1 $krep -$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[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0 +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep $krep +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Ptr.$tcFunPtr ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles2.$tcT2 ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcIO ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = 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 0c834cd53b..bfc62cc196 100644 --- a/testsuite/tests/roles/should_compile/Roles3.stderr +++ b/testsuite/tests/roles/should_compile/Roles3.stderr @@ -21,7 +21,7 @@ COERCION AXIOMS axiom Roles3.N:C3 :: C3 a b = a -> F3 b -> F3 b axiom Roles3.N:C4 :: C4 a b = a -> F4 b -> F4 b Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles3.$tcC4 @@ -48,25 +48,23 @@ Roles3.$tc'C:C1 = GHC.Types.TyCon 4508088879886988796## 13962145553903222779## Roles3.$trModule (GHC.Types.TrNameS "'C:C1"#) 1 $krep -$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[~]] +$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=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint [] -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tc~ ((:) GHC.Types.krep$* ((:) $krep ((:) $krep []))) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles3.$tcC2 ((:) $krep ((:) $krep [])) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = 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 da6d90df05..bd7baee0c6 100644 --- a/testsuite/tests/roles/should_compile/Roles4.stderr +++ b/testsuite/tests/roles/should_compile/Roles4.stderr @@ -9,7 +9,7 @@ COERCION AXIOMS axiom Roles4.N:C1 :: C1 a = a -> a axiom Roles4.N:C3 :: C3 a = a -> Syn1 a Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== Roles4.$tcC3 @@ -28,20 +28,19 @@ Roles4.$tc'C:C1 = GHC.Types.TyCon 3870707671502302648## 10631907186261837450## Roles4.$trModule (GHC.Types.TrNameS "'C:C1"#) 1 $krep -$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[~]] +$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=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tc[] ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint [] -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp Roles4.$tcC3 ((:) $krep []) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = 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 ab2d069774..203f978daa 100644 --- a/testsuite/tests/roles/should_compile/T8958.stderr +++ b/testsuite/tests/roles/should_compile/T8958.stderr @@ -16,7 +16,7 @@ CLASS INSTANCES -- Defined at T8958.hs:10:10 instance [incoherent] Nominal a -- Defined at T8958.hs:7:10 Dependent modules: [] -Dependent packages: [base-4.14.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] +Dependent packages: [base-4.15.0.0, ghc-bignum-1.0, ghc-prim-0.7.0] ==================== Typechecker ==================== T8958.$tcMap @@ -43,33 +43,32 @@ T8958.$tc'C:Nominal = GHC.Types.TyCon 10562260635335201742## 1215478186250709459## T8958.$trModule (GHC.Types.TrNameS "'C:Nominal"#) 1 $krep -$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[~]] +$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=[~]] = GHC.Types.KindRepTyConApp GHC.Tuple.$tc(,) ((:) @GHC.Types.KindRep $krep ((:) @GHC.Types.KindRep $krep [] @GHC.Types.KindRep)) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp T8958.$tcMap ((:) @GHC.Types.KindRep $krep ((:) @GHC.Types.KindRep $krep [] @GHC.Types.KindRep)) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tc[] ((:) @GHC.Types.KindRep $krep [] @GHC.Types.KindRep) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp GHC.Types.$tcConstraint [] @GHC.Types.KindRep -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp T8958.$tcRepresentational ((:) @GHC.Types.KindRep $krep [] @GHC.Types.KindRep) -$krep [InlPrag=NOUSERINLINE[~]] +$krep [InlPrag=[~]] = GHC.Types.KindRepTyConApp T8958.$tcNominal ((:) @GHC.Types.KindRep $krep [] @GHC.Types.KindRep) @@ -79,7 +78,7 @@ T8958.$trModule AbsBinds [a] [] {Exports: [T8958.$fRepresentationala <= $dRepresentational wrap: <>] - Exported types: T8958.$fRepresentationala [InlPrag=NOUSERINLINE CONLIKE] + Exported types: T8958.$fRepresentationala [InlPrag=CONLIKE] :: forall a. Representational a [LclIdX[DFunId], Unf=DFun: \ (@a) -> T8958.C:Representational TYPE: a] @@ -88,7 +87,7 @@ AbsBinds [a] [] AbsBinds [a] [] {Exports: [T8958.$fNominala <= $dNominal wrap: <>] - Exported types: T8958.$fNominala [InlPrag=NOUSERINLINE CONLIKE] + Exported types: T8958.$fNominala [InlPrag=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/Makefile b/testsuite/tests/simplCore/should_compile/Makefile index a1155d678e..3712fd5477 100644 --- a/testsuite/tests/simplCore/should_compile/Makefile +++ b/testsuite/tests/simplCore/should_compile/Makefile @@ -2,6 +2,17 @@ TOP=../../.. include $(TOP)/mk/boilerplate.mk include $(TOP)/mk/test.mk + +# T18815 should not have a non-recursive join-point for 'go' +# Previously we ended up with +# join {go_sPI w_sQ3 = case w_sQ3 of { GHC.Types.I# ww1_sQ6 -> +# jump $wgo_sQ8 ww1_sQ6 } } in +# jump go_sPI x_atE +# With the bug fixed, go is inlined, so the 'join' vanishes +T18815: + $(RM) -f T18815.o T18815.hi + - '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-simpl T18815.hs 2> /dev/null | grep 'join ' + T17966: $(RM) -f T17966.o T17966.hi - '$(TEST_HC)' $(TEST_HC_OPTS) -O -c -ddump-spec T17966.hs 2> /dev/null | grep 'SPEC' diff --git a/testsuite/tests/simplCore/should_compile/T13143.stderr b/testsuite/tests/simplCore/should_compile/T13143.stderr index f90459114b..73ac2fd1a8 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.(##) end Rec } -- RHS size: {terms: 4, types: 4, coercions: 0, joins: 0/0} -f [InlPrag=NOUSERINLINE[final]] :: forall a. Int -> a +f [InlPrag=[final]] :: forall a. Int -> a [GblId, Arity=1, Str=b, @@ -66,7 +66,7 @@ lvl = T13143.$wf @Int GHC.Prim.(##) Rec { -- RHS size: {terms: 28, types: 7, coercions: 0, joins: 0/0} -T13143.$wg [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] +T13143.$wg [InlPrag=[2], Occ=LoopBreaker] :: Bool -> Bool -> GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=3, Str=, Unf=OtherCon []] T13143.$wg @@ -86,7 +86,7 @@ T13143.$wg end Rec } -- RHS size: {terms: 14, types: 6, coercions: 0, joins: 0/0} -g [InlPrag=NOUSERINLINE[2]] :: Bool -> Bool -> Int -> Int +g [InlPrag=[2]] :: Bool -> Bool -> Int -> Int [GblId, Arity=3, Str=, diff --git a/testsuite/tests/simplCore/should_compile/T18815.hs b/testsuite/tests/simplCore/should_compile/T18815.hs new file mode 100644 index 0000000000..0bbebca603 --- /dev/null +++ b/testsuite/tests/simplCore/should_compile/T18815.hs @@ -0,0 +1,6 @@ +module T18815 where + +loop :: Int -> Int -> (Int, ()) +loop x y = go x + where + go x = if x > y then (x, ()) else go (x*2) diff --git a/testsuite/tests/simplCore/should_compile/T3717.stderr b/testsuite/tests/simplCore/should_compile/T3717.stderr index 13fc4e943a..7ed4f14e60 100644 --- a/testsuite/tests/simplCore/should_compile/T3717.stderr +++ b/testsuite/tests/simplCore/should_compile/T3717.stderr @@ -41,7 +41,7 @@ T3717.$trModule Rec { -- RHS size: {terms: 10, types: 2, coercions: 0, joins: 0/0} -T3717.$wfoo [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] +T3717.$wfoo [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=1, Str=, Unf=OtherCon []] T3717.$wfoo @@ -53,7 +53,7 @@ T3717.$wfoo end Rec } -- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0} -foo [InlPrag=NOUSERINLINE[2]] :: Int -> Int +foo [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, Str=, diff --git a/testsuite/tests/simplCore/should_compile/T3772.stdout b/testsuite/tests/simplCore/should_compile/T3772.stdout index dae44e102b..b4c072db75 100644 --- a/testsuite/tests/simplCore/should_compile/T3772.stdout +++ b/testsuite/tests/simplCore/should_compile/T3772.stdout @@ -62,7 +62,7 @@ T3772.$wfoo } -- RHS size: {terms: 6, types: 3, coercions: 0, joins: 0/0} -foo [InlPrag=NOUSERINLINE[final]] :: Int -> () +foo [InlPrag=[final]] :: Int -> () [GblId, Arity=1, Str=, diff --git a/testsuite/tests/simplCore/should_compile/T4908.stderr b/testsuite/tests/simplCore/should_compile/T4908.stderr index 76e46f98f3..84cfde275b 100644 --- a/testsuite/tests/simplCore/should_compile/T4908.stderr +++ b/testsuite/tests/simplCore/should_compile/T4908.stderr @@ -56,7 +56,7 @@ T4908.f_$s$wf end Rec } -- RHS size: {terms: 24, types: 13, coercions: 0, joins: 0/0} -T4908.$wf [InlPrag=NOUSERINLINE[2]] :: Int# -> (Int, Int) -> Bool +T4908.$wf [InlPrag=[2]] :: Int# -> (Int, Int) -> Bool [GblId, Arity=2, Str=, @@ -78,7 +78,7 @@ T4908.$wf } -- RHS size: {terms: 8, types: 6, coercions: 0, joins: 0/0} -f [InlPrag=NOUSERINLINE[2]] :: Int -> (Int, Int) -> Bool +f [InlPrag=[2]] :: Int -> (Int, Int) -> Bool [GblId, Arity=2, Str=, diff --git a/testsuite/tests/simplCore/should_compile/T4930.stderr b/testsuite/tests/simplCore/should_compile/T4930.stderr index b58298aedb..adf3bf37aa 100644 --- a/testsuite/tests/simplCore/should_compile/T4930.stderr +++ b/testsuite/tests/simplCore/should_compile/T4930.stderr @@ -41,7 +41,7 @@ T4930.$trModule Rec { -- RHS size: {terms: 17, types: 3, coercions: 0, joins: 0/0} -T4930.$wfoo [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] +T4930.$wfoo [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=1, Str=, Unf=OtherCon []] T4930.$wfoo @@ -53,7 +53,7 @@ T4930.$wfoo end Rec } -- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0} -foo [InlPrag=NOUSERINLINE[2]] :: Int -> Int +foo [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, Str=, diff --git a/testsuite/tests/simplCore/should_compile/T7360.stderr b/testsuite/tests/simplCore/should_compile/T7360.stderr index 0e1c1d1978..6295890f08 100644 --- a/testsuite/tests/simplCore/should_compile/T7360.stderr +++ b/testsuite/tests/simplCore/should_compile/T7360.stderr @@ -126,7 +126,7 @@ T7360.$tcFoo GHC.Types.krep$* -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0} -T7360.$tc'Foo4 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep +T7360.$tc'Foo4 [InlPrag=[~]] :: GHC.Types.KindRep [GblId, Unf=OtherCon []] T7360.$tc'Foo4 = GHC.Types.KindRepTyConApp @@ -189,7 +189,7 @@ T7360.$tc'Foo2 T7360.$tc'Foo4 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -T7360.$tc'Foo9 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep +T7360.$tc'Foo9 [InlPrag=[~]] :: GHC.Types.KindRep [GblId, Unf=OtherCon []] 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 76088acdb0..37bc4157cc 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=NOUSERINLINE[final]] :: Int -> Int +expensive [InlPrag=[final]] :: Int -> Int case T7865.$wexpensive ww1 of ww2 [Occ=Once1] { __DEFAULT -> 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 d9541e9318..76f9567f3d 100644 --- a/testsuite/tests/simplCore/should_compile/all.T +++ b/testsuite/tests/simplCore/should_compile/all.T @@ -340,3 +340,5 @@ test('T18649', normal, compile, ['-O -ddump-rules -Wno-simplifiable-class-constr test('T18747A', normal, compile, ['']) test('T18747B', normal, compile, ['']) +test('T18815', only_ways(['optasm']), makefile_test, ['T18815']) + diff --git a/testsuite/tests/simplCore/should_compile/spec-inline.stderr b/testsuite/tests/simplCore/should_compile/spec-inline.stderr index c91b3ef901..36639b35e1 100644 --- a/testsuite/tests/simplCore/should_compile/spec-inline.stderr +++ b/testsuite/tests/simplCore/should_compile/spec-inline.stderr @@ -73,8 +73,7 @@ Roman.foo_$s$wgo end Rec } -- RHS size: {terms: 61, types: 18, coercions: 0, joins: 0/0} -Roman.$wgo [InlPrag=NOUSERINLINE[2]] - :: Maybe Int -> Maybe Int -> GHC.Prim.Int# +Roman.$wgo [InlPrag=[2]] :: Maybe Int -> Maybe Int -> GHC.Prim.Int# [GblId, Arity=2, Str=, @@ -109,8 +108,7 @@ Roman.$wgo } -- RHS size: {terms: 9, types: 5, coercions: 0, joins: 0/0} -Roman.foo_go [InlPrag=NOUSERINLINE[2]] - :: Maybe Int -> Maybe Int -> Int +Roman.foo_go [InlPrag=[2]] :: Maybe Int -> Maybe Int -> Int [GblId, Arity=2, Str=, diff --git a/testsuite/tests/stranal/should_compile/T10482.stderr b/testsuite/tests/stranal/should_compile/T10482.stderr index 2c2f7ca067..387fca39de 100644 --- a/testsuite/tests/stranal/should_compile/T10482.stderr +++ b/testsuite/tests/stranal/should_compile/T10482.stderr @@ -3,7 +3,7 @@ Result size of Tidy Core = {terms: 167, types: 116, coercions: 15, joins: 0/0} -- RHS size: {terms: 13, types: 14, coercions: 4, joins: 0/0} -T10482.$WFooPair [InlPrag=INLINE[0]] :: forall a b. Foo a -> Foo b -> Foo (a, b) +T10482.$WFooPair [InlPrag=INLINE[final] CONLIKE] :: forall a b. Foo a %1 -> Foo b %1 -> Foo (a, b) [GblId[DataConWrapper], Arity=2, Caf=NoCafRefs, @@ -11,17 +11,17 @@ T10482.$WFooPair [InlPrag=INLINE[0]] :: forall a b. Foo a -> Foo b -> Foo (a, b) 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= \ (@a_atL) (@b_atM) (dt_a1r7 [Occ=Once] :: Foo a_atL) (dt_a1r8 [Occ=Once] :: Foo b_atM) -> - (case dt_a1r7 of dt_X0 [Occ=Once] { __DEFAULT -> - case dt_a1r8 of dt_X1 [Occ=Once] { __DEFAULT -> T10482.FooPair @a_atL @b_atM dt_X0 dt_X1 } + Tmpl= \ (@a_atI) (@b_atJ) (dt_aSX [Occ=Once1] :: Foo a_atI) (dt_aSY [Occ=Once1] :: Foo b_atJ) -> + (case dt_aSX of dt_X0 [Occ=Once1] { __DEFAULT -> + case dt_aSY of dt_X1 [Occ=Once1] { __DEFAULT -> T10482.FooPair @a_atI @b_atJ dt_X0 dt_X1 } }) - `cast` (Sym (T10482.D:R:Foo(,)0[0] _N _N) :: T10482.R:Foo(,) a_atL b_atM ~R# Foo (a_atL, b_atM))}] + `cast` (Sym (T10482.D:R:Foo(,)0[0] _N _N) :: T10482.R:Foo(,) a_atI b_atJ ~R# Foo (a_atI, b_atJ))}] T10482.$WFooPair - = \ (@a_atL) (@b_atM) (dt_a1r7 [Occ=Once] :: Foo a_atL) (dt_a1r8 [Occ=Once] :: Foo b_atM) -> - (case dt_a1r7 of dt_X0 [Occ=Once] { __DEFAULT -> - case dt_a1r8 of dt_X1 [Occ=Once] { __DEFAULT -> T10482.FooPair @a_atL @b_atM dt_X0 dt_X1 } + = \ (@a_atI) (@b_atJ) (dt_aSX [Occ=Once1] :: Foo a_atI) (dt_aSY [Occ=Once1] :: Foo b_atJ) -> + (case dt_aSX of dt_X0 [Occ=Once1] { __DEFAULT -> + case dt_aSY of dt_X1 [Occ=Once1] { __DEFAULT -> T10482.FooPair @a_atI @b_atJ dt_X0 dt_X1 } }) - `cast` (Sym (T10482.D:R:Foo(,)0[0] _N _N) :: T10482.R:Foo(,) a_atL b_atM ~R# Foo (a_atL, b_atM)) + `cast` (Sym (T10482.D:R:Foo(,)0[0] _N _N) :: T10482.R:Foo(,) a_atI b_atJ ~R# Foo (a_atI, b_atJ)) -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T10482.$trModule4 :: GHC.Prim.Addr# @@ -30,9 +30,7 @@ T10482.$trModule4 = "main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T10482.$trModule3 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] T10482.$trModule3 = GHC.Types.TrNameS T10482.$trModule4 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} @@ -42,47 +40,43 @@ T10482.$trModule2 = "T10482"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T10482.$trModule1 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] T10482.$trModule1 = GHC.Types.TrNameS T10482.$trModule2 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -T10482.$trModule :: GHC.Unit.Module -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}] -T10482.$trModule = GHC.Unit.Module T10482.$trModule3 T10482.$trModule1 +T10482.$trModule :: GHC.Types.Module +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +T10482.$trModule = GHC.Types.Module T10482.$trModule3 T10482.$trModule1 -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0} -$krep_r1Gw :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep_r1Gw = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep) +$krep_r12A :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep_r12A = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -$krep1_r1Gx :: GHC.Types.KindRep -[GblId, Cpr=m2, Unf=OtherCon []] -$krep1_r1Gx = GHC.Types.KindRepVar 1# +$krep1_r12B :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep1_r12B = GHC.Types.KindRepVar 1# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -$krep2_r1Gy :: GHC.Types.KindRep -[GblId, Cpr=m2, Unf=OtherCon []] -$krep2_r1Gy = GHC.Types.KindRepVar 0# +$krep2_r12C :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep2_r12C = GHC.Types.KindRepVar 0# -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0} -$krep3_r1Gz :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep3_r1Gz = GHC.Types.: @GHC.Types.KindRep $krep1_r1Gx (GHC.Types.[] @GHC.Types.KindRep) +$krep3_r12D :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep3_r12D = GHC.Types.: @GHC.Types.KindRep $krep1_r12B (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0} -$krep4_r1GA :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep4_r1GA = GHC.Types.: @GHC.Types.KindRep $krep2_r1Gy $krep3_r1Gz +$krep4_r12E :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep4_r12E = GHC.Types.: @GHC.Types.KindRep $krep2_r12C $krep3_r12D -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep5_r1GB :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep5_r1GB = GHC.Types.KindRepTyConApp GHC.Tuple.$tc(,) $krep4_r1GA +$krep5_r12F :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep5_r12F = GHC.Types.KindRepTyConApp GHC.Tuple.$tc(,) $krep4_r12E -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T10482.$tcFoo2 :: GHC.Prim.Addr# @@ -91,67 +85,63 @@ T10482.$tcFoo2 = "Foo"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T10482.$tcFoo1 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] T10482.$tcFoo1 = GHC.Types.TrNameS T10482.$tcFoo2 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} T10482.$tcFoo :: GHC.Types.TyCon -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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_r1GC :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep6_r1GC = GHC.Types.: @GHC.Types.KindRep $krep2_r1Gy (GHC.Types.[] @GHC.Types.KindRep) +$krep6_r12G :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep6_r12G = GHC.Types.: @GHC.Types.KindRep $krep2_r12C (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep7_r1GD :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep7_r1GD = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep6_r1GC +$krep7_r12H :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep7_r12H = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep6_r12G -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep8_r1GE :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep8_r1GE = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep3_r1Gz +$krep8_r12I :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep8_r12I = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep3_r12D -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0} -$krep9_r1GF :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep9_r1GF = GHC.Types.: @GHC.Types.KindRep $krep5_r1GB (GHC.Types.[] @GHC.Types.KindRep) +$krep9_r12J :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep9_r12J = GHC.Types.: @GHC.Types.KindRep $krep5_r12F (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep10_r1GG :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep10_r1GG = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep9_r1GF +$krep10_r12K :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep10_r12K = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep9_r12J -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep11_r1GH :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -$krep11_r1GH = GHC.Types.KindRepFun $krep8_r1GE $krep10_r1GG +$krep11_r12L :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep11_r12L = GHC.Types.KindRepFun $krep8_r12I $krep10_r12K -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -T10482.$tc'FooPair1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -T10482.$tc'FooPair1 = GHC.Types.KindRepFun $krep7_r1GD $krep11_r1GH +T10482.$tc'FooPair1 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +T10482.$tc'FooPair1 = GHC.Types.KindRepFun $krep7_r12H $krep11_r12L -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0} -$krep12_r1GI :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep12_r1GI = GHC.Types.: @GHC.Types.KindRep $krep_r1Gw (GHC.Types.[] @GHC.Types.KindRep) +$krep12_r12M :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep12_r12M = GHC.Types.: @GHC.Types.KindRep $krep_r12A (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep13_r1GJ :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep13_r1GJ = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep12_r1GI +$krep13_r12N :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep13_r12N = GHC.Types.KindRepTyConApp T10482.$tcFoo $krep12_r12M -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -T10482.$tc'Foo1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -T10482.$tc'Foo1 = GHC.Types.KindRepFun $krep_r1Gw $krep13_r1GJ +T10482.$tc'Foo1 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +T10482.$tc'Foo1 = GHC.Types.KindRepFun $krep_r12A $krep13_r12N -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} T10482.$tc'FooPair3 :: GHC.Prim.Addr# @@ -160,16 +150,12 @@ T10482.$tc'FooPair3 = "'FooPair"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T10482.$tc'FooPair2 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] T10482.$tc'FooPair = GHC.Types.TyCon 5329411373903054066## 1455261321638291317## T10482.$trModule T10482.$tc'FooPair2 2# T10482.$tc'FooPair1 @@ -180,64 +166,60 @@ T10482.$tc'Foo3 = "'Foo"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} T10482.$tc'Foo2 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] T10482.$tc'Foo = GHC.Types.TyCon 5096937192618987042## 15136671864408054946## T10482.$trModule T10482.$tc'Foo2 0# T10482.$tc'Foo1 -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -lvl_r1GK :: Int -[GblId, Cpr=m1, Unf=OtherCon []] -lvl_r1GK = GHC.Types.I# 0# +lvl_r12O :: Int +[GblId, Unf=OtherCon []] +lvl_r12O = GHC.Types.I# 0# Rec { -- RHS size: {terms: 19, types: 5, coercions: 3, joins: 0/0} -T10482.$wfoo [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: Foo Int -> GHC.Prim.Int# -> Int +T10482.$wfoo [InlPrag=[2], Occ=LoopBreaker] :: Foo Int -> GHC.Prim.Int# -> Int [GblId, Arity=2, Str=, Unf=OtherCon []] T10482.$wfoo - = \ (ww_s1Fu + = \ (ww_s11H :: Foo Int Unf=OtherCon []) - (ww1_s1FB :: GHC.Prim.Int#) -> - case ww1_s1FB of wild_X1 { + (ww1_s11O :: GHC.Prim.Int#) -> + case ww1_s11O of wild_X1 { __DEFAULT -> case GHC.Prim.remInt# wild_X1 2# of { - __DEFAULT -> ww_s1Fu `cast` (T10482.D:R:FooInt0[0] ; T10482.N:R:FooInt[0] :: Foo Int ~R# Int); - 0# -> T10482.$wfoo ww_s1Fu (GHC.Prim.-# wild_X1 1#) + __DEFAULT -> ww_s11H `cast` (T10482.D:R:FooInt0[0] ; T10482.N:R:FooInt[0] :: Foo Int ~R# Int); + 0# -> T10482.$wfoo ww_s11H (GHC.Prim.-# wild_X1 1#) }; - 0# -> lvl_r1GK + 0# -> lvl_r12O } end Rec } -- RHS size: {terms: 14, types: 27, coercions: 8, joins: 0/0} -foo [InlPrag=NOUSERINLINE[2]] :: Foo ((Int, Int), Int) -> Int -> Int +foo [InlPrag=[2]] :: Foo ((Int, Int), Int) -> Int -> Int [GblId, Arity=2, Str=, 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_s1Fn [Occ=Once] :: Foo ((Int, Int), Int)) (w1_s1Fo [Occ=Once!] :: Int) -> - case w_s1Fn `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N _N :: Foo ((Int, Int), Int) ~R# T10482.R:Foo(,) (Int, Int) Int) of - { FooPair ww1_s1Fr [Occ=Once] _ [Occ=Dead] -> - case ww1_s1Fr `cast` (T10482.D:R:Foo(,)0[0] _N _N :: Foo (Int, Int) ~R# T10482.R:Foo(,) Int Int) of - { FooPair ww4_s1Fu [Occ=Once] _ [Occ=Dead] -> - case w1_s1Fo of { GHC.Types.I# ww7_s1FB [Occ=Once] -> T10482.$wfoo ww4_s1Fu ww7_s1FB } + Tmpl= \ (w_s11A [Occ=Once1!] :: Foo ((Int, Int), Int)) (w1_s11B [Occ=Once1!] :: Int) -> + case w_s11A `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N _N :: Foo ((Int, Int), Int) ~R# T10482.R:Foo(,) (Int, Int) Int) of + { FooPair ww1_s11E [Occ=Once1!] _ [Occ=Dead] -> + case ww1_s11E `cast` (T10482.D:R:Foo(,)0[0] _N _N :: Foo (Int, Int) ~R# T10482.R:Foo(,) Int Int) of + { FooPair ww4_s11H [Occ=Once1] _ [Occ=Dead] -> + case w1_s11B of { GHC.Types.I# ww7_s11O [Occ=Once1] -> T10482.$wfoo ww4_s11H ww7_s11O } } }}] foo - = \ (w_s1Fn :: Foo ((Int, Int), Int)) (w1_s1Fo :: Int) -> - case w_s1Fn `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N _N :: Foo ((Int, Int), Int) ~R# T10482.R:Foo(,) (Int, Int) Int) of - { FooPair ww1_s1Fr ww2_s1Fx -> - case ww1_s1Fr `cast` (T10482.D:R:Foo(,)0[0] _N _N :: Foo (Int, Int) ~R# T10482.R:Foo(,) Int Int) of - { FooPair ww4_s1G0 ww5_s1G1 -> - case w1_s1Fo of { GHC.Types.I# ww7_s1FB -> T10482.$wfoo ww4_s1G0 ww7_s1FB } + = \ (w_s11A :: Foo ((Int, Int), Int)) (w1_s11B :: Int) -> + case w_s11A `cast` (T10482.D:R:Foo(,)0[0] <(Int, Int)>_N _N :: Foo ((Int, Int), Int) ~R# T10482.R:Foo(,) (Int, Int) Int) of + { FooPair ww1_s11E ww2_s11K -> + case ww1_s11E `cast` (T10482.D:R:Foo(,)0[0] _N _N :: Foo (Int, Int) ~R# T10482.R:Foo(,) Int Int) of + { FooPair ww4_s12d ww5_s12e -> + case w1_s11B of { GHC.Types.I# ww7_s11O -> T10482.$wfoo ww4_s12d ww7_s11O } } } diff --git a/testsuite/tests/stranal/should_compile/T10482a.stderr b/testsuite/tests/stranal/should_compile/T10482a.stderr index ec04d2c3c9..51b13f3a3f 100644 --- a/testsuite/tests/stranal/should_compile/T10482a.stderr +++ b/testsuite/tests/stranal/should_compile/T10482a.stderr @@ -3,7 +3,7 @@ Result size of Tidy Core = {terms: 342, types: 152, coercions: 3, joins: 0/0} -- RHS size: {terms: 9, types: 8, coercions: 0, joins: 0/0} -Foo.$WMkT4 [InlPrag=INLINE[0] CONLIKE] :: forall a. Foo a -> Int -> T4 a +Foo.$WMkT4 [InlPrag=INLINE[final] CONLIKE] :: forall a. Foo a %1 -> Int %1 -> T4 a [GblId[DataConWrapper], Arity=2, Caf=NoCafRefs, @@ -11,14 +11,14 @@ Foo.$WMkT4 [InlPrag=INLINE[0] CONLIKE] :: forall a. Foo a -> Int -> T4 a 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= \ (@a_agr) (dt_a1h9 [Occ=Once] :: Foo a_agr) (dt_a1ha [Occ=Once] :: Int) -> - case dt_a1h9 of dt_X0 [Occ=Once] { __DEFAULT -> Foo.MkT4 @a_agr dt_X0 dt_a1ha }}] + Tmpl= \ (@a_agp) (dt_aJ1 [Occ=Once1] :: Foo a_agp) (dt_aJ2 [Occ=Once1] :: Int) -> + case dt_aJ1 of dt_X0 [Occ=Once1] { __DEFAULT -> Foo.MkT4 @a_agp dt_X0 dt_aJ2 }}] Foo.$WMkT4 - = \ (@a_agr) (dt_a1h9 [Occ=Once] :: Foo a_agr) (dt_a1ha [Occ=Once] :: Int) -> - case dt_a1h9 of dt_X0 [Occ=Once] { __DEFAULT -> Foo.MkT4 @a_agr dt_X0 dt_a1ha } + = \ (@a_agp) (dt_aJ1 [Occ=Once1] :: Foo a_agp) (dt_aJ2 [Occ=Once1] :: Int) -> + case dt_aJ1 of dt_X0 [Occ=Once1] { __DEFAULT -> Foo.MkT4 @a_agp dt_X0 dt_aJ2 } -- RHS size: {terms: 8, types: 3, coercions: 0, joins: 0/0} -Foo.$WMkT2 [InlPrag=INLINE[0] CONLIKE] :: Int -> Int -> T2 +Foo.$WMkT2 [InlPrag=INLINE[final] CONLIKE] :: Int %1 -> Int %1 -> T2 [GblId[DataConWrapper], Arity=2, Caf=NoCafRefs, @@ -26,11 +26,11 @@ Foo.$WMkT2 [InlPrag=INLINE[0] CONLIKE] :: Int -> Int -> T2 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= \ (dt_a1gi [Occ=Once] :: Int) (dt_a1gj [Occ=Once] :: Int) -> - case dt_a1gi of dt_X0 [Occ=Once] { __DEFAULT -> Foo.MkT2 dt_X0 dt_a1gj }}] + Tmpl= \ (dt_aIj [Occ=Once1] :: Int) (dt_aIk [Occ=Once1] :: Int) -> + case dt_aIj of dt_X0 [Occ=Once1] { __DEFAULT -> Foo.MkT2 dt_X0 dt_aIk }}] Foo.$WMkT2 - = \ (dt_a1gi [Occ=Once] :: Int) (dt_a1gj [Occ=Once] :: Int) -> - case dt_a1gi of dt_X0 [Occ=Once] { __DEFAULT -> Foo.MkT2 dt_X0 dt_a1gj } + = \ (dt_aIj [Occ=Once1] :: Int) (dt_aIk [Occ=Once1] :: Int) -> + case dt_aIj of dt_X0 [Occ=Once1] { __DEFAULT -> Foo.MkT2 dt_X0 dt_aIk } -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$trModule4 :: GHC.Prim.Addr# @@ -39,9 +39,7 @@ Foo.$trModule4 = "main"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$trModule3 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$trModule3 = GHC.Types.TrNameS Foo.$trModule4 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} @@ -51,27 +49,23 @@ Foo.$trModule2 = "Foo"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$trModule1 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$trModule1 = GHC.Types.TrNameS Foo.$trModule2 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -Foo.$trModule :: GHC.Unit.Module -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 30}] -Foo.$trModule = GHC.Unit.Module Foo.$trModule3 Foo.$trModule1 +Foo.$trModule :: GHC.Types.Module +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] +Foo.$trModule = GHC.Types.Module Foo.$trModule3 Foo.$trModule1 -- RHS size: {terms: 3, types: 1, coercions: 0, joins: 0/0} -$krep_r1w5 :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep_r1w5 = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep) +$krep_rSS :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep_rSS = GHC.Types.KindRepTyConApp GHC.Types.$tcInt (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -$krep1_r1w6 :: GHC.Types.KindRep -[GblId, Cpr=m2, Unf=OtherCon []] -$krep1_r1w6 = GHC.Types.KindRepVar 0# +$krep1_rST :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep1_rST = GHC.Types.KindRepVar 0# -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$tcT5 :: GHC.Prim.Addr# @@ -80,32 +74,28 @@ Foo.$tcT5 = "T2"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tcT1 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$tcT1 = GHC.Types.TrNameS Foo.$tcT5 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} Foo.$tcT2 :: GHC.Types.TyCon -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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_r1w7 :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep2_r1w7 = GHC.Types.KindRepTyConApp Foo.$tcT2 (GHC.Types.[] @GHC.Types.KindRep) +$krep2_rSU :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep2_rSU = GHC.Types.KindRepTyConApp Foo.$tcT2 (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep3_r1w8 :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -$krep3_r1w8 = GHC.Types.KindRepFun $krep_r1w5 $krep2_r1w7 +$krep3_rSV :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep3_rSV = GHC.Types.KindRepFun $krep_rSS $krep2_rSU -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -Foo.$tc'MkT1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -Foo.$tc'MkT1 = GHC.Types.KindRepFun $krep_r1w5 $krep3_r1w8 +Foo.$tc'MkT1 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +Foo.$tc'MkT1 = GHC.Types.KindRepFun $krep_rSS $krep3_rSV -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT6 :: GHC.Prim.Addr# @@ -114,16 +104,12 @@ Foo.$tc'MkT6 = "'MkT2"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT5 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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} @@ -133,32 +119,28 @@ Foo.$tcT7 = "T3"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tcT6 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$tcT6 = GHC.Types.TrNameS Foo.$tcT7 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} Foo.$tcT3 :: GHC.Types.TyCon -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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_r1w9 :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep4_r1w9 = GHC.Types.KindRepTyConApp Foo.$tcT3 (GHC.Types.[] @GHC.Types.KindRep) +$krep4_rSW :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep4_rSW = GHC.Types.KindRepTyConApp Foo.$tcT3 (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep5_r1wa :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -$krep5_r1wa = GHC.Types.KindRepFun $krep_r1w5 $krep4_r1w9 +$krep5_rSX :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep5_rSX = GHC.Types.KindRepFun $krep_rSS $krep4_rSW -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -Foo.$tc'MkT7 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -Foo.$tc'MkT7 = GHC.Types.KindRepFun $krep_r1w5 $krep5_r1wa +Foo.$tc'MkT7 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +Foo.$tc'MkT7 = GHC.Types.KindRepFun $krep_rSS $krep5_rSX -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT9 :: GHC.Prim.Addr# @@ -167,49 +149,43 @@ Foo.$tc'MkT9 = "'MkT3"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT8 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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_r1wb :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep6_r1wb = GHC.Types.: @GHC.Types.KindRep $krep1_r1w6 (GHC.Types.[] @GHC.Types.KindRep) +$krep6_rSY :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep6_rSY = GHC.Types.: @GHC.Types.KindRep $krep1_rST (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep7_r1wc :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep7_r1wc = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep6_r1wb +$krep7_rSZ :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep7_rSZ = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep6_rSY -- RHS size: {terms: 3, types: 2, coercions: 0, joins: 0/0} -$krep8_r1wd :: [GHC.Types.KindRep] -[GblId, Cpr=m2, Unf=OtherCon []] -$krep8_r1wd = GHC.Types.: @GHC.Types.KindRep $krep_r1w5 (GHC.Types.[] @GHC.Types.KindRep) +$krep8_rT0 :: [GHC.Types.KindRep] +[GblId, Unf=OtherCon []] +$krep8_rT0 = GHC.Types.: @GHC.Types.KindRep $krep_rSS (GHC.Types.[] @GHC.Types.KindRep) -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep9_r1we :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep9_r1we = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep8_r1wd +$krep9_rT1 :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep9_rT1 = GHC.Types.KindRepTyConApp Foo.$tcFoo $krep8_rT0 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -Foo.$tc'Foo1 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -Foo.$tc'Foo1 = GHC.Types.KindRepFun $krep_r1w5 $krep9_r1we +Foo.$tc'Foo1 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +Foo.$tc'Foo1 = GHC.Types.KindRepFun $krep_rSS $krep9_rT1 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$tc'Foo3 :: GHC.Prim.Addr# @@ -218,16 +194,12 @@ Foo.$tc'Foo3 = "'Foo"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tc'Foo2 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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} @@ -237,32 +209,28 @@ Foo.$tcT9 = "T4"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tcT8 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$tcT8 = GHC.Types.TrNameS Foo.$tcT9 -- RHS size: {terms: 7, types: 0, coercions: 0, joins: 0/0} Foo.$tcT4 :: GHC.Types.TyCon -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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_r1wf :: GHC.Types.KindRep -[GblId, Cpr=m1, Unf=OtherCon []] -$krep10_r1wf = GHC.Types.KindRepTyConApp Foo.$tcT4 $krep6_r1wb +$krep10_rT2 :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep10_rT2 = GHC.Types.KindRepTyConApp Foo.$tcT4 $krep6_rSY -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -$krep11_r1wg :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -$krep11_r1wg = GHC.Types.KindRepFun $krep_r1w5 $krep10_r1wf +$krep11_rT3 :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +$krep11_rT3 = GHC.Types.KindRepFun $krep_rSS $krep10_rT2 -- RHS size: {terms: 3, types: 0, coercions: 0, joins: 0/0} -Foo.$tc'MkT10 [InlPrag=NOUSERINLINE[~]] :: GHC.Types.KindRep -[GblId, Cpr=m4, Unf=OtherCon []] -Foo.$tc'MkT10 = GHC.Types.KindRepFun $krep7_r1wc $krep11_r1wg +Foo.$tc'MkT10 [InlPrag=[~]] :: GHC.Types.KindRep +[GblId, Unf=OtherCon []] +Foo.$tc'MkT10 = GHC.Types.KindRepFun $krep7_rSZ $krep11_rT3 -- RHS size: {terms: 1, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT12 :: GHC.Prim.Addr# @@ -271,174 +239,169 @@ Foo.$tc'MkT12 = "'MkT4"# -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} Foo.$tc'MkT11 :: GHC.Types.TrName -[GblId, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 20}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] 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, - Cpr=m1, - Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 70}] +[GblId, Unf=Unf{Src=, TopLvl=True, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [] 10 10}] Foo.$tc'MkT4 = GHC.Types.TyCon 6077781708614236332## 14823286043222481570## Foo.$trModule Foo.$tc'MkT11 1# Foo.$tc'MkT10 Rec { -- RHS size: {terms: 14, types: 4, coercions: 3, joins: 0/0} -Foo.$wf4 [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: Foo Int -> GHC.Prim.Int# -> Int +Foo.$wf4 [InlPrag=[2], Occ=LoopBreaker] :: Foo Int -> GHC.Prim.Int# -> Int [GblId, Arity=2, Str=, Unf=OtherCon []] Foo.$wf4 - = \ (ww_s1sF + = \ (ww_sPs :: Foo Int Unf=OtherCon []) - (ww1_s1sJ :: GHC.Prim.Int#) -> - case GHC.Prim.># ww1_s1sJ 0# of { - __DEFAULT -> ww_s1sF `cast` (Foo.D:R:FooInt0[0] ; Foo.N:R:FooInt[0] :: Foo Int ~R# Int); - 1# -> Foo.$wf4 ww_s1sF (GHC.Prim.-# ww1_s1sJ 1#) + (ww1_sPw :: GHC.Prim.Int#) -> + case GHC.Prim.># ww1_sPw 0# of { + __DEFAULT -> ww_sPs `cast` (Foo.D:R:FooInt0[0] ; Foo.N:R:FooInt[0] :: Foo Int ~R# Int); + 1# -> Foo.$wf4 ww_sPs (GHC.Prim.-# ww1_sPw 1#) } end Rec } -- RHS size: {terms: 10, types: 9, coercions: 0, joins: 0/0} -f4 [InlPrag=NOUSERINLINE[2]] :: T4 Int -> Int +f4 [InlPrag=[2]] :: T4 Int -> Int [GblId, Arity=1, Str=, 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_s1sC [Occ=Once!] :: T4 Int) -> - case w_s1sC of { MkT4 ww1_s1sF [Occ=Once] ww2_s1sG [Occ=Once!] -> - case ww2_s1sG of { GHC.Types.I# ww4_s1sJ [Occ=Once] -> Foo.$wf4 ww1_s1sF ww4_s1sJ } + Tmpl= \ (w_sPp [Occ=Once1!] :: T4 Int) -> + case w_sPp of { MkT4 ww1_sPs [Occ=Once1] ww2_sPt [Occ=Once1!] -> + case ww2_sPt of { GHC.Types.I# ww4_sPw [Occ=Once1] -> Foo.$wf4 ww1_sPs ww4_sPw } }}] f4 - = \ (w_s1sC :: T4 Int) -> - case w_s1sC of { MkT4 ww1_s1sF ww2_s1sG -> case ww2_s1sG of { GHC.Types.I# ww4_s1sJ -> Foo.$wf4 ww1_s1sF ww4_s1sJ } } + = \ (w_sPp :: T4 Int) -> + case w_sPp of { MkT4 ww1_sPs ww2_sPt -> case ww2_sPt of { GHC.Types.I# ww4_sPw -> Foo.$wf4 ww1_sPs ww4_sPw } } -- RHS size: {terms: 2, types: 0, coercions: 0, joins: 0/0} -lvl_r1wh :: Int -[GblId, Cpr=m1, Unf=OtherCon []] -lvl_r1wh = GHC.Types.I# 1# +lvl_rT4 :: Int +[GblId, Unf=OtherCon []] +lvl_rT4 = GHC.Types.I# 1# Rec { -- RHS size: {terms: 21, types: 4, coercions: 0, joins: 0/0} -Foo.$wf2 [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: Int -> GHC.Prim.Int# -> Int +Foo.$wf2 [InlPrag=[2], Occ=LoopBreaker] :: Int -> GHC.Prim.Int# -> Int [GblId, Arity=2, Str=, Unf=OtherCon []] Foo.$wf2 - = \ (ww_s1sQ + = \ (ww_sPD :: Int Unf=OtherCon []) - (ww1_s1sU :: GHC.Prim.Int#) -> - case GHC.Prim.># ww1_s1sU 0# of { + (ww1_sPH :: GHC.Prim.Int#) -> + case GHC.Prim.># ww1_sPH 0# of { __DEFAULT -> - case GHC.Prim.># ww1_s1sU 1# of { - __DEFAULT -> ww_s1sQ; - 1# -> lvl_r1wh + case GHC.Prim.># ww1_sPH 1# of { + __DEFAULT -> ww_sPD; + 1# -> lvl_rT4 }; - 1# -> Foo.$wf2 ww_s1sQ (GHC.Prim.-# ww1_s1sU 1#) + 1# -> Foo.$wf2 ww_sPD (GHC.Prim.-# ww1_sPH 1#) } end Rec } -- RHS size: {terms: 10, types: 6, coercions: 0, joins: 0/0} -f2 [InlPrag=NOUSERINLINE[2]] :: T2 -> Int +f2 [InlPrag=[2]] :: T2 -> Int [GblId, Arity=1, Str=, 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_s1sN [Occ=Once!] :: T2) -> - case w_s1sN of { MkT2 ww1_s1sQ [Occ=Once] ww2_s1sR [Occ=Once!] -> - case ww2_s1sR of { GHC.Types.I# ww4_s1sU [Occ=Once] -> Foo.$wf2 ww1_s1sQ ww4_s1sU } + Tmpl= \ (w_sPA [Occ=Once1!] :: T2) -> + case w_sPA of { MkT2 ww1_sPD [Occ=Once1] ww2_sPE [Occ=Once1!] -> + case ww2_sPE of { GHC.Types.I# ww4_sPH [Occ=Once1] -> Foo.$wf2 ww1_sPD ww4_sPH } }}] f2 - = \ (w_s1sN :: T2) -> - case w_s1sN of { MkT2 ww1_s1sQ ww2_s1sR -> case ww2_s1sR of { GHC.Types.I# ww4_s1sU -> Foo.$wf2 ww1_s1sQ ww4_s1sU } } + = \ (w_sPA :: T2) -> case w_sPA of { MkT2 ww1_sPD ww2_sPE -> case ww2_sPE of { GHC.Types.I# ww4_sPH -> Foo.$wf2 ww1_sPD ww4_sPH } } Rec { -- RHS size: {terms: 15, types: 4, coercions: 0, joins: 0/0} -Foo.$wh [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> Bool +Foo.$wh [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> Bool [GblId, Arity=2, Str=, Unf=OtherCon []] Foo.$wh - = \ (ww_s1t2 :: GHC.Prim.Int#) (ww1_s1t6 :: GHC.Prim.Int#) -> - case ww_s1t2 of ds_X2 { - __DEFAULT -> Foo.$wh (GHC.Prim.-# ds_X2 1#) ww1_s1t6; - 0# -> GHC.Prim.tagToEnum# @Bool (GHC.Prim.># ww1_s1t6 0#) + = \ (ww_sPP :: GHC.Prim.Int#) (ww1_sPT :: GHC.Prim.Int#) -> + case ww_sPP of ds_X2 { + __DEFAULT -> Foo.$wh (GHC.Prim.-# ds_X2 1#) ww1_sPT; + 0# -> GHC.Prim.tagToEnum# @Bool (GHC.Prim.># ww1_sPT 0#) } end Rec } -- RHS size: {terms: 11, types: 6, coercions: 0, joins: 0/0} -h [InlPrag=NOUSERINLINE[2]] :: Int -> Int -> Bool +h [InlPrag=[2]] :: Int -> Int -> Bool [GblId, Arity=2, Str=, 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_s1sY [Occ=Once!] :: Int) (w1_s1sZ [Occ=Once!] :: Int) -> - case w_s1sY of { GHC.Types.I# ww1_s1t2 [Occ=Once] -> - case w1_s1sZ of { GHC.Types.I# ww3_s1t6 [Occ=Once] -> Foo.$wh ww1_s1t2 ww3_s1t6 } + Tmpl= \ (w_sPL [Occ=Once1!] :: Int) (w1_sPM [Occ=Once1!] :: Int) -> + case w_sPL of { GHC.Types.I# ww1_sPP [Occ=Once1] -> + case w1_sPM of { GHC.Types.I# ww3_sPT [Occ=Once1] -> Foo.$wh ww1_sPP ww3_sPT } }}] -h = \ (w_s1sY :: Int) (w1_s1sZ :: Int) -> - case w_s1sY of { GHC.Types.I# ww1_s1t2 -> case w1_s1sZ of { GHC.Types.I# ww3_s1t6 -> Foo.$wh ww1_s1t2 ww3_s1t6 } } +h = \ (w_sPL :: Int) (w1_sPM :: Int) -> + case w_sPL of { GHC.Types.I# ww1_sPP -> case w1_sPM of { GHC.Types.I# ww3_sPT -> Foo.$wh ww1_sPP ww3_sPT } } Rec { -- RHS size: {terms: 12, types: 2, coercions: 0, joins: 0/0} -Foo.$wf1 [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# +Foo.$wf1 [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=1, Str=, Unf=OtherCon []] Foo.$wf1 - = \ (ww_s1tc :: GHC.Prim.Int#) -> - case Foo.$wh ww_s1tc ww_s1tc of { - False -> Foo.$wf1 (GHC.Prim.-# ww_s1tc 1#); - True -> ww_s1tc + = \ (ww_sPZ :: GHC.Prim.Int#) -> + case Foo.$wh ww_sPZ ww_sPZ of { + False -> Foo.$wf1 (GHC.Prim.-# ww_sPZ 1#); + True -> ww_sPZ } end Rec } -- RHS size: {terms: 10, types: 4, coercions: 0, joins: 0/0} -f1 [InlPrag=NOUSERINLINE[2]] :: Int -> Int +f1 [InlPrag=[2]] :: Int -> Int [GblId, Arity=1, Str=, Cpr=m1, 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_s1t9 [Occ=Once!] :: Int) -> - case w_s1t9 of { GHC.Types.I# ww1_s1tc [Occ=Once] -> - case Foo.$wf1 ww1_s1tc of ww2_s1tg [Occ=Once] { __DEFAULT -> GHC.Types.I# ww2_s1tg } + Tmpl= \ (w_sPW [Occ=Once1!] :: Int) -> + case w_sPW of { GHC.Types.I# ww1_sPZ [Occ=Once1] -> + case Foo.$wf1 ww1_sPZ of ww2_sQ3 [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww2_sQ3 } }}] f1 - = \ (w_s1t9 :: Int) -> - case w_s1t9 of { GHC.Types.I# ww1_s1tc -> case Foo.$wf1 ww1_s1tc of ww2_s1tg { __DEFAULT -> GHC.Types.I# ww2_s1tg } } + = \ (w_sPW :: Int) -> + case w_sPW of { GHC.Types.I# ww1_sPZ -> case Foo.$wf1 ww1_sPZ of ww2_sQ3 { __DEFAULT -> GHC.Types.I# ww2_sQ3 } } Rec { -- RHS size: {terms: 14, types: 3, coercions: 0, joins: 0/0} -Foo.$wf3 [InlPrag=NOUSERINLINE[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# +Foo.$wf3 [InlPrag=[2], Occ=LoopBreaker] :: GHC.Prim.Int# -> GHC.Prim.Int# -> GHC.Prim.Int# [GblId, Arity=2, Str=, Unf=OtherCon []] Foo.$wf3 - = \ (ww_s1to :: GHC.Prim.Int#) (ww1_s1tt :: GHC.Prim.Int#) -> - case Foo.$wh ww_s1to ww1_s1tt of { - False -> ww_s1to; - True -> Foo.$wf3 ww_s1to (GHC.Prim.-# ww1_s1tt 1#) + = \ (ww_sQb :: GHC.Prim.Int#) (ww1_sQg :: GHC.Prim.Int#) -> + case Foo.$wh ww_sQb ww1_sQg of { + False -> ww_sQb; + True -> Foo.$wf3 ww_sQb (GHC.Prim.-# ww1_sQg 1#) } end Rec } -- RHS size: {terms: 17, types: 9, coercions: 0, joins: 0/0} -f3 [InlPrag=NOUSERINLINE[2]] :: T3 -> Int +f3 [InlPrag=[2]] :: T3 -> Int [GblId, Arity=1, Str=, Cpr=m1, 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_s1ti [Occ=Once!] :: T3) -> - case w_s1ti of { MkT3 ww1_s1tl [Occ=Once!] ww2_s1tq [Occ=Once!] -> - case ww1_s1tl of { GHC.Types.I# ww4_s1to [Occ=Once] -> - case ww2_s1tq of { GHC.Types.I# ww6_s1tt [Occ=Once] -> - case Foo.$wf3 ww4_s1to ww6_s1tt of ww7_s1ty [Occ=Once] { __DEFAULT -> GHC.Types.I# ww7_s1ty } + Tmpl= \ (w_sQ5 [Occ=Once1!] :: T3) -> + case w_sQ5 of { MkT3 ww1_sQ8 [Occ=Once1!] ww2_sQd [Occ=Once1!] -> + case ww1_sQ8 of { GHC.Types.I# ww4_sQb [Occ=Once1] -> + case ww2_sQd of { GHC.Types.I# ww6_sQg [Occ=Once1] -> + case Foo.$wf3 ww4_sQb ww6_sQg of ww7_sQl [Occ=Once1] { __DEFAULT -> GHC.Types.I# ww7_sQl } } } }}] f3 - = \ (w_s1ti :: T3) -> - case w_s1ti of { MkT3 ww1_s1tl ww2_s1tq -> - case ww1_s1tl of { GHC.Types.I# ww4_s1to -> - case ww2_s1tq of { GHC.Types.I# ww6_s1tt -> case Foo.$wf3 ww4_s1to ww6_s1tt of ww7_s1ty { __DEFAULT -> GHC.Types.I# ww7_s1ty } } + = \ (w_sQ5 :: T3) -> + case w_sQ5 of { MkT3 ww1_sQ8 ww2_sQd -> + case ww1_sQ8 of { GHC.Types.I# ww4_sQb -> + case ww2_sQd of { GHC.Types.I# ww6_sQg -> case Foo.$wf3 ww4_sQb ww6_sQg of ww7_sQl { __DEFAULT -> GHC.Types.I# ww7_sQl } } } } diff --git a/testsuite/tests/stranal/should_compile/T16029.stdout b/testsuite/tests/stranal/should_compile/T16029.stdout index 59507ee4ce..2d1f2106f3 100644 --- a/testsuite/tests/stranal/should_compile/T16029.stdout +++ b/testsuite/tests/stranal/should_compile/T16029.stdout @@ -3,9 +3,9 @@ = \ (dt [Occ=Once1!] :: Int) (dt [Occ=Once1!] :: Int) -> :: GHC.Prim.Int# -> GHC.Prim.Int# = \ (ww :: GHC.Prim.Int#) -> -g2 [InlPrag=NOUSERINLINE[2]] :: T -> Int -> Int +g2 [InlPrag=[2]] :: T -> Int -> Int Tmpl= \ (w [Occ=Once1!] :: T) (w1 [Occ=Once1!] :: Int) -> = \ (w :: T) (w1 :: Int) -> -g1 [InlPrag=NOUSERINLINE[2]] :: S -> Int -> Int +g1 [InlPrag=[2]] :: S -> Int -> Int Tmpl= \ (w [Occ=Once1!] :: S) (w1 [Occ=Once1!] :: Int) -> = \ (w :: S) (w1 :: Int) -> diff --git a/testsuite/tests/th/TH_Roles2.stderr b/testsuite/tests/th/TH_Roles2.stderr index c2cea26115..43ce297d3a 100644 --- a/testsuite/tests/th/TH_Roles2.stderr +++ b/testsuite/tests/th/TH_Roles2.stderr @@ -2,18 +2,17 @@ TYPE CONSTRUCTORS data type T{2} :: forall k. k -> * roles nominal representational Dependent modules: [] -Dependent packages: [array-0.5.4.0, base-4.14.0.0, deepseq-1.4.4.0, - ghc-bignum-1.0, ghc-boot-th-8.9.0.20191106, ghc-prim-0.7.0, - pretty-1.1.3.6, template-haskell-2.16.0.0] +Dependent packages: [array-0.5.4.0, base-4.15.0.0, deepseq-1.4.4.0, + ghc-bignum-1.0, ghc-boot-th-9.1.0.20201005, ghc-prim-0.7.0, + pretty-1.1.3.6, template-haskell-2.17.0.0] ==================== Typechecker ==================== TH_Roles2.$tcT = GHC.Types.TyCon 11651627537942629178## 11503899791410937231## TH_Roles2.$trModule (GHC.Types.TrNameS "T"#) 1 $krep -$krep [InlPrag=NOUSERINLINE[~]] = GHC.Types.KindRepVar 0 -$krep [InlPrag=NOUSERINLINE[~]] - = GHC.Types.KindRepFun $krep GHC.Types.krep$* +$krep [InlPrag=[~]] = GHC.Types.KindRepVar 0 +$krep [InlPrag=[~]] = GHC.Types.KindRepFun $krep GHC.Types.krep$* TH_Roles2.$trModule = GHC.Types.Module (GHC.Types.TrNameS "main"#) (GHC.Types.TrNameS "TH_Roles2"#) -- cgit v1.2.1