
Hello, in reformulation of a code with no space leak, the leak reappeares. It takes near constant space to get at the n-th elt in the produced list here (http://ideone.com/fiifl): {-# OPTIONS_GHC -O2 -fno-cse #-} primes = 2 : ([3,5..] `minus` foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x<- ys]) where ys = 3 : ([5,7..] `minus` foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x<- ys]) foldi f (x:xs) = f x (foldi f (pairs f xs)) pairs f (x:y:t) = f x y : pairs f t Here it doesn't (http://ideone.com/m744a): {-# OPTIONS_GHC -O2 -fno-cse #-} primes = 2 : g (fix g) where g = (3:) . ([5,7..] `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) I expected the 2nd to be equivalent to the 1st. In Hugs (Nov 2002) the reported stats and run times are very similar for the both versions. Is this a GHC thing, or a language thing? Thanks,

Hi Will,
in reformulation of a code with no space leak, the leak reappeares.
It takes near constant space to get at the n-th elt in the produced list here (http://ideone.com/fiifl):
{-# OPTIONS_GHC -O2 -fno-cse #-} primes = 2 : ([3,5..] `minus` foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x<- ys]) where ys = 3 : ([5,7..] `minus` foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x<- ys]) foldi f (x:xs) = f x (foldi f (pairs f xs)) pairs f (x:y:t) = f x y : pairs f t
Here it doesn't (http://ideone.com/m744a):
{-# OPTIONS_GHC -O2 -fno-cse #-} primes = 2 : g (fix g) where g = (3:) . ([5,7..] `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..])
This is entirely expected. What is gobbling up the memory is the shared [5,7..] list that some invocation of g consume while others hang onto the head of the same list. (Note that g is a constant.) If you change the code to make g pointful, and compile with -fno-full-laziness, then the memory usage will go down again. {-# OPTIONS_GHC -O2 -fno-full-laziness #-} primes :: [Int] primes = 2 : g (fix g) where g xs = (3:) . ([5,7..] `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) $ xs With -ffull-laziness, ghc will notice that [5,7..] does not depend on xs, and float it out to the surrounding scope, essentially turning the code into {-# OPTIONS_GHC -O2 #-} primes :: [Int] primes = 2 : g (fix g) where g xs = (3:) . (odds `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) $ xs odds = [5,7..] and the [5,7..] list will be shared once more. Using -fno-cse has no effect in this example, because there are no duplicate subexpressions in the code. It is still a good idea to try this option when one encounters odd space leaks. Bertram

Bertram Felgenhauer
Hi Will,
in reformulation of a code with no space leak, the leak reappeares.
This is entirely expected. What is gobbling up the memory is the shared [5,7..] list that some invocation of g consume while others hang onto the head of the same list. (Note that g is a constant.) If you change the code to make g pointful, and compile with -fno-full-laziness, then the memory usage will go down again.
{-# OPTIONS_GHC -O2 -fno-full-laziness #-} primes :: [Int] primes = 2 : g (fix g) where g xs = (3:) . ([5,7..] `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) $ xs
With -ffull-laziness, ghc will notice that [5,7..] does not depend on xs, and float it out to the surrounding scope, essentially turning the code into
{-# OPTIONS_GHC -O2 #-} primes :: [Int] primes = 2 : g (fix g) where g xs = (3:) . (odds `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) $ xs odds = [5,7..]
and the [5,7..] list will be shared once more.
Using -fno-cse has no effect in this example, because there are no duplicate subexpressions in the code. It is still a good idea to try this option when one encounters odd space leaks.
Bertram
Hi Bertram,
thanks so much for your help!
I could only get rid of the leak, with your advice, using the switch
-fno-full-laziness, with pointful "g" code, and this (correction at the bottom!):
([5,7..] `minus`),
or this
(odds () `minus`),
where odds () = [5,7..]
(notice the (), without it there's a huge leak), or with this
(gaps 5)
where
gaps k s@(x:xs) =
if k

Will Ness
Bertram Felgenhauer
writes: Hi Will,
in reformulation of a code with no space leak, the leak reappeares.
This is entirely expected. (.....)
{-# OPTIONS_GHC -O2 #-} primes :: [Int] primes = 2 : g (fix g) where g xs = (3:) . (odds `minus`) . foldi (\(x:xs) -> (x:) . union xs) . map (\x-> [x*x, x*x+2*x..]) $ xs odds = [5,7..]
CORRECTION: just with "gaps" (but not the other ones), changing the "g" function from composed pieces into a "normal" code, it did it! (probably some ghc version-specific stuff at play): g xs = 3 : gaps 5 ( foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x <- xs] ) addition: with gaps k xs = minus [k,k+2..] xs it also runs without the space leak, but with gaps k = minus [k,k+2..] the leak reappears. (?)

Hi Will, Will Ness wrote:
Will Ness
writes: CORRECTION: just with "gaps" (but not the other ones), changing the "g" function from composed pieces into a "normal" code, it did it! (probably some ghc version-specific stuff at play):
g xs = 3 : gaps 5 ( foldi (\(x:xs) -> (x:) . union xs) [[x*x, x*x+2*x..] | x <- xs] )
addition: with gaps k xs = minus [k,k+2..] xs it also runs without the space leak, but with gaps k = minus [k,k+2..] the leak reappears.
I'm not sure that I tried the same code as you did, but for me both these versions were leaky. I cannot explain why, but I see that in the resulting core (ghc ... -ddump-simpl) the [5,7..] list ends up as a top level constant, despite -fno-full-laziness. So the cause of the space leak remains the same -- the [5,7..] list is being shared among several invocations of g. Tricky. Bertram

Bertram Felgenhauer
Hi Will,
Will Ness wrote:
addition: with gaps k xs = minus [k,k+2..] xs it also runs without the space leak, but with gaps k = minus [k,k+2..] the leak reappears.
I'm not sure that I tried the same code as you did, but for me both these versions were leaky. I cannot explain why, but I see that in the resulting core (ghc ... -ddump-simpl) the [5,7..] list ends up as a top level constant, despite -fno-full-laziness. So the cause of the space leak remains the same -- the [5,7..] list is being shared among several invocations of g. Tricky.
Bertram
Hi, I've ended up with primes = 2 : g (fix g) where g xs = 3 : gaps 5 (unionAll [[x*x, x*x+2*x..] | x <- xs]) Here's the test entry: https://ideone.com/qpnqe The both "gaps" leak (25MB for 500k run) if "fix" is made internal function and there's no -fno-cse switch. But with the switch, one stops leaking, and the other goes to 120MB. Tricky, one could say, is an understatement. :) I wish (avoidable) space leaks could/would be considered a "bug" and compiler would find ways to avoid it, all by itself (or with a super-switch, "-fno- leaks" say). Then we'd needn't worry about such things, and could just write such "mythical one-liners" with confidence. :) Cheers, and thanks a lot, Will
participants (2)
-
Bertram Felgenhauer
-
Will Ness