[Haskell-cafe] Re: Difficult memory leak in array processing

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Mon Nov 27 14:45:10 EST 2006


> nor that I would really understand the code you've posted. On the positive
> side of things, you've given me a lot to think about. Maybe in the
> fullness of time I shall return and say 'Lo! I can write leakless
> Haskell code!'. But alas, that time seems so distant now.

I tried to show how the code can be rewritten in a more declarative
manner by the use of the higher order function (accumM) which is akin to
the accumulation function (Data.Array.accum) for immutable arrays. This
removes the need for traversing the array by hand with (worker). As
Claus Reinke already pointed out, the accumulating parameter (acc) in
your full example has to be evaluated strictly or it will overflow the
stack. This is the same situation as in the famous example

   length' []     n = n
   length' (_:xs) n = length' xs (n+1)

By avoiding (worker) and using higher order functions, you can avoid
this kind of accumulating parameters altogether:

   length xs        = foldr (+1) 0 xs

Besides, writing things explicitly tail recursive does not help much in
Haskell.


In the following, I'm going to explain the restructured code posted.

First of all, reducing the amount of IOs is always good for code sanity.
Formulated with an emotional undertone, IO is "evil". Why do you need
IO? There are two reasons: the mutable array and the random numbers.
Random numbers clearly are a side-effect, but there is a wonderful
trick: you simply fetch a lazy infinite list of random numbers and work
with that. With System.Random, you can say

    do
        -- get the default pseudo-random number generator,
        -- it already has good random seed
        gen <- getStgGen
        let
            rs     = randomsRs (2,12) gen
            result = dostuffwith rs
        return result

(rs) is an infinite list of random numbers and (dostuffwith) is a pure
function, no IO involved. In our case,

    twodice (x:x':xs)   = (x+x') `div` 2 : twodice xs
    noise rng gen       = twodice $ randomRs rng gen

is a combination of (rs) and (dostuff). (noise) simply supplies an
infinite list of random numbers to (twodice). (twodice) processes this
list by taking pairs and averaging them. Both cover the functionality of
your (tpdf) offers.


Concerning mutable arrays,
> I can say neither that I have any idea what an 'undead array' is
"UndeadArray" is a bowdlerization of "Unboxed Array" which is the type
you're using as Buffer. They generally are to be considered "evil" as
well, hence the renaming. Their only use is to store huge amounts of
memory like their most prominent example (ByteString). If you want to
add noise to an actual audio channel, then they can be adequate. But if
you only want statistics about random numbers, they're completely out of
place. In that case,

    countNumber k xs = length $ filter (k==) xs
    main = do
        gen <- getStdGen
        return $ countNumber 7 (noise (2,12) gen)

will do everything you need.


If mutable arrays are really unavoidable (hence this is only for
"necromancers"), the use of higher order functions is mandatory. One
useful higher order function is (accum) from Data.Array. The adaption to
the mutable case uses the helper function

    modifyArray arr i f =
        readArray arr i >>= \y -> writeArray arr i (f y)

which applies f to the array element at position i.

    accumM f arr xs = mapM_ chg xs
        where chg (i,x) = modifyArray arr i (flip f x)

"takes an array and an association list and accumulates pairs from the
list into the array with the accumulating function f" (documentation
from Data.Array.accum). For example if

    arr[0] == 0, arr[1] == 1, arr[2] == 2, arr[3] == 3

then

    brr = accum (+) arr [(1,2),(1,3),(2,3)]

yields

    brr[0] == 0, brr[1] == 6, brr[2] == 5, brr[3] == 3

As another example, (accum (curry snd) arr xs) replaces the array
entries by those listed in xs.

Finally, countNumber can be expressed as a fold over the array. In
general, every higher order function for lists can be translated to one
for arrays.


> However, this necromancy business really does sound like an exiting new
> career prospect. Interesting job opportunities, respect of the
> community, flexible hours and extremely loyal peers and other
> commandlings that will literally work for just for the Brain Food.
> 
> Regards,
> Nik The Blak, Necromancer of the Glorious Forces of Evil

This is indeed very tempting :) Though I suspect that the glory of
forces built on (IO a) will be very limited.


Regards,
apfelmus, Golden Delicious of the Shining Bulbs of Light



More information about the Haskell-Cafe mailing list