Skip to content

Commit

Permalink
Merge pull request #219 from ndmitchell/master
Browse files Browse the repository at this point in the history
Fix #218, mapAccum and mapAccumM should be strict in their state
  • Loading branch information
snoyberg committed Jul 23, 2015
2 parents 09e7f6c + bb1a072 commit de53a2f
Showing 1 changed file with 6 additions and 5 deletions.
11 changes: 6 additions & 5 deletions conduit/Data/Conduit/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -510,7 +510,7 @@ concatMapMC f = awaitForever $ sourceList <=< lift . f
{-# INLINE concatMapMC #-}
STREAMING(concatMapM, concatMapMC, concatMapMS, f)

-- | 'concatMap' with an accumulator.
-- | 'concatMap' with a strict accumulator.
--
-- Subject to fusion
--
Expand All @@ -535,7 +535,8 @@ scanlM f s = void $ mapAccumM f s
{-# DEPRECATED scanlM "Use mapAccumM instead" #-}

-- | Analog of @mapAccumL@ for lists. Note that in contrast to @mapAccumL@, the function argument
-- takes the accumulator as its second argument, not its first argument.
-- takes the accumulator as its second argument, not its first argument, and the accumulated value
-- is strict.
--
-- Subject to fusion
--
Expand All @@ -544,7 +545,7 @@ mapAccum, mapAccumC :: Monad m => (a -> s -> (s, b)) -> s -> ConduitM a b m s
mapAccumC f =
loop
where
loop s = await >>= maybe (return s) go
loop !s = await >>= maybe (return s) go
where
go a = case f a s of
(s', b) -> yield b >> loop s'
Expand All @@ -559,7 +560,7 @@ mapAccumM, mapAccumMC :: Monad m => (a -> s -> m (s, b)) -> s -> ConduitM a b m
mapAccumMC f =
loop
where
loop s = await >>= maybe (return s) go
loop !s = await >>= maybe (return s) go
where
go a = do (s', b) <- lift $ f a s
yield b
Expand All @@ -583,7 +584,7 @@ INLINE_RULE(scan, f, mapAccum (\a b -> let r = f a b in (r, r)))
scanM :: Monad m => (a -> b -> m b) -> b -> ConduitM a b m b
INLINE_RULE(scanM, f, mapAccumM (\a b -> f a b >>= \r -> return (r, r)))

-- | 'concatMapM' with an accumulator.
-- | 'concatMapM' with a strict accumulator.
--
-- Subject to fusion
--
Expand Down

0 comments on commit de53a2f

Please sign in to comment.