[GHC] #10346: Cross-module SpecConstr

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Blocked By: Test Case: | Related Tickets: Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- Type-class specialisation now happens flawlessly across modules. That is, if I define {{{ module DefineF where f :: Num a => a -> a {-# INLINEABLE f #-} f x = ...f x'.... }}} then modules that import `DefineF` and call `f` at some particular type (say `Int`) will generate a specialised copy of `f`'s code. But this does not happen for `SpecConstr`; we only specialise a function for calls made in the same module. All the infrastructure is in place to allow cross-module `SpecConstr`; it just hasn't been done yet. This ticket is to record the idea. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr
-------------------------------------+-------------------------------------
Reporter: simonpj | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr 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 simonpj): * keywords: => SpecConstr -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer 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 mpickering): * keywords: SpecConstr => SpecConstr, newcomer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * related: => #13016 * milestone: => 8.4.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ak3n): * owner: (none) => ak3n -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): ak3n:I have a mostly complete patch already on phab which you might want to fi nish off and refine. https://phabricator.haskell.org/D3566 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ak3n Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ak3n): I am sorry, but what is the desired behaviour? I made a simple test with modules. The first module contains the drop function, while the second one calls it. At the current moment, both versions (ghc with the patch (D3566) and ghc 8.2.1) with enabled -O2 flag optimize the function with SpecConstr pass in the first module, and substitute the call to the optimized version into the second module. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.4.1 Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ak3n): * owner: ak3n => (none) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.6.1 => Comment: Removing milestone as there is no one actively working on this at the moment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by simonpj: Old description:
Type-class specialisation now happens flawlessly across modules. That is, if I define {{{ module DefineF where f :: Num a => a -> a {-# INLINEABLE f #-} f x = ...f x'.... }}} then modules that import `DefineF` and call `f` at some particular type (say `Int`) will generate a specialised copy of `f`'s code.
But this does not happen for `SpecConstr`; we only specialise a function for calls made in the same module. All the infrastructure is in place to allow cross-module `SpecConstr`; it just hasn't been done yet. This ticket is to record the idea.
New description: Type-class specialisation now happens flawlessly across modules. That is, if I define {{{ module DefineF where f :: Num a => a -> a {-# INLINEABLE f #-} f x = ...f x'.... }}} then modules that import `DefineF` and call `f` at some particular type (say `Int`) will generate a specialised copy of `f`'s code. But this does not happen for `SpecConstr`; we only specialise a function for calls made in the same module. For example: {{{ module M where {-# INLINABLE foo #-} foo True y = y foo False (a,b) = foo True (a+b,b) module X where import M bar = ...(foo (x,y))... }}} Here `foo` is called with an explicit `(x,y)` argument in module `X`, and we'd like to !SpecConstr it, as it would be if the call was in module `M`. All the infrastructure is in place to allow cross-module `SpecConstr`; it just hasn't been done yet. This ticket is to record the idea. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ckoparkar): * owner: (none) => ckoparkar Comment: I'd like to work on this. The updated example is what helped me understand what the expected Core output should be. Thanks for that! (I'm relatively new to GHC hacking.) So far, I've read the `SpecConstr` paper, and am reading the source code now. My hunch is that we need to change the `Propagation` phase somehow to include the proper rewrite rules across modules. Is this correct ? Other than that, I don't have any specific questions at the moment. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): Are you starting from my patch https://phabricator.haskell.org/D3566 ? I understand how this is meant to work better now so can help you if you have any questions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:14 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar): I did use that patch. However, I couldn't get it to do what we want. Not sure if I did something wrong. I'm using the example given in the description: {{{ module M where {-# INLINABLE foo #-} foo True y = y foo False (a,b) = foo True (a+b,b) baz = foo False (1,2) ----------------------------------- module X where import M bar = foo False (3,4) }}} and compiling it with `ghc-stage2 -fforce-recomp -ddump-spec -ddump-rules -O X.hs`. Relevant Core output: {{{ baz :: (Integer, Integer) [LclIdX, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 240 0}] baz = foo_aZc GHC.Types.False (1, 2) }}} where `foo_aZc` is the specialized version of `foo`. On the other hand, `bar` still uses the regular `foo`. {{{ bar :: (Integer, Integer) [LclIdX, Unf=Unf{Src=<vanilla>, TopLvl=True, Value=False, ConLike=False, WorkFree=False, Expandable=False, Guidance=IF_ARGS [] 250 0}] bar = foo @ Integer GHC.Num.$fNumInteger GHC.Types.False (3, 4) }}} I'm going to use that patch as a starting point though. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:15 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar):
I understand how this is meant to work better now so can help you if you have any questions.
Thanks! I'll keep posting any updates or questions as I make some progress on this. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:16 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by mpickering): I never claimed that it worked but that it was at least somewhere to start! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:17 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar): It turns out that I was comparing the Core output of the regular Specializer instead of SpecConstr. Now that I'm looking at the proper thing, I'm a bit confused and have the same question as ak3n did. Even if I just use GHC HEAD, it seems that the call to `foo` in a different module is specialized. Using the same example with modules `M` and `X`, and compiling it with: `ghc-stage2 -O2 -fforce-recomp -ddump-spec -fspec- constr -fno-specialize X.hs`, this is what `bar` looks like after SpecConstr runs: {{{ bar :: (Integer, Integer) [LclIdX] bar = case $wfoo1_s1h9 GHC.Types.False ww_s1h3 ww_s1h4 of { (# ww_s1ha, ww_s1hb #) -> (ww_s1ha, ww_s1hb) } }}} (This is exactly what the last paragraph in the `Note [Seeding top-level recursive groups]` says should happen. There's a specialized copy of `foo` in the importing module. Or that's what I think it is.) I feel like I'm making a dumb mistake and I'm trying to track this down. mpickering: Do you remember if you were using some specific example while working on that patch ? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:18 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

Now that I'm looking at the proper thing, I'm a bit confused and have
#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by sgraf): Replying to [comment:18 ckoparkar]: the same question as ak3n did. I blame the example. 1. After SpecConstr runs on M, the call isn't really recursive anymore: There will be a specialisation for the call pattern `[x, y] |> [True, (x, y)]`. The resulting function is non-recursive, inlined, and suddenly foo itself isn't recursive anymore and simply gets inlined in X. 2. The `baz` binding in M will make it so that there is a specialisation for the call pattern `[x,y] |> [False, (x,y)]` anyway. The call in X matches this pattern, so will be specialised appropriately. Try this instead: {{{#!hs module M where {-# INLINABLE foo #-} foo 0 y = y foo n y = foo (n-1) y --baz = foo 14 (2,2) --------------------- module X where import M bar = foo 2 (3,4) }}} This works better, because integer literals are not currently considered values (probably to avoid code bloat through endless loop unrolling). Notice that the call in X specialises iff you comment in `baz` in M which has the same call pattern. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:19 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: ckoparkar Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by ckoparkar): Thanks for the explanation sgraf! I did not realize that having exactly same call patterns would triggering this. I'll try out this example later today. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:20 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10346: Cross-module SpecConstr -------------------------------------+------------------------------------- Reporter: simonpj | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.10.1 Resolution: | Keywords: SpecConstr, | newcomer Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: #13016 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by ckoparkar): * owner: ckoparkar => (none) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10346#comment:21 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC