[GHC] #16366: Strict version of `foldlM`.
GHC
ghc-devs at haskell.org
Tue Feb 26 10:44:15 UTC 2019
#16366: Strict version of `foldlM`.
-------------------------------------+-------------------------------------
Reporter: autotaker | Owner: (none)
Type: feature | Status: new
request |
Priority: normal | Milestone:
Component: | Version: 8.6.3
libraries/base |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: None/Unknown
Unknown/Multiple |
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
`Data.Foldable.foldlM` is lazy on the accumulation parameter.
A user can define
{{{foldlM (\acc x -> acc `seq` step acc x) z xs}}},
but actually this function is NOT strict! It is simplified to the
following core:
{{{#!hs
foldlM (\acc x -> acc `seq` step acc x) z xs
==
go xs z where
go [] acc = pure acc
go (x:xs) acc = (acc `seq` step acc x) >>= go xs
}}}
DemandAnalysis infers that `go` is lazy on the second argument
because `pure` is lazy in general (e.g. `IO` Monad).
Thus `foldlM'` is needed.
Its definition would be:
{{{#!hs
foldlM' :: (Monad m, Foldable t) => (b -> a -> m b) -> b -> t a -> m b
foldlM' f z0 xs = foldr c (\x -> x `seq` pure x) xs z0
where c x k = \z -> z `seq` (f z x >>= k)
{-# INLINE c #-}
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/16366>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list