
#8763: forM_ [1..N] does not get fused (10 times slower than go function) -------------------------------------+------------------------------------- Reporter: nh2 | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.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 sgraf): This definition of `efdtIntUpFB` only has a single occurence of `c` and `n` and consequently fixes th issue. But this probably doesn't have the same performance for the non-fused case. {{{ data CounterState = More | Last | End -- Requires x2 >= x1 {-# INLINE [0] efdtIntUpFB #-} -- See Note [Inline FB functions] in GHC.List efdtIntUpFB :: (Int -> r -> r) -> r -> Int# -> Int# -> Int# -> r efdtIntUpFB c n x1 x2 y = -- Be careful about overflow! let !first_state | isTrue# (y <# x2) = if isTrue# (y <# x1) then End else Last | otherwise = More -- Common case: x1 <= x2 <= y !delta = x2 -# x1 -- >= 0 !y' = y -# delta -- x1 <= y' <= y; hence y' is representable next_state End _ = End next_state Last _ = End next_state More x | isTrue# (x ># y') = Last | otherwise = More -- Invariant: x <= y -- Note that: z <= y' => z + delta won't overflow -- so we are guaranteed not to overflow if/when we recurse emit End _ = n emit st x | let x' = x +# delta = I# x `c` emit (next_state st x') x' in emit first_state x1 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/8763#comment:52 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler