[GHC] #11272: Overloaded state-monadic function is not specialised

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I have a simple typeclass-polymorphic function which fails to specialise. Here is module A which defines the function `overloaded`: {{{#!hs module A where import Control.Monad.Trans.State import Control.Monad overloaded :: Ord a => a -> a -> State () () overloaded x y = do () <- get when (x <= y) (overloaded y x) }}} In module B I use `overloaded` on `Int`s: {{{#!hs module B where import A import Control.Monad.Trans.State specialised :: Int -> Int -> () specialised x y = execState (A.overloaded x y) () }}} Unfortunately the generated code is not specialised but passes an `Ord` dictionary around. It doesn't make any difference if I mark `overloaded` as `INLINEABLE` or not. In the core file, `overloaded` has been worker-wrapper transformed but the worker is marked `INLINEABLE[0]` - so I'm not sure why it's not being specialised. Curiously, if I make `overloaded` be a normal function instead of one in the state monad, or if I replace `() <- get` with simply `get`, specialisation goes through fine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NickSmallbone): * Attachment "A.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NickSmallbone): * Attachment "B.hs" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NickSmallbone): * Attachment "A.hcr" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by NickSmallbone): * Attachment "B.hcr" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised
-------------------------------------+-------------------------------------
Reporter: NickSmallbone | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by simonpj):
That is terrible. I understand what is happening.
* Since `overloaded` is recursive you must have an INLINEABLE pragma to
have a chance of specialising it in an importing module
* Sadly, when compiling A.hs with `{-# INLINEABLE overloaded #-}` I see a
mutually recursive group of two functions:
{{{
Rec {
-- RHS size: {terms: 15, types: 14, coercions: 4}
T11272a.$woverloaded [InlPrag=INLINABLE[0], Occ=LoopBreaker]
:: forall a_arY. Ord a_arY => a_arY -> a_arY -> () -> (# (), () #)
[GblId,
Arity=4,
Caf=NoCafRefs,
Str=DmdType
,
Unf=Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True,
WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 0 0 20] 120
30
Tmpl= \ (@ a8_Xst)
(w_X1Me :: Ord a8_Xst)
(w1_X1Mg :: a8_Xst)
(w2_X1Mi :: a8_Xst)
(w3_s1LL [Occ=Once!] :: ()) ->
case w3_s1LL of _ [Occ=Dead] { () ->
case <= @ a8_Xst w_X1Me w1_X1Mg w2_X1Mi of _ [Occ=Dead] {
False -> (# (), () #);
True -> T11272a.$woverloaded @ a8_Xst w_X1Me w2_X1Mi
w1_X1Mg ()
}
}}]
T11272a.$woverloaded =
\ (@ a8_Xst)
(w_X1Me :: Ord a8_Xst)
(w1_X1Mg :: a8_Xst)
(w2_X1Mi :: a8_Xst)
(w3_s1LL
:: ()
Unf=OtherCon []) ->
case (a_r1OI @ a8_Xst w_X1Me w1_X1Mg w2_X1Mi w3_s1LL)
`cast` (NTCo:Identity[0] <((), ())>_R
:: Identity ((), ()) ~R# ((), ()))
of _ [Occ=Dead] { (ww1_s1LX, ww2_s1LY) ->
(# ww1_s1LX, ww2_s1LY #)
}
-- RHS size: {terms: 26, types: 17, coercions: 10}
a_r1OI
:: forall a_a1zi.
Ord a_a1zi =>
a_a1zi -> a_a1zi -> () -> Identity ((), ())
[GblId,
Arity=4,
Caf=NoCafRefs,
Str=DmdType
m]
a_r1OI =
\ (@ a8_a1zi)
(w_s1LP :: Ord a8_a1zi)
(w1_s1LQ :: a8_a1zi)
(w2_s1LR :: a8_a1zi)
(w3_s1LS :: ()) ->
case w3_s1LS of _ [Occ=Dead] { () ->
case <= @ a8_a1zi w_s1LP w1_s1LQ w2_s1LR of _ [Occ=Dead] {
False ->
lvl_r1OH
`cast` (Sym (NTCo:Identity[0] <((), ())>_R)
:: ((), ()) ~R# Identity ((), ()));
True ->
case T11272a.$woverloaded @ a8_a1zi w_s1LP w2_s1LR w1_s1LQ ()
of _ [Occ=Dead] { (# ww1_s1M1, ww2_s1M2 #) ->
(ww1_s1M1, ww2_s1M2)
`cast` (Sym (NTCo:Identity[0] <((), ())>_R)
:: ((), ()) ~R# Identity ((), ()))
}
}
}
end Rec }
}}}
That's bad; we'd prefer a tight self-recursive function.
* Worse, it doesn't specialise, because the cast makes it look as if it
doesn't have top-level lambdas.
Need to think about this, but thought I'd jot down what I know so far.
--
Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by nfrisby): If I add the `INLINABLE overloaded` pragma in `A` and place a `SPECIALIZE overloaded :: Int -> Int -> State () ()` pragma in `B`, then the desired specialization ultimately happens (with GHC 7.10.2). I mention this as a possible workaround for people stuck on this bug. Forcing the `overloaded` wrapper to be specialized creates a "SPEC" rule whose RHS gets gently simplified enough before the Specialise pass such that GHC then notices the specializable call to the `$woverloaded` worker. Since that worker inherits the original `INLINABLE` pragma (see #6056), GHC automatically specializes the worker. The specialized worker eventually ends up in the RHS of `specialised`. This approach was not obvious to me because I hadn't yet realized that forcibly specializing a w/w wrapper function tends to cause the worker to be automatically specialized. Two shortcomings come immediately to mind. 1. I get the `SPECIALISE pragma on INLINE function probably won't fire: ‘overloaded’` warning, even though the rule does fire. 1. In my experience, `SPECIALIZE` pragmas are often rejected with "LHS too complicated to desugar" (e.g. #10555), so you may need to use `GHC.Exts.inline` instead. * Note that `inline` crucially causes the w/w wrapper to be inlined before the Specialise pass (during `Phase = InitialPhase [Gentle]`), whereas the w/w wrapper's `INLINE[0]` activation delays its natural inlining until after the Specialise pass. * This is awkward: we only want to inline `overloaded` '''if it was replaced by a w/w wrapper'''! A "safer" but more troublesome alternative is to have `inline overloaded` somewhere else in the module, but then you must ensure that it's exported from this module, else GHC will cull it and the SPEC rule before the rule can usefully affect `specialise`. This risks binary bloat, but it also prevents `inline` from ever accidentally inlining `overloaded` into the genuine code. It's remarkable that the w/w transform creates the cast that prevents the wrapper from being automatically specialized (that cast floats to the top of the unfolding, which blocks specialization; see `Note [Specialisation shape]` in `Specialise.hs`). The demand analyzer and w/w transform in this example see through the `State` type synonym, `StateT` newtype, and `Identity` newtype all the way to the `s -> (# a, s #)` worker type -- the `Specialise` pass does not yet have the complementary X-ray vision to see through the corresponding cast to the desired lambdas in the wrapper's unfolding. (#9509 is also specialization-blocked-by-a-cast-atop-the-unfolding, but I think the cast in that case comes from an actual bug.) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): This appears to be fixed in HEAD (as long as `overloaded` has an `INLINABLE` pragma. I'm not sure how test cases for this sort of thing are supposed to be added to the test suite; should I be digging through `-ddump-rule-firings` or somethinhg? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari):
should I be digging through -ddump-rule-firings or somethinhg?
Either that or test `-ddump-simpl`. Both are sadly rather fragile. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: (none) Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler | Version: 7.10.3 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3561 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: new => patch * differential: => Phab:D3561 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11272: Overloaded state-monadic function is not specialised
-------------------------------------+-------------------------------------
Reporter: NickSmallbone | Owner: (none)
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.3
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: Runtime | Unknown/Multiple
performance bug | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s): Phab:D3561
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by David Feuer

#11272: Overloaded state-monadic function is not specialised -------------------------------------+------------------------------------- Reporter: NickSmallbone | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 7.10.3 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Phab:D3561 Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * status: patch => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11272#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC