[GHC] #14211: Compiler is unable to INLINE as well as the programmer can manually

GHC ghc-devs at haskell.org
Sun Sep 10 02:37:14 UTC 2017


#14211: Compiler is unable to INLINE as well as the programmer can manually
-------------------------------------+-------------------------------------
           Reporter:  harendra       |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:
          Component:  Compiler       |           Version:  8.2.1
           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:
-------------------------------------+-------------------------------------
 The test case is in this repo on the `inlining-issue` branch:
 https://github.com/harendra-kumar/ghc-perf/tree/inlining-issue.

 Performance with manually inlining a function is more than 10% faster
 compared to factoring out code and using INLINE pragma.

 `stack bench` for compiler inlined code
 {{{
 time                 46.71 ms   (45.53 ms .. 47.79 ms)
 }}}

 `stack bench --flag ghc-perf:manual` for manually inlined code
 {{{
 time                 39.46 ms   (38.92 ms .. 39.94 ms)
 }}}

 Here is the relevant code:

 {{{#!hs
 {-# INLINE bindWith #-}
 bindWith
     :: (forall c. AsyncT m c -> AsyncT m c -> AsyncT m c)
     -> AsyncT m a
     -> (a -> AsyncT m b)
     -> AsyncT m b
 bindWith k (AsyncT m) f = AsyncT $ \_ stp yld ->
     let run x = (runAsyncT x) Nothing stp yld
         yield a _ Nothing  = run $ f a
         yield a _ (Just r) = run $ f a `k` (bindWith k r f)
     in m Nothing stp yield

 instance Monad m => Monad (AsyncT m) where
     return a = AsyncT $ \ctx _ yld -> yld a ctx Nothing

 #ifdef MANUAL_INLINE
     AsyncT m >>= f = AsyncT $ \_ stp yld ->
         let run x = (runAsyncT x) Nothing stp yld
             yield a _ Nothing  = run $ f a
             yield a _ (Just r) = run $ f a <> (r >>= f)
         in m Nothing stp yield
 #else
     (>>=) = bindWith (<>)
 #endif
 }}}

 I have seen this many times.

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14211>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list