[Haskell-cafe] Difficult memory leak in array processing
Niko Korhonen
niko.korhonen at gmail.com
Mon Nov 27 07:40:14 EST 2006
Ian Lynagh wrote:
> I'm also unable to reproduce this. Can you tell us exactly what
> commandline you are using to compile and run the program please?
In fact it turned out that the example code I posted did not exhibit the
memory leak at all. It just took a /very long time/ to complete
(compared to a Java version), but it did complete. My complete code,
which also counted the instances of a given number from the array, does
however exhibit the leak. It is here:
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
countNumbers :: Buffer -> Int -> IO Int
countNumbers buf x =
let worker lo i acc
| i >= lo = do
n <- readArray buf i
if n == x
then worker lo (i - 1) (acc + 1)
else worker lo (i - 1) acc
| otherwise = return acc
in do
(lo, hi) <- getBounds buf
worker lo hi 0
main = do
buf <- newArray_ (0, 10000000) :: IO Buffer
genSeries buf tpdf (2, 12)
sevens <- countNumbers buf 7
putStrLn ("Magic number sevens: " ++ show sevens)
return 0
More information about the Haskell-Cafe
mailing list