
On the test case i'm running the performance impacts of reversing the
return list are negligible:
mapM3 :: Monad m => (a -> m b) -> [a] -> m [b]
{-# INLINE mapM3 #-}
mapM3 fn lst = mapM3accum fn lst []
where mapM3accum _ [] accum = return $ reverse accum
mapM3accum fn (x:xs) accum = do
r <- fn x
mapM3accum fn xs (r:accum)
main5 = do
print $ length $ mapM_ (flip replicate ()) [1..11]
time ~ 18 seconds (about the same, faster on my machine probably due
to timing artifacts) and the memory was about the same (strangely less
than the non-reversing one though again that's probably an artifact.)
In any case, I have some questions:
1) Why is the Prelude mapM so slow? It seems like running 10x slower
than mapM_ when generating only 50,000 return values is a problem.
2) Is there a reason to not use mapM3 above?
Thanks and take care, Ben
On Thu, Apr 24, 2008 at 2:33 PM, Bulat Ziganshin
Hello Niklas,
Friday, April 25, 2008, 1:25:39 AM, you wrote:
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. :-)
unfortunately, this affects performance too. reverse costs one more scan through the list and building lot of thunks has its own space and time cost
-- Best regards, Bulat mailto:Bulat.Ziganshin@gmail.com