[Haskell-cafe] High memory consumption of "print"

Peter Robinson thaldyron at gmail.com
Tue Sep 8 05:57:10 EDT 2009


The following toy program consumes either 25MB or 70MB, depending on
whether the line
print "done"
is a comment or code. (Using only 1 OS thread increases memory consumption
to 130MB when the print is active vs 25MB when inactive.)

What am I doing wrong?

---------------------

module Main
where
import Control.Concurrent
import Control.Concurrent.STM
import Control.Concurrent.STM.TChan
import System.Environment
import Control.Applicative


main = do
  n <- read . head <$> getArgs
  tvar  <- newTVarIO 0
  tchan <- newTChanIO
  tids <- sequence [ forkIO (test tchan tvar i) | i <- [1..10^n] ]
  waitForAll tchan $! length tids
    where
      waitForAll _     0   = return ()
      waitForAll tchan len = do
        atomically $ readTChan tchan
        waitForAll tchan (len-1)


test :: TChan () -> TVar Int -> Int -> IO ()
test tchan tvar i = do
  atomically $ do
    val <- readTVar tvar
    if val+1 == i
      then do
        writeTVar tvar i
        writeTChan tchan ()
      else retry
  print "done"

---------------------
ghc --make -O2 teststm.hs -threaded && ./teststm 4 +RTS -sstderr


More information about the Haskell-Cafe mailing list