2008/12/7 S. Günther <h8spawn@googlemail.com>
Hi,

I have a small problem with System.Random.randoms. I need a rather
large number of random numbers but the following program consumes a
huge amount of memory. I terminated it when it used up more than 2 Gb:

module Main where

import System.Random

n :: Int
n = maxBound

main = do
 g <- getStdGen
 print $ length $ take n $ ((randoms g)::[Int])

I think the problem is that the list spine is being forced, but not the elements, so the generator is becoming a rather massive thunk.  This is peculiar to your benchmark, and would probably not occur in practice when you are actually using the random numbers.

Try:

strictTake 0 _ = []
strictTake n [] = []
strictTake n (x:xs) = x `seq` (x : strictTake (n-1) xs)

And use that instead of take.

Again, this strictTake is probably not necessary in your actual application, it's just to fix your benchmark.

Luke




On the other hand using
 take n $ [1..]
it runs in constant space.
Am I doing something wrong? Or should I just abandon randoms and use
the more primitive functions in System.Random?

Thanks in advance
S. Günther

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe