[GHC] #13376: GHC fails to specialize a pair of polymorphic INLINABLE functions
GHC
ghc-devs at haskell.org
Sun Mar 5 04:44:37 UTC 2017
#13376: GHC fails to specialize a pair of polymorphic INLINABLE functions
-------------------------------------+-------------------------------------
Reporter: jberryman | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets: #8668
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
This is a boiled down version of a library I'm working on. It's possible
this is the same issue as #8668 which seems to have stalled. Hopefully
this example is simpler and useful in that case. Also likely the same as
this https://github.com/jmoy/testing-specialize
I have a library which defines the classes `H` and `S`; library consumers
are likely to define their own `H` instances, and import `S` instances
declared by ''other'' library authors (not me), who will depend on my `H`.
Performance depends on all of it getting fully-specialized `hash` (i.e.
for each combination of `H` and `S` that the consumer uses). But I don't
really want `hash` inlined at every call site.
Here is the code to repro with explanation below. I'm compiling like: `ghc
--make -Wall -O2 -rtsopts -funbox-strict-fields -ddump-to-file -ddump-
simpl -dsuppress-module-prefixes -dsuppress-uniques -ddump-core-stats
-ddump-inlinings -ddump-asm -fforce-recomp Main.hs`, and we get the same
bad behavior on GHC 7.10.3 and GHC 8.0.1:
Lib.hs:
{{{#!hs
module Lib where
class H h where
hash :: (S s)=> s -> h -> s
class S s where
mix :: s -> Int -> s
instance H Int where
{-# INLINABLE hash #-}
hash s = \x ->
s `mix` x
-- make this look big:
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
`mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x `mix` x
}}}
S.hs:
{{{#!hs
module S where
import Lib
newtype Foo = Foo Int
deriving Show
instance S Foo where
{-# INLINABLE mix #-}
mix (Foo x) y = Foo (x+y)
}}}
And the `Main` I'm using, though you can just call print; it's obvious
dumping inlinings when the functions get specialized and unboxed (look for
"Inlining done: $fNumInt_$c+"):
{{{#!hs
module Main where
import Lib
import S
import Criterion.Main
main = defaultMain [
bench "foo" $ whnf (hash (Foo 1)) (1::Int)
]
}}}
If I use the `INLINABLE` pragmas above or omit them entirely we get bad
code.
If I put an `INLINE` on the `hash` declaration in Lib (and no pragmas in
S), we get good unboxed additions and things are fast.
Finally and most bizarrely, if I omit the `INLINE` pragma in `hash` (and
similarly no pragmas in `S`) but make the body small enough (5 lines of
the "`mix` x `mix` x..." junk) then we also get nice unboxed code.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13376>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list