
On Sunday 15 May 2011 18:49:26, Felipe Almeida Lessa wrote:
On Sun, May 15, 2011 at 11:39 AM, Manfred Lotz
wrote: I also tried something similar, and indeed you are right. mapM_ in conjunction with toList is better in terms of memory and runtime (mainly because GC is less busy) than using functions from Traversable.
If you want just the side effects you shouldn't be using Traversable, but Foldable. In particular [1],
mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
Doing the same test as Daniel Fischer's, but with an additional definition
import qualified Data.Foldable as F
perFoldable :: (Ord k, Show v) => Map k v -> IO () perFoldable = F.mapM_ print
which is also the shortest definition, I get the following results:
viaList: 208 MiB total memory, 2.24s MUT time, 1.11s GC time, 3.35s total time viaElems: 208 MiB total memory, 1.40s MUT time, 1.13s GC time, 2.53s total time perTraverse: 322 MiB total memory, 1.77s MUT time, 2.84s GC time, 4.61s total time perFoldable: 215 MiB total memory, 1.53s MUT time, 1.73s GC time, 3.26s total time
I get MUT time 1.63s ( 1.63s elapsed) GC time 1.49s ( 1.49s elapsed) for that, presumably because a) your computer is faster than mine and b) my pointers are half as large as yours, so I need fewer GCs. Probably all GC times could be reduced significantly by supplying a suitable -A (with -A64M, I get 1.76 MUT, 1.03 GC). But, Data.Foldable.mapM_ is defined in terms of Data.Foldable.foldr, while Data.Map only directly defines foldMap. The default definition of Data.Foldable.foldr is defined in terms of foldMap, but of course needs some plumbing. We can eliminate that plumbing to make it a bit more memory- friendly and faster (warning: evil special-purpose code ahead): {-# LANGUAGE FlexibleInstances #-} import Data.Monoid import qualified Data.Foldable as F -- This is the evil part: instance Monoid (IO ()) where mempty = return () mappend = (>>) mconcat = sequence_ perFoldMap :: (Ord k, Show v) => Map k v -> IO () perFoldMap = F.foldMap print That clocks in at MUT time 1.57s ( 1.57s elapsed) GC time 1.24s ( 1.24s elapsed) and is clear second (1.68 + 0.80 with -A64M). So, simply getting the list of elems an printing those out is still the fastest (and note that it's trivial to print keys and values by converting the Map to a list, while doing that with Data.Traversable and Data.Foldable requires some contortions). Moral: simple is good.
Cheers,
[1] http://hackage.haskell.org/packages/archive/base/4.3.1.0/doc/html/Data- Foldable.html#v:mapM_