mapM/concatMapMy
Sengan Baring-Gould
senganb@ia.nsc.com
Wed, 18 Oct 2000 22:34:01 -0600 (MDT)
> > senganb@ia.nsc.com (Sengan Baring-Gould) wrote:
> >
> > > mapM seems to be a memory hog (and thus also concatMapM).
> > > In the following eg:
> > >
> > > > main = mapM print ([1..102400] :: [Integer])
> > >
> > > memory usage climbs to 1.6M with ghc and needs -K20M
> >
> > As a guess: since 'mapM print ([1..102400] :: [Integer])'
> > has type 'IO [()]', perhaps the result of the IO operation --
> > a list of 100K empty tuples -- is the culprit, even though
> > the result is never used.
> >
> > Does 'mapM_ print ... ' (:: IO ()) perform any better?
>
> Yes, but in the following eg
>
> > main = print $ sum x
> > x = _scc_ "x" [1..102400] :: [Integer]
>
> x takes 1M allocations, and I would think that () would be smaller than
> an Integer. Therefore I'm not sure that is the reason. The sum is there to
> force the evaluation.
Assuming you are right, why do I see the same 1.6M profile with:
> main = mapM2 (_scc_ "p" (\x -> print x)) ([1..102400] :: [Integer]) >> return ()
> mapM2 :: Monad m => (a -> m b) -> [a] -> m [b]
> mapM2 f [] = return []
> mapM2 f (c:cs) = _scc_ "a" (>>=) (_scc_ "d" f c) (\x ->
> _scc_ "b" (>>=) (_scc_ "e" mapM2 f cs) (\xs ->
> _scc_ "f" return (x:xs)))
Is >>= not lazy?
Sengan