[GHC] #8774: Transitivity of Auto-Specialization

#8774: Transitivity of Auto-Specialization -------------------------+------------------------------------------------- Reporter: | Owner: crockeea | Status: new Type: bug | Milestone: Priority: | Version: 7.6.3 normal | Operating System: Linux Component: | Type of failure: Compile-time performance bug Compiler | Test Case: Keywords: | Blocking: Architecture: | Unknown/Multiple | Difficulty: | Unknown | Blocked By: | Related Tickets: 5928, | 8668, 8099 | -------------------------+------------------------------------------------- From [http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/pragmas.html#idp49866... the docs]: [Y]ou often don't even need the SPECIALIZE pragma in the first place. When compiling a module M, GHC's optimiser (with -O) automatically considers each top-level overloaded function declared in M, and specialises it for the different types at which it is called in M. The optimiser also considers each imported INLINABLE overloaded function, and specialises it for the different types at which it is called in M. ... Moreover, given a SPECIALIZE pragma for a function f, GHC will automatically create specialisations for any type-class-overloaded functions called by f, if they are in the same module as the SPECIALIZE pragma, or if they are INLINABLE; and so on, transitively. So GHC should automatically specialize some/most/all(?) functions marked `INLINABLE` ''without'' a pragma, and if I use an explicit pragma, the specialization is transitive. My question is: is the ''auto''-specialization transitive? Either way, I'd like to see the docs updated to answer this question. Specifically, the attached files demonstrate a bug if auto-specialization ''should'' be transitive. Main.hs: {{{ #!haskell import Data.Vector.Unboxed as U import Foo main = let y = Bar $ Qux $ U.replicate 11221184 0 :: Foo (Qux Int) (Bar (Qux ans)) = iterate (plus y) y !! 100 in putStr $ show $ foldl1' (*) ans }}} Foo.hs: {{{ #!haskell module Foo (Qux(..), Foo(..), plus) where import Data.Vector.Unboxed as U newtype Qux r = Qux (Vector r) -- GHC inlines `plus` if I remove the bangs or the Baz constructor data Foo t = Bar !t | Baz !t instance (Num r, Unbox r) => Num (Qux r) where {-# INLINABLE (+) #-} (Qux x) + (Qux y) = Qux $ U.zipWith (+) x y {-# INLINABLE plus #-} plus :: (Num t) => (Foo t) -> (Foo t) -> (Foo t) plus (Bar v1) (Bar v2) = Bar $ v1 + v2 }}} GHC specializes the call to `plus`, but does *not* specialize `(+)` in the `Qux` `Num` instance. (In the attached core excerpt: `main6` calls `iterate main8`. `main8` is just `plus`, specialized for `Int`. So far so good. However, `splus` calls the *polymorphic* `c+`. If auto- specialization is transitive, I expect `c+` to be specialized to `Int`.) This kills performance: an explicit pragma `{-# SPECIALIZE plus :: Foo (Qux Int) -> Foo (Qux Int) -> Foo (Qux Int) #-}` results in ''transitive'' specialization as the docs indicate, so `(+)` is specialized and the code is 30x faster. Is this expected behavior? Should I only expect `(+)` to be specialized transitively with an explicit pragma? Note: this question is different from #5928 for two reasons: 1. I believe that no inlining is occuring, and hence I don't think inlining is interfering with specialization 2. I have `INLINABLE` pragmas on all relevant functions. Note: this question is different from #8668 because I am asking about ''auto''-specialization. This question was originally posted on [http://stackoverflow.com/questions/21502335/transitivity-of-auto- specialization-in-ghc StackOverflow]. As mentioned in the comments of that question, I am intentionally ''not'' fully applying the call to `plus` in Main, contrary to the suggestions in #8099. I'd love to see why I'm getting that behavior as well. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Operating System: Linux | Architecture: Unknown/Multiple Type of failure: Compile- | Difficulty: Unknown time performance bug | Blocked By: Test Case: | Related Tickets: #5928, #8668, Blocking: | #8099 Differential Revisions: | -------------------------------------+------------------------------------- Changes (by thomie): * related: 5928, 8668, 8099 => #5928, #8668, #8099 Comment: crockeaa: this seems to have been overlooked, maybe try asking on the ghc- devs mailinglist. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * keywords: => Inlining -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by erikd): * cc: erikd (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: erikd (removed) Comment: Matthew Pickering and I were recently pondering this. I wrote down some thoughts on the matter on #12463. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * cc: erikd (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): JFollowing your plea today, I've just tried this with HEAD. I get great, specialised code. I don't have 8.0 available. Can you try and see what happens now? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): @simonpj For the rest of us following along, how does one check this? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by bgamari): @erikd, plop the `Foo` and `Main` modules given in the ticket description in appropriately named files and compile `Main` with `ghc -ddump-simpl -dsuppress-idinfo -O`. You should see no `Foo a`s in the simplified core; instead you should see a nicely specialized definition of `plus` with all `Foo`s should be instantiated at `Int`. There should be no calls to the polymorphic `Foo.plus`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Doing as suggested I see no `Foo a` but I do see the specialized `Foo (Qux Int)` with both ghc 8.0 or with 7.10. Don't have 7.8 installed on this machine. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Even with ghc 7.6, this seems to specialize correctly: {{{ cabal exec -- ghc -fforce-recomp -ddump-simpl -dsuppress-idinfo main.hs 2>&1 | grep 'Foo a' ... @ (Foo.Qux GHC.Types.Int) @ (Foo.Foo (Foo.Qux GHC.Types.Int)) (Foo.$WBar @ (Foo.Qux GHC.Types.Int)) ... }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): I finally got 7.6 installed, and can reproduce the issue. The problem isn't that a `Foo a` appears, it's that without the SPECIALIZE pragma, there is a function called `Main.$splus` in core that takes/uses dictionaries, even though the type is monomorphic: {{{ Main.$splus :: Foo.Foo (Foo.Qux GHC.Types.Int) -> Foo.Foo (Foo.Qux GHC.Types.Int) -> Foo.Foo (Foo.Qux GHC.Types.Int) [GblId, Arity=2, Str=DmdType SS, Unf=Unf{Src=<vanilla>, TopLvl=True, Arity=2, Value=True, ConLike=True, WorkFree=True, Expandable=True, Guidance=IF_ARGS [30 30] 110 20}] Main.$splus = \ (ds_dJ0 :: Foo.Foo (Foo.Qux GHC.Types.Int)) (ds1_dJ1 :: Foo.Foo (Foo.Qux GHC.Types.Int)) -> case ds_dJ0 of _ { Foo.Bar v1_aH6 -> case ds1_dJ1 of _ { Foo.Bar v2_aH7 -> case (Foo.$fNumQux_$c+ @ GHC.Types.Int GHC.Num.$fNumInt Data.Vector.Unboxed.Base.$fUnboxInt v1_aH6 v2_aH7) }}} Replying to [comment:10 erikd]:
Even with ghc 7.6, this seems to specialize correctly:
{{{ cabal exec -- ghc -fforce-recomp -ddump-simpl -dsuppress-idinfo main.hs 2>&1 | grep Foo ... @ (Foo.Qux GHC.Types.Int) @ (Foo.Foo (Foo.Qux GHC.Types.Int)) (Foo.$WBar @ (Foo.Qux GHC.Types.Int)) ... }}}
-- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): However, as SPJ pointed out, this seems to be resolved in GHC 8.0.1. Indeed, I don't need either the SPECIALIZE ''or'' the INLINABLE with GHC 8.0.1. Kudos to it. I'll consider this resolved as soon as someone confirms (or denies) that auto-specialization is intended to be transitive. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): @crockeea Two quick questions: 1) The presence of the dictionary is inferred from case expression matching on `Foo.$fNumQux_$c+` right? 2) What command line are you using to compile this. I'm still having a bit of trouble reproducing this even with ghc 7.6.3. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): Replying to [comment:13 erikd]:
@crockeea Two quick questions:
1) The presence of the dictionary is inferred from case expression matching on `Foo.$fNumQux_$c+` right?
Not quite sure what you're asking, but the dictionaries I see are the arguments to `Foo.$fNumQux_$c+`, namely `GHC.Num.$fNumInt` and `Data.Vector.Unboxed.Base.$fUnboxInt`.
2) What command line are you using to compile this. I'm still having a
bit of trouble reproducing this even with ghc 7.6.3.
I'm compiling with `ghc-7.6.3 -ddump-simpl -O2 Main.hs`. With just the `INLINABLE` pragma on `Foo.plus`, this takes over a minute on my computer. With the `SPECIALIZE` pragma (with or without the `INLINABLE`), it completes in 3 seconds. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Without `SPECIALIZE` it takes about a second on my laptop (month old high end Dell with SSD). I simply can't image an x86_64 machine could be over 60 times slower. Ok, so the suspicious code is: {{{ case (Foo.$fNumQux_$c+ @ GHC.Types.Int GHC.Num.$fNumInt Data.Vector.Unboxed.Base.$fUnboxInt v1_aHk v2_aHl) }}} which is what I get with ghc-7.6.3. I get something very similar with ghc-7.8.4. For ghc 7.10.3 and 8.0.1 there is no instance of the string `GHC.Num` in the output from `Main` (but there is for `Foo` which is expected). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): OK, so is the conclusion is that this is a perf bug in 7.6 (and maybe 7.8) but fine now? Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#8774: Transitivity of Auto-Specialization -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.6.3 Resolution: | Keywords: Inlining Operating System: Linux | Architecture: Type of failure: Compile-time | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8668, | Differential Rev(s): #8099 | Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): @erikd: The performance disparity is odd. Not sure what to tell you there. @simonpj: Correct: performance bug in 7.6 and 7.8, fixed after that apparently. There's still the question of intended behavior: yes or no to transitivity of auto-specialization? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8774#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC