[Haskell-cafe] Difficult memory leak in array processing

Niko Korhonen niko.korhonen at gmail.com
Thu Nov 23 05:11:43 EST 2006


Hi everyone,

I have the following code whose purpose is to add dither (noise) to a given
array. The code looks very straightforward but apparently it has a memory
leak somewhere. Here I try to run the algorithm for an array of 10,000,000
integers. Ten million unboxed strict integers should equal to 40MB which
should pose no problems to any modern system. However, the program fails
with a stack overflow error. I'm using GHC 6.6 on Windows with 1 GB of RAM.

I've tried applying seq and some other strictness tricks (such as x == x)
pretty much everywhere on the code with no results. Could you please help me
understand what is going on here? Have I misunderstood something critical in
how Haskell works? Here is the relevant portion of the code:

module Main where

import Data.Array.IO
import System.Random

type Buffer = IOUArray Int Int

-- | Triangular Probability Density Function, equivalent to a roll of two
dice.
-- The number sums have different probabilities of surfacing.
tpdf :: (Int, Int) -> IO Int
tpdf (low, high) = do
    first <- getStdRandom (randomR (low, high))
    second <- getStdRandom (randomR (low, high))
    return ((first + second) `div` 2)

-- | Fills an array with dither generated by the specified function.
genSeries :: Buffer -> ((Int, Int) -> IO Int) -> (Int, Int) -> IO ()
genSeries buf denfun lims =
    let worker low i
            | i >= low = do
                r <- denfun lims
                writeArray buf i r
                worker low (i - 1)
            | otherwise = return ()
    in do
        (lo, hi) <- getBounds buf
        worker lo hi

main = do
    -- This should allocate a 40 MB array
    buf <- newArray_ (0, 10000000) :: IO Buffer
    -- Fill the array with dither
    genSeries buf tpdf (2, 12)

-- 
niko.korhonen at gmail.com
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20061123/6f2b20b7/attachment.htm


More information about the Haskell-Cafe mailing list