Why is there a space leak here?

Alastair David Reid reid@cs.utah.edu
05 Jun 2001 11:14:03 -0600


Executive summary: David's program has an incredibly subtle space leak
in it (or I'm being incredibly dumb).  I encourage the honchos (and
would be honchos) to have a look.  Users of other compilers might give
it a shot too.


David Bakin <davidbak@cablespeed.com> writes:

> Why is there a space leak in foo1 but not in foo2?  (I.e., in Hugs
> Nov '99) foo1 eats cells (and eventually runs out) where foo2
> doesn't.  That is, if I do (length (foo1 1000000)) I eventually run
> out of cells but (length (foo2 1000000)) runs fine (every GC returns
> basically the same amount of space).  Something must be wrong in
> flatten but it follows the pattern of many functions in the prelude
> (which I'm trying to learn from).  I have been puzzling over this
> for nearly a full day (getting this reduced version from my own code
> which wasn't working).  In general, how can I either a) analyze code
> looking for a space leak or b) experiment (e.g., using Hugs) to find
> a space leak?  Thanks!  -- Dave

Interesting question.  The functions certainly look as though either
both should leak or neither should leak.  As for how to chase this
sort of problem, I'll try to describe everything I do in trying to
chase the problem down in the hope that this might be instructive.

1) Is there really a problem?

   Using Feb 2001 Hugs, I run "hugs +g /tmp/leak.hs" and type 

     length (foo1 1000000)

   output is:

     {{Gc:235464}}{{Gc:227548}}{{Gc:219900}}{{Gc:212509}}{{Gc:205364}}{{Gc:198465}}{{Gc:191793}}{{Gc:185343}}{{Gc:179119}}{{Gc:173090}}{{Gc:167274}}{{Gc:161653}}{{Gc:156217}}{{Gc:150968}}{{Gc:145888}}{{Gc:140989}}{{Gc:136245}}{{Gc:131668}}{{Gc:127238}}{{Gc:122965}}{{Gc:118832}}{{Gc:114844}}{{Gc:110976}}{{Gc:107248}}{{Gc:103648}}{{Gc:100165}}{{Gc:96796}}{{Gc:93542}}{{Gc:90391}}{{Gc:87353}}{{Gc:84419}}{{Gc:81583}}{Interrupted!}

   Yup, it leaks.

   I then quit (just to be certain), restart and type:

     length (foo2 1000000)

   output is:

     {{Gc:239721}}{{Gc:239718}}{{Gc:239722}}{{Gc:239725}}{{Gc:239713}}{{Gc:239717}}{{Gc:239717}}{{Gc:239722}}{{Gc:239725}}{{Gc:239713}}{{Gc:239717}}{{Gc:239717}}{{Gc:239722}}{{Gc:239725}}{Interrupted!}

   Nope, it doesn't leak.

2) Could it be something to do with CAFs and the monmomorphism restriction?
   Check the type:

    Main> :t foo1
    foo1 :: Num a => Int -> [a]
    Main> :t foo2
    foo2 :: Num a => Int -> [a]
    
   Same type, almost certainly not.
   (The fact that all definitions are of the form "foo m = ..." makes it
   even less likely.  The fact that I tried this at all shows that I'm
   already grasping for straws.)

3) Could it be a bug in the garbage collector or code generator?

   1) Try swapping the two definitions and see if it still leaks.

      Yes, still leaks.

   2) Try adding a third definition in the hope that it will perturb
      code generation and heap allocation enough to make the problem show up.
      (This definition is based on "double x = [x,x]")
      
      Both foo1 (triple) and foo2 (double) leak, foo3 (single) still
      doesn't leak.

   3) Try a different compiler (ghc) and run with +RTS -Sstderr flags:

      foo1: leaks (6Mb maximum residency)
      foo2: leaks (5Mb maximum residency)
      foo3: doesn't leak (1,112 bytes maximum residency)

4) Maybe there's something funny in your definition of flatten - write
   my own.
    
    f1 :: [[a]] -> [a]
    f1 []       = []
    f1 ([]:xss) = f1 xss
    f1 ((x:xs):xss) = x : f1 (xs:xss)

   Nope, foo1 still leaks and foo3 doesn't leak.

5) Cut and paste code for map and take from language definition into
   this module in case Hugs (and GHC) are doing something funny.
   (The straws are getting smaller and further away.)

   No change.

   (Actually, I wrote the definitions from memory - effect should be
   the same.)

Well, I thought I understood lazy evaluation, garbage collectors, Hugs
and GHC but I'm at a complete loss for why one definition leaks and
the other doesn't.  I would be really fascinated to learn what is
going on here.

I'm attaching my revised version of David's program and David's
original version.

-- 
Alastair Reid        reid@cs.utah.edu        http://www.cs.utah.edu/~reid/

David's version:
----------------------------------------------------------------
-- This has a space leak, e.g., when reducing (length (foo1 1000000))
foo1 m 
  = take m v
    where
      v = 1 : flatten (map triple v)
      triple x = [x,x,x]

-- This has no space leak, e.g., when reducing (length (foo2 1000000))
foo2 m 
  = take m v
    where
      v = 1 : flatten (map single v)
      single x = [x]

-- flatten a list-of-lists
flatten :: [[a]] -> [a]
flatten []             = []
flatten ([]:xxs)       = flatten xxs
flatten ((x':xs'):xxs) = x' : flatten' xs' xxs
flatten' [] xxs        = flatten xxs
flatten' (x':xs') xxs  = x': flatten' xs' xxs
----------------------------------------------------------------



The Haggoidal version:

----------------------------------------------------------------
module Main( main ) where

import Prelude hiding ( take, map )

take :: Int -> [a] -> [a]
take 0 xs = []
take m [] = []
take m (x:xs) | m > 0 = x : take (m-1) xs

map :: (a -> b) -> ([a] -> [b])
map f []     = []
map f (x:xs) = f x : map f xs

main :: IO ()
main = do
  print (length (foo1 1000000))

-- This has a space leak, e.g., when reducing (length (foo1 1000000))
foo1 m 
  = take m v
    where
      v = 1 : f1 (map triple v)
      triple x = [x,x,x]

-- This has no space leak, e.g., when reducing (length (foo2 1000000))
foo2 m 
  = take m v
    where
      v = 1 : flatten (map double v)
      double x = [x,x]

-- This has no space leak, e.g., when reducing (length (foo3 1000000))
foo3 m 
  = take m v
    where
      v = 1 : f1 (map single v)
      single x = [x]

-- This has no space leak, e.g., when reducing (length (foo3 1000000))
foo4 m 
  = take m v
    where
      v = 1 : f1 (map single v)
      single x = [x,x,x]

-- flatten a list-of-lists
flatten :: [[a]] -> [a]
flatten []             = []
flatten ([]:xxs)       = flatten xxs
flatten ((x':xs'):xxs) = x' : flatten' xs' xxs

flatten' :: [a] -> [[a]] -> [a]
flatten' [] xxs        = flatten xxs
flatten' (x':xs') xxs  = x': flatten' xs' xxs

f1 :: [[a]] -> [a]
f1 []       = []
f1 ([]:xss) = f1 xss
f1 ((x:xs):xss) = x : f1 (xs:xss)
----------------------------------------------------------------