[GHC] #12454: Cross-module specialisation of recursive functions

#12454: Cross-module specialisation of recursive functions -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Keywords: Inlining | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: #5928 Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- It is common for library authors to write overloaded functions but in doing so they cause a performance penalty for their consumers as GHC refuses the specialise such functions across modules. For example, {{{#!hs {-# language FlexibleContexts #-} module M where import Control.Monad.IO.Class import Control.Monad.Reader hello :: (MonadIO m, MonadReader Int m) => Int -> m () hello n = do m <- ask case m `mod` n == 0 of True -> liftIO $ print "helloo" False -> hello (n-1) }}} Using `hello` in a client module, we would like to optimise away the explicit dictionary passing once we specialise `hello` to a specific monad stack. {{{#!hs import M import Control.Monad.Reader import M (hello) main :: IO () main = runReaderT (hello 128) 42 }}} However, as `hello` is recursive its unfolding was not included in the interface file. As a result, the specialisation can't take place which leaves us with less efficient code. The solution to this is mark `hello` as `INLINABLE`. Once we do this the unfolding of `hello` is included in the interface file even though `hello` will never be inlined as it is self-recursive and hence the loop-breaker. Once included in the interface file, GHC can properly specialise `hello` and produce optimal code. An aside, it is quite strange to mark such a recursive definition as `INLINABLE` to get this behaviour as you know it will never be inlined. It would perhaps be better to have a better named pragma which ensured unfoldings were placed in interface files. This ticket is to track the behaviour of these types of definitions which are very common in the wild. A proposed solution on #5928 was to add a flag to always mark overloaded functions as inlinable to make sure these specialisations can take place. This is something which I am planning to implement in order to see what the consequences are in terms of performance and interface file sizes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12454 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12454: Cross-module specialisation of recursive functions -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * Attachment "opt.txt" added. Core when marking hello as inlinable -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12454 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12454: Cross-module specialisation of recursive functions -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * Attachment "unopt.txt" added. Core when not marking hello as inlinable -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12454 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12454: Cross-module specialisation of recursive functions -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5928 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by mpickering: @@ -52,0 +52,7 @@ + The two attached files contain the core for these two programs. They were + compiled with + + {{{ + ghc-8.0.1 -fforce-recomp -ddump-simpl -O2 mtl-stack.hs + }}} + New description: It is common for library authors to write overloaded functions but in doing so they cause a performance penalty for their consumers as GHC refuses the specialise such functions across modules. For example, {{{#!hs {-# language FlexibleContexts #-} module M where import Control.Monad.IO.Class import Control.Monad.Reader hello :: (MonadIO m, MonadReader Int m) => Int -> m () hello n = do m <- ask case m `mod` n == 0 of True -> liftIO $ print "helloo" False -> hello (n-1) }}} Using `hello` in a client module, we would like to optimise away the explicit dictionary passing once we specialise `hello` to a specific monad stack. {{{#!hs import M import Control.Monad.Reader import M (hello) main :: IO () main = runReaderT (hello 128) 42 }}} However, as `hello` is recursive its unfolding was not included in the interface file. As a result, the specialisation can't take place which leaves us with less efficient code. The solution to this is mark `hello` as `INLINABLE`. Once we do this the unfolding of `hello` is included in the interface file even though `hello` will never be inlined as it is self-recursive and hence the loop-breaker. Once included in the interface file, GHC can properly specialise `hello` and produce optimal code. An aside, it is quite strange to mark such a recursive definition as `INLINABLE` to get this behaviour as you know it will never be inlined. It would perhaps be better to have a better named pragma which ensured unfoldings were placed in interface files. The two attached files contain the core for these two programs. They were compiled with {{{ ghc-8.0.1 -fforce-recomp -ddump-simpl -O2 mtl-stack.hs }}} This ticket is to track the behaviour of these types of definitions which are very common in the wild. A proposed solution on #5928 was to add a flag to always mark overloaded functions as inlinable to make sure these specialisations can take place. This is something which I am planning to implement in order to see what the consequences are in terms of performance and interface file sizes. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12454#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12454: Cross-module specialisation of recursive functions -------------------------------------+------------------------------------- Reporter: mpickering | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Inlining Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #5928, #8589 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * related: #5928 => #5928, #8589 Comment: #8589 also provides some discussion about adding inlinable pragmas to recursive functions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12454#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC