[GHC] #8763: forM_ [1..N] does not get fused (allocates 50% more)

GHC ghc-devs at haskell.org
Tue Sep 4 23:37:47 UTC 2018


#8763: forM_ [1..N] does not get fused (allocates 50% more)
-------------------------------------+-------------------------------------
        Reporter:  nh2               |                Owner:  (none)
            Type:  bug               |               Status:  new
        Priority:  normal            |            Milestone:  8.8.1
       Component:  Compiler          |              Version:  7.6.3
      Resolution:                    |             Keywords:
Operating System:  Unknown/Multiple  |         Architecture:
 Type of failure:  Runtime           |  Unknown/Multiple
  performance bug                    |            Test Case:
      Blocked By:                    |             Blocking:
 Related Tickets:  #7206             |  Differential Rev(s):
       Wiki Page:                    |
-------------------------------------+-------------------------------------

Comment (by simonpj):

 Thanks for the explanation.

 Try this
 {{{
 forM_2 :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
 forM_2 xs f = let c x k = f x >> k
                   {-# INLINE c #-}
               in foldr c (return ()) xs
 }}}
 and use `forM_2` instead of `forM_` in the outer calls in `f` and `g`.
 I then get good results for both.

 How does this work?  Well by marking `c` as INLINE, I prevent `f` from
 inlining into it -- remember, the promise of INLINE things is that what
 you write gets inlined.  And this is what we want: `c` is small, just
 `f x >> k`, and inlining it is very very good.   Without the INLINE
 pragmas on `c` we have something like
 {{{
   let f = BIG
   in let c x k = f x >> k
   in BODY
 }}}
 Since `f` occurs just once, we inline `f` to give
 {{{
   let c x k = BIG x >> k
   in BODY
 }}}
 and now `c` becomes too big to inline.  This is a classic inlining
 dilemma:
 do we inline `f` into `c` or `c` into `BODY`?  The latter is much better
 in
 this case.

 I think we could build this into the libraries just by changing the
 definition
 of `mapM_`.

 Do you agree?

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


More information about the ghc-tickets mailing list