Re: [Haskell] space behaviour of lazy recursive lists

2005-02-03 Thread Colin Runciman
Axel,
...
However, they do not directly solve my problem in the bigger program which
still has the same linearly growing memory requirement. The problem seems to be
very, very hard to find. I suspect it is related to lazyness as in the gibs
example, but I just cannot put my finger on the code that needs to be
changed. Is there any good method to track down this kind of problem? (I
tried all the ghc memory profiling techniques, that seemed promising to
me.)
 

If your program is in Haskell 98, not using any of the Glasgow 
extensions, you could also try compiling it for memory profiling under 
nhc.  The nhc heap profiler has some options not available in ghc.  Most 
but not all space problems due to laziness have similar effects across 
different implementations.

Colin R
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-02-03 Thread Axel Jantsch

Hi,

Both variants of the strict zipWith solved the gibs problem I posed:

   gibs = 1 : 1 : f gibs (tail gibs)
  where f (x:xs) (y:ys) = z `seq` z : f xs ys
   where z = min (x + y) 10
   by Simon MArlow

and 

   zipWith' f (x:xs) (y:ys) = let z = f x y
  in z `seq` (z : zipWith' f xs ys)
   zipWith' _ _  _  = []
   by Adrian Hey

However, they do not directly solve my problem in the bigger program which
still has the same linearly growing memory requirement. The problem seems to be
very, very hard to find. I suspect it is related to lazyness as in the gibs
example, but I just cannot put my finger on the code that needs to be
changed. Is there any good method to track down this kind of problem? (I
tried all the ghc memory profiling techniques, that seemed promising to
me.)

Thanks to all that responded to my question!
--Axel

Axel Jantsch writes:
 > 
 > Hi,
 > 
 > How can I get constant space behaviour for lazy, recursive streams?
 > 
 > Consider:
 > 
>> gibs = 1 : 1 : (zipWith f gibs (tail gibs))
>> where f x y = min (x + y) 10
 > 
 > This is derived from the fibs text book example, modified to bound the
 > memory requirement for each list element.
 > 
 > Evaluating gibs should require constant amount of memory, since the
 > computed parts of the list are not needed any more and can be reclaimed.
 > 
 > However, hugs says:
 > 
Main> nth 100 fibs
 >   10
 >   (2818 reductions, 3730 cells, 1 garbage collection)
 > 
Main> nth 200 fibs
 >   10
 >   (5618 reductions, 7430 cells, 1 garbage collection)
 > 
 > which suggests linear space behaviour. Also, ghc shows the same behaviour
 > with a linearly growing stack size as shown by the profiler (+RTS -hc -xt)
 > and sooner or later the program runs out of memory with a stack overflow. 
 > 
 > It seems the entire list up to the last evaluated element is stored. Since
 > I want to use lazy streams to simulate process networks, I want to run the
 > simulation arbitrarily long without *ever* running out of memory. 
 > 
 > So my question is, how can I process recursive, lazy streams in constant
 > space? 
 > 
 > Or, in other words, how can I force the garbage collector to reclaim the
 > memory of the head of the list after I have processed it, since I will
 > never ever reference it again?
 > 
 > With best regards
 > Axel Jantsch
 > 
 > 
 > ---
 > Phone: +46 8 790 4124, Email: [EMAIL PROTECTED], Web: www.imit.kth.se/~axel
 > ___
 > Haskell mailing list
 > Haskell@haskell.org
 > http://www.haskell.org/mailman/listinfo/haskell
 > 
 > 

---
Phone: +46 8 790 4124, Email: [EMAIL PROTECTED], Web: www.imit.kth.se/~axel
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] space behaviour of lazy recursive lists

2005-02-01 Thread Simon Marlow
On 30 January 2005 17:09, Ben Rudiak-Gould wrote:

> Axel Jantsch wrote:
> 
>  >Consider:
>  >
>  >>gibs = 1 : 1 : (zipWith f gibs (tail gibs))
>  >>   where f x y = min (x + y) 10
>  >
>  >[...] how can I force the garbage collector to reclaim the
>  >memory of the head of the list after I have processed it, since I
>  will >never ever reference it again?
> 
> There's no entirely satisfactory way to do this. The language standard
> doesn't specify caching behavior, so you have to rely on the way that
> actual implementations handle caching.
> 
> I think it's safe in practice to assume that a binding inside a
> function won't be cached across call boundaries, even if the value of
> the binding doesn't depend on the function argument. I.e. you should
> be able to solve your problem with
> 
> makeGibs () = gibs where
>   gibs = 1 : 1 : (zipWith f gibs (tail gibs))
>   f x y = min (x + y) 10
> 
> In principle a compiler could float the definition of gibs outside the
> function makeGibs and cache it across calls, but I don't think any
> compiler will actually do this, precisely because it makes this trick
> stop working.

Actually, GHC can garbage collect top-level definitions, and it also
floats things out to the top-level precisely because doing so doesn't
affect the space behaviour (any more than floating in general, that is).

Unfortunately in this case, laziness is the culprit.  Each element of
the list is a thunk that refers to the previous two elements of the
list, which are thunks that refer to the previous two elements... and so
on.  So even if you drop the front of the list, each element keeps the
whole list alive until it is evaluated.

Try this:

gibs = 1 : 1 : f gibs (tail gibs)
   where f (x:xs) (y:ys) = z `seq` z : f xs ys
where z = min (x + y) 10

main = print (head (drop 100 gibs))

Cheers,
Simon
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread Adrian Hey
On Sunday 30 Jan 2005 4:00 pm, Axel Jantsch wrote:
> Main> nth 100 fibs
>   10
>   (2818 reductions, 3730 cells, 1 garbage collection)
>
> Main> nth 200 fibs
>   10
>   (5618 reductions, 7430 cells, 1 garbage collection)
>
> which suggests linear space behaviour.

Hmm, not sure exactly what Hugs is measuring here.
I suspect this is a measure of total allocation during
program execution rather than maximimum memory in use
at any time during execution. So you'd expect to see
this kind of thing anyway.

As it happens, I think both heap and stack requirement
will be proportional to the first arg of nth for the
reasons I indicated earlier. But I think the version
using zipWith' will execute in constant space (but this
doesn't mean constant cell allocation, you'll probably
still see  of cells used).

Regards
--
Adrian Hey

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread Adrian Hey
On Sunday 30 Jan 2005 7:40 pm, Adrian Hey wrote:
> On Sunday 30 Jan 2005 4:00 pm, Axel Jantsch wrote:
> > Hi,
> >
> > How can I get constant space behaviour for lazy, recursive streams?
> >
> > Consider:
> > > gibs = 1 : 1 : (zipWith f gibs (tail gibs))
> > >where f x y = min (x + y) 10
> >
> > This is derived from the fibs text book example, modified to bound the
> > memory requirement for each list element.
> >
> > Evaluating gibs should require constant amount of memory, since the
> > computed parts of the list are not needed any more and can be reclaimed.
> >
> > However, hugs says:
> >
> > Main> nth 100 fibs
> >   10
> >   (2818 reductions, 3730 cells, 1 garbage collection)
>
> I think maybe you need a strict version of zipWith, otherwise
> even if gibs itself is garbage collected as expected you will
> still get 98 lazy applications of f (thunks) before the actual
> value of f is demanded.
---^

Erm, that should be the value of the nth element of course.

Regards
--
Adrian Hey
 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread Adrian Hey
On Sunday 30 Jan 2005 4:00 pm, Axel Jantsch wrote:
> Hi,
>
> How can I get constant space behaviour for lazy, recursive streams?
>
> Consider:
> > gibs = 1 : 1 : (zipWith f gibs (tail gibs))
> >where f x y = min (x + y) 10
>
> This is derived from the fibs text book example, modified to bound the
> memory requirement for each list element.
>
> Evaluating gibs should require constant amount of memory, since the
> computed parts of the list are not needed any more and can be reclaimed.
>
> However, hugs says:
>
> Main> nth 100 fibs
>   10
>   (2818 reductions, 3730 cells, 1 garbage collection)

I think maybe you need a strict version of zipWith, otherwise
even if gibs itself is garbage collected as expected you will
still get 98 lazy applications of f (thunks) before the actual
value of f is demanded. When it is eventually demanded you'll
get a lot of stack use (and maybe an overflow in some situations)
because f is strict in it's arguments. Maybe something like this
would fix the problem..

zipWith' f (x:xs) (y:ys) = let z = f x y
   in z `seq` (z : zipWith' f xs ys)
zipWith' _ _  _  = []

(Haven't tried it though). Actually this kind of problem worries
the me a lot. Dunno if I'm being unduly anal, but I usually end
up writing strict and lazy versions of most of my HOFs to deal
with this kind of problem, but this isn't a terribly satifactory
solution IMO.

Regards
--
Adrian Hey



 
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread karczma
Ben Rudiak-Gould writes: 

Axel Jantsch wrote:

>>gibs = 1 : 1 : (zipWith f gibs (tail gibs))
>>   where f x y = min (x + y) 10
>
>[...] how can I force the garbage collector to reclaim the
>memory of the head of the list after I have processed it, since I will
>never ever reference it again? 

There's no entirely satisfactory way to do this. The language standard 
doesn't specify caching behavior, so you have to rely on the way that 
actual implementations handle caching. 

I think it's safe in practice to assume that a binding inside a function 
won't be cached across call boundaries, even if the value of the binding 
doesn't depend on the function argument. I.e. you should be able to solve 
your problem with 

   makeGibs () = gibs where
 gibs = 1 : 1 : (zipWith f gibs (tail gibs))
 f x y = min (x + y) 10 

In principle a compiler could float the definition of gibs outside the 
function makeGibs and cache it across calls, but I don't think any 
compiler will actually do this, precisely because it makes this trick stop 
working. 

A more elegant variation which definitely won't be cached is 

   gibsFrom a b = gibs where
 gibs = a : b : (zipWith f gibs (tail gibs))
 f x y = min (x + y) 10
In both cases Hugs seems to consume the memory at the same rate as the
original program. 

Jerzy Karczmarczuk 

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] space behaviour of lazy recursive lists

2005-01-30 Thread Ben Rudiak-Gould
Axel Jantsch wrote:
>Consider:
>
>>gibs = 1 : 1 : (zipWith f gibs (tail gibs))
>>   where f x y = min (x + y) 10
>
>[...] how can I force the garbage collector to reclaim the
>memory of the head of the list after I have processed it, since I will
>never ever reference it again?
There's no entirely satisfactory way to do this. The language standard 
doesn't specify caching behavior, so you have to rely on the way that 
actual implementations handle caching.

I think it's safe in practice to assume that a binding inside a function 
won't be cached across call boundaries, even if the value of the binding 
doesn't depend on the function argument. I.e. you should be able to 
solve your problem with

   makeGibs () = gibs where
 gibs = 1 : 1 : (zipWith f gibs (tail gibs))
 f x y = min (x + y) 10
In principle a compiler could float the definition of gibs outside the 
function makeGibs and cache it across calls, but I don't think any 
compiler will actually do this, precisely because it makes this trick 
stop working.

A more elegant variation which definitely won't be cached is
   gibsFrom a b = gibs where
 gibs = a : b : (zipWith f gibs (tail gibs))
 f x y = min (x + y) 10
-- Ben
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell