a faster,
accumulating mapM (was Re: [Haskell-cafe] mapM vs mapM_ performance)
Niklas Broberg
niklas.broberg at gmail.com
Thu Apr 24 17:25:39 EDT 2008
Hi Ben,
> mapM2 :: Monad m => (a -> m b) -> [a] -> m [b]
> {-# INLINE mapM2 #-}
> mapM2 fn lst = mapM2accum fn lst []
> where mapM2accum _ [] accum = return accum
> mapM2accum fn (x:xs) accum = do
> r <- fn x
> mapM2accum fn xs (r:accum)
Not that it should matter for performance any, but you really ought to
reverse the result list too, or compute the accumulator in the right
order. :-)
mapM2 :: Monad m => (a -> m b) -> [a] -> m [b]
{-# INLINE mapM2 #-}
mapM2 fn lst = mapM2accum fn lst id
where mapM2accum _ [] accum = return $ accum []
mapM2accum fn (x:xs) accum = do
r <- fn x
mapM2accum fn xs (accum . (r:))
Cheers,
/Niklas
More information about the Haskell-Cafe
mailing list