[Haskell-cafe] mapM vs mapM_ performance

Ben midfield at gmail.com
Tue Apr 22 13:32:12 EDT 2008


Hello Haskellers,

I'm running ghc 6.8.2 on vista 64.  Consider the following program,
which is compiled with -02 -prof -auto-all:

module Main where

import System.IO (openFile, IOMode(..), hPutStr)

testlst = let ls = [(i, [(j, (fromIntegral j)::Float) | j <-
[1..5]::[Int]]) | i <- [1..500000]::[Int]]
          in ls

main2 = do
  h <- openFile "bardump" WriteMode
  mapM_ ((hPutStr h) . show) testlst


main = do
  h <- openFile "bardump2" WriteMode
  mapM ((hPutStr h) . show) testlst
  return ()

main and main2 are different in only that mapM_ versus mapM_ are used.
 But the mapM version runs about 20x slower!  I'm running with +RTS -p
-hc -RTS and I see that the amount of memory allocated is about the
same, and I think the resident memory is about the same too.  But the
mapM_ version runs in about 8.7 seconds, and the mapM version takes
167 seconds.

You may ask, why use mapM if you're discarding the values?
Unfortunately in my real app I need the values, which are more
interesting than IO ().

?

Take care, Ben


More information about the Haskell-Cafe mailing list