The problem is that the elements in the list [1..] are not used by
the function lens, so they will not be evaluated. This is fatal, since
the unevaluated elements are becoming larger and larger function applications:
[1..] = [1, 1+1, 1+1+1, ...]
For the same reasons, length [1..n] does not run in constant space.
By using a more strict definition of [1..], the space leak disappears:
> myFrom n = if n == n then t else t where t = n : myFrom (n+1)
> main = interact(("Enter stride: "++). unwords . map show .
> (flip lens)(myFrom 1) .
> fst . head . readDec)
Regards
/Magnus
Rex L. Page writes:
>
> length[1 .. n] seems to run in constant space (that is, space
> independent of n), as expected.
>
> However, length[1 ..] runs out of space.
> This doesn't seem reasonable to me.
>
> The following program, which computes length[1 ..]
> and reports its progress after every n-th element, also runs out of
> space, inexplicably to me.
>
> > lens n = everyNth n . scanl (\n _ -> n+1) 0
>
> > everyNth n = map head . takeWhile(not.null) . iterate(drop n)
>
> > main = interact(("Enter stride: "++). unwords . map show .
> > (flip lens)[1 ..] .
> > fst . head . readDec)
>
> With a stride of 1000, the program runs out of space
> after 28,000 list elements with the default heap size in Hugs
> on my Unix (Sun) installation, and after 164,000 list elements under ghc.
> With larger strides, it runs out of space sooner on both Hugs and ghc.
>
> What's going on here? It appears to me that both length[1..] and the
> above definition of main should evaluate in constant space.
>
> Rex Page
> [EMAIL PROTECTED]
> School of Computer Science 405-325-4397
> University of Oklahoma fax 405-325-4044
> Norman OK 73019-0631