
#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): Phab:D5131 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here's a longer, and to me more comprehensible, Note {{{ Note [List fusion and continuations in 'c'] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ Suppose we define mapM_ f = foldr ((>>) . f) (return ()) (this is the way it used to be). Now suppose we want to optimise the call mapM_ <big> (build g) where g c n = ...(c x1 y1)...(c x2 y2)....n... GHC used to proceed like this: mapM_ <big> (build g) = { Defintion of mapM_ } foldr ((>>) . <big>) (return ()) (build g) = { foldr/build rule } g ((>>) . <big>) (return ()) = { Inline g ] let c = (>>) . <big> n = return () in ...(c x1 y1)...(c x2 y2)....n... The trouble is that `c`, being big, will not be inlined. And that can be absolutely terrible for performance, as we saw in Trac #8763. It's much better to define mapM_ f = foldr c (return ()) where c x k = f x >> k {-# INLINE c #-} Now we get mapM_ <big> (build g) = { inline mapM_ } foldr c (return ()) (build g) where c x k = f x >> k {-# INLINE c #-} f = <big> Notice that `f` does not inine into the RHS of `c`, because the ININE pragma stops it; see Note [How INLINE pragmas /prevent/ inlining]. Continuing: = { foldr/build rule } g c (return ()) where ... c x k = f x >> k {-# INLINE c #-} f = <big> = { inline g } ...(c x1 y1)...(c x2 y2)....n... where c x k = f x >> k {-# INLINE c #-} f = <big> n = return () Now, crucially, `c` does inline = { inline c } ...(f x1 >> y1)...(f x2 >> y2)....n... where f = <big> n = return () And all is well! The key thing is that the fragment `(f x1 >> y1)` is inlined into the body of the builder `g`. }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8763#comment:81 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler