[Haskell-cafe] Space leak with replicateM

Alexander Eyers-Taylor aeyerstaylor11 at gmail.com
Tue Jun 16 12:34:22 UTC 2015


Hello

Looking at the generated core numbers is shared in both cases. This is 
very small list and hence shouldn't
create the memory problems.

The problem comes from floating out.

The test1 expands to roughly the following (in imperative pseudo code)

sequence [nums,nums,nums,nums]=
   xs := sequence [nums,n]
   for (a in nums)
     for (rest in xs)
       yield (a:rest)

while test2 expands becomes

for (a in nums)
   for (b in nums)
     for (c in nums)
       for (d in nums)
         yield [a,b,c,d]

In the first case xs is shared between all elements in nums.

If we write out explicit definitions of replicateM specialised to lists  
we see

replicateM' 0 xs = return []
replicateM' n xs = do
   a <- xs
   b <- replicateM' (n-1) xs
   return (a:b)

which is optimised to be


replicateM' 0 xs = return []
replicateM' n xs =
let recCase = replicateM' (n-1) xs
    in do a <- xs
          b <- recCase
          return (a:b)

wheras we can write


replicateM'' 0 xs = return []
replicateM'' n xs = do
   b <- replicateM' (n-1) xs
   a <- xs
   return (b ++ [a])

The second version has no space leak. However when n is large it is 
inefficient due
to ++ but this can probably be avoided. The reason why this causes a 
space leak
is due to ghc floating the recursive case out of the lambda which is 
then shared between
the iterations. This avoid some computation but then causes a space leak.

test2 itself optimises really well and causes fusion resulting in the tight
structure

Alex

On 16/06/15 10:09, Joachim Breitner wrote:
> Hi,
>
> Am Dienstag, den 16.06.2015, 03:37 -0400 schrieb Ken Takusagawa II:
>> In the following program, the function "test1" results in huge memory
>> usage, but substituting "test2", which does essentially the same
>> thing, does not.  GHC 7.10.1, AMD64.  Is there a different
>> implementation of replicateM that avoids the space leak?
>>
>> module Main where {
>> import Control.Monad;
>>
>> numbers :: [Int];
>> numbers=[1..200];
>>
>> -- has a space leak
>> test1 :: [[Int]];
>> test1 = replicateM 4 numbers;
>>
>> -- no space leak
>> test2 :: [[Int]];
>> test2 = do {
>> x1 <- numbers;
>> x2 <- numbers;
>> x3 <- numbers;
>> x4 <- numbers;
>> return [x1,x2,x3,x4];
>> };
>>
>> main :: IO();
>> main = print $ length $ test1;
>>
>> }
>>
> Could be the state hack causing `numbers` to inline, see
> http://stackoverflow.com/questions/29404065/why-does-this-haskell-code-run-slower-with-o/30603291#30603291
> and
> https://ghc.haskell.org/trac/ghc/ticket/9349
>
> Greetings,
> Joachim
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe



More information about the Haskell-Cafe mailing list