
Hi, I'm just a beginner trying to learn a little about Haskell, and as such write some toy programs (e.g. for projecteuler.net) in Haskell. Currently, I'm experiencing what I would call "strange behaviour": I've got a data-type data Fraction = Fraction Int Int to hold rational numbers (maybe there's already some built-in type for this in Haskell, much like for instance Scheme has a rational type?), and then I compute a list of pairs of those numbers, that is [(Fraction, Fraction)]. Fraction is declared an instance of Ord. This list has up to 3 million elements. If I do main = print $ length $ points then the program prints out the length fine and takes around 6s to finish (compiled with GHC -O3). Ok, but I acknowledge that length isn't quite an expensive function, as I can imagine that Haskell does not compute and hold the entire list for this but instead each element at once and discards it afterwards. Doing main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points instead, gives a slightly longer runtime (6.6s), but in this case I'm sure that at least each element is computed; right? main = print $ length $ reverse points gives 11.9s, and here I guess (?) that for this to work, the entire list is computed and hold in memory. However, trying to do import List main = print $ length $ sort points makes memory usage go up and the program does not finish in 15m, also spending most time waiting for swapped out memory. What am I doing wrong, why is sort this expensive in this case? I would assume that computing and holding the whole list does not take too much memory, given its size and data type; doing the very same calculation in C should be straight forward. And sort should be O(n * log n) for time and also not much more expensive in memory, right? Am I running into a problem with lazyness? What can I do to avoid it? As far as I see it though, the reverse or map call above should do nearly the same as sort, except maybe that the list needs to be stored in memory as a whole and sort has an additional *log n factor, but neither of those should matter. What's the problem here? Is this something known with sort or similar functions? I couldn't find anything useful on Google, though. My code is below, and while I would of course welcome critics, I do not want to persuade anyone to read through it. Thanks a lot, Daniel ---------------------------------------------------------- -- Problem 165: Intersections of lines. import List -- The random number generator. seeds :: [Integer] seeds = 290797 : [ mod (x * x) 50515093 | x <- seeds ] numbers :: [Int] numbers = map fromInteger (map (\x -> mod x 500) (tail seeds)) -- Line segments, vectors and fractions. data Segment = Segment Int Int Int Int data Vector = Vector Int Int data Fraction = Fraction Int Int instance Eq Fraction where (Fraction a b) == (Fraction c d) = (a == c && b == d) instance Ord Fraction where compare (Fraction a b) (Fraction c d) | (a == c && b == d) = EQ | b > 0 = if a * d < b * c then LT else GT | otherwise = if a * d > b * c then LT else GT -- Build a normalized fraction and get its value. normalize (Fraction a b) = let g = gcd a b; aa = div a g; bb = div b g in if bb < 0 then Fraction (-aa) (-bb) else Fraction aa bb -- Find the inner product of two vectors. innerProduct (Vector a b) (Vector c d) = a * c + b * d -- Find the normal vector and direction of a line segment, as well as -- the constant in straight-normal form for a given normal vector. normalVector (Segment x1 y1 x2 y2) = Vector (y1 - y2) (x2 - x1) direction (Segment x1 y1 x2 y2) = Vector (x2 - x1) (y2 - y1) nfConstant (Segment x1 y1 x2 y2) n = innerProduct n (Vector x1 y1) -- Check if a point is between the ends of the segment times D. betweenEndsTimes d (Segment x1 y1 x2 y2) xD yD = let x1D = x1 * d; x2D = x2 * d; y1D = y1 * d; y2D = y2 * d; xDMin = min x1D x2D; xDMax = max x1D x2D; yDMin = min y1D y2D; yDMax = max y1D y2D in (xDMin <= xD && xDMax >= xD && yDMin <= yD && yDMax >= yD && (x1D /= xD || y1D /= yD) && (x2D /= xD || y2D /= yD)) -- If they are not parallel, we can find their intersection point (at least, -- the one it would be if both were straights). Then it is easy to check if -- it is between the endpoints for both. -- -- n1 * x + m1 * y = c1 -- n2 * x + m2 * y = c2 -- -- => x = (c1 * m2 - x2 * m1) / (n1 * m2 - n2 * m1) -- => y = (n1 * c2 - n2 * c1) / (n1 * m2 - n2 * m1) -- -- (Iff they are parallel, the determinant will be 0.) trueIntersect s1 s2 = let (Vector n1 m1) = normalVector s1; (Vector n2 m2) = normalVector s2; c1 = nfConstant s1 (Vector n1 m1); c2 = nfConstant s2 (Vector n2 m2); d = n1 * m2 - n2 * m1; xD = c1 * m2 - c2 * m1; yD = n1 * c2 - n2 * c1 in if d == 0 then Nothing else if (betweenEndsTimes d s1 xD yD) && (betweenEndsTimes d s2 xD yD) then Just ((normalize $ Fraction xD d), (normalize $ Fraction yD d)) else Nothing -- Build list of segments. takeEveryForth :: [Int] -> [Int] takeEveryForth (a:_:_:_:t) = a : (takeEveryForth t) n1 = numbers n2 = tail n1 n3 = tail n2 n4 = tail n3 segments = [ Segment a b c d | ((a, b), (c, d)) <- zip (zip (takeEveryForth n1) (takeEveryForth n2)) (zip (takeEveryForth n3) (takeEveryForth n4)) ] -- For the first 5000 segments, calculate intersections. firstSegments = take 5000 segments intersects :: [Maybe (Fraction, Fraction)] intersects = findInters firstSegments [] where findInters [] l = l findInters (h:t) l = findInters t (addInters h t l) where addInters _ [] l = l addInters e (h:t) l = addInters e t ((trueIntersect e h) : l) getPoints :: [Maybe (Fraction, Fraction)] -> [(Fraction, Fraction)] getPoints [] = [] getPoints (Nothing : t) = getPoints t getPoints ((Just v) : t) = v : (getPoints t) points = getPoints intersects -- Main program. main :: IO () main = print $ length $ reverse points --main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points --main = print $ length $ sort points

-----BEGIN PGP SIGNED MESSAGE----- Hash: SHA1 On Dec 19, 2008, at 7:40 AM, Daniel Kraft wrote:
data Fraction = Fraction Int Int
to hold rational numbers (maybe there's already some built-in type for this in Haskell, much like for instance Scheme has a rational type?),
There is one. It is called Rational. :)
and then I compute a list of pairs of those numbers, that is [(Fraction, Fraction)]. Fraction is declared an instance of Ord.
This list has up to 3 million elements. If I do
main = print $ length $ points
then the program prints out the length fine and takes around 6s to finish (compiled with GHC -O3). Ok, but I acknowledge that length isn't quite an expensive function, as I can imagine that Haskell does not compute and hold the entire list for this but instead each element at once and discards it afterwards.
Unless something has changed since I last checked, there is little difference between ghc -O2 and ghc -O3, and the latter can even be slower much of the time. It may depend on the situation, but I'm just letting you know. In this case, the runtime should not actually be computing _any_ of the elements of the list since it doesn't care what their values are. You are only counting them, not using them, so it really only computes the spine of the list.
Doing
main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points
instead, gives a slightly longer runtime (6.6s), but in this case I'm sure that at least each element is computed; right?
No. The elements' values are still not actually used, so you are still only evaluating the spine of the list.
main = print $ length $ reverse points
gives 11.9s, and here I guess (?) that for this to work, the entire list is computed and hold in memory.
This is beginning to sound like you think Haskell lists are arrays. They aren't. They are actually linked lists. In order to reverse a linked list, you have to travel all the way to the end and then reconstruct it from there. This explains the time increase. It doesn't really have anything to do with computing the elements or holding anything in memory.
However, trying to do
import List main = print $ length $ sort points
makes memory usage go up and the program does not finish in 15m, also spending most time waiting for swapped out memory. What am I doing wrong, why is sort this expensive in this case? I would assume that computing and holding the whole list does not take too much memory, given its size and data type; doing the very same calculation in C should be straight forward. And sort should be O(n * log n) for time and also not much more expensive in memory, right?
This is actually the first time you really evaluated any of the elements of the list, hence a massive increase in memory use. - - Jake -----BEGIN PGP SIGNATURE----- Version: GnuPG v1.4.8 (Darwin) iEYEARECAAYFAklLsaoACgkQye5hVyvIUKlJYgCfYtwPv/neOnl3+wIu8VhIqfoA lXMAn3EmANZbSRyYeOiXtOdGl7hxCj34 =NJwT -----END PGP SIGNATURE-----

Currently, I'm experiencing what I would call "strange behaviour":
I've got a data-type
data Fraction = Fraction Int Int
to hold rational numbers (maybe there's already some built-in type for this in Haskell,
http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Ratio.html
This list has up to 3 million elements. If I do
main = print $ length $ points
main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points
main = print $ length $ reverse points
However, trying to do
import List main = print $ length $ sort points
makes memory usage go up and the program does not finish in 15m, also spending most time waiting for swapped out memory. What am I doing wrong, why is sort this expensive in this case? I would assume that computing and holding the whole list does not take too much memory, given its size and data type; doing the very same calculation in C should be straight forward. And sort should be O(n * log n) for time and also not much more expensive in memory, right?
Not having looked at your code, I think you are benefiting from fusion/deforestation in the first three main functions. In this case, although you may appear to be evaluating the entire list, in fact the list elements can be discarded as they are generated, so functions like length and reverse can run using constant space, rather than O(n) space. The sort function, however, requires that the entire list is retained, hence greater memory usage. I also think you are optimistic in the memory requirements of your 3 million element list. A list of Ints will take a lot more than 4 bytes per element (on 32-bit machines) because there's overhead for the list pointers, plus possibly the boxes for the Ints themselves. I think there are 3 machine words for each list entry (pointer to this element, pointer to next element, info-table pointer), and 2 words for each Int, but I'm just guessing: http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObje cts You might get some mileage by suggesting to GHC that your Fraction type is strict e.g.
data Fraction = Fraction !Int !Int
which might persuade it to unbox the Ints, giving some space savings. Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

Bayley, Alistair wrote:
Currently, I'm experiencing what I would call "strange behaviour":
I've got a data-type
data Fraction = Fraction Int Int
to hold rational numbers (maybe there's already some built-in type for this in Haskell,
http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Ratio.html
Thanks for the pointer, I knew there would be something already there :)
This list has up to 3 million elements. If I do
main = print $ length $ points
main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points
main = print $ length $ reverse points
However, trying to do
import List main = print $ length $ sort points
makes memory usage go up and the program does not finish in 15m, also spending most time waiting for swapped out memory. What am I doing wrong, why is sort this expensive in this case? I would assume that computing and holding the whole list does not take too much memory, given its size and data type; doing the very same calculation in C should be straight forward. And sort should be O(n * log n) for time and also not much more expensive in memory, right?
Not having looked at your code, I think you are benefiting from fusion/deforestation in the first three main functions. In this case, although you may appear to be evaluating the entire list, in fact the list elements can be discarded as they are generated, so functions like length and reverse can run using constant space, rather than O(n) space.
How does reverse work in constant space? At the moment I can't imagine it doing so; that's why I tried it, but of course you could be right.
The sort function, however, requires that the entire list is retained, hence greater memory usage. I also think you are optimistic in the memory requirements of your 3 million element list. A list of Ints will take a lot more than 4 bytes per element (on 32-bit machines) because there's overhead for the list pointers, plus possibly the boxes for the Ints themselves. I think there are 3 machine words for each list entry (pointer to this element, pointer to next element, info-table pointer), and 2 words for each Int, but I'm just guessing: http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObje cts
Of course that's the case, but the list being 3 million elements, and not, say 100 (which would still fit into memory for a simple C array of ints) I thought would make it possible. Otherwise, how can one handle such amounts in data anyway? Only using arrays?
You might get some mileage by suggesting to GHC that your Fraction type is strict e.g.
data Fraction = Fraction !Int !Int
which might persuade it to unbox the Ints, giving some space savings.
I already tried so, but this doesn't change anything to the performance. I will however try now to use the provided rational type, maybe this helps. Thanks for the answers, Daniel

On Fri, Dec 19, 2008 at 7:58 AM, Daniel Kraft
Not having looked at your code, I think you are benefiting from
fusion/deforestation in the first three main functions. In this case, although you may appear to be evaluating the entire list, in fact the list elements can be discarded as they are generated, so functions like length and reverse can run using constant space, rather than O(n) space.
How does reverse work in constant space? At the moment I can't imagine it doing so; that's why I tried it, but of course you could be right.
No, you are correct, reverse is not constant space. However, as Duncan explained, reverse does not force any elements of the list, so even if you had a list of elements which consumed 1Mb each (when fully evaluated), they would not be forced so the memory would look exactly the same.
The sort function, however, requires that the entire list is retained,
hence greater memory usage. I also think you are optimistic in the memory requirements of your 3 million element list. A list of Ints will take a lot more than 4 bytes per element (on 32-bit machines) because there's overhead for the list pointers, plus possibly the boxes for the Ints themselves. I think there are 3 machine words for each list entry (pointer to this element, pointer to next element, info-table pointer), and 2 words for each Int, but I'm just guessing: http://hackage.haskell.org/trac/ghc/wiki/Commentary/Rts/Storage/HeapObje cts
Of course that's the case, but the list being 3 million elements, and not, say 100 (which would still fit into memory for a simple C array of ints) I thought would make it possible. Otherwise, how can one handle such amounts in data anyway? Only using arrays?
Well, if you know the size beforehand and you know the whole thing needs to fit into memory at the same time, an array is usually a better choice than a list. Lists are more like loops -- i.e. control flow rather than data, whereas Arrays are definitely data. I realize the imprecision of that statement... However, I am not sure what all this jabber about swapping is. 28 bytes/elt * 3,000,000 elts = 84 Mb, which easily fits into a modern machine's memory. There are a lot of traps for the unwary in memory performance though. Depending on how things are defined, you may be computing *too* lazily, building up thunks when you should just be crunching numbers. Still, swapping on this 3,000,000 element list is absurd, and we should look closer into your example. Post the rest (eg. the instances?)? Luke
You might get some mileage by suggesting to GHC that your Fraction type
is strict e.g.
data Fraction = Fraction !Int !Int
which might persuade it to unbox the Ints, giving some space savings.
I already tried so, but this doesn't change anything to the performance. I will however try now to use the provided rational type, maybe this helps.
Thanks for the answers, Daniel
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Fri, 2008-12-19 at 15:58 +0100, Daniel Kraft wrote:
How does reverse work in constant space? At the moment I can't imagine it doing so; that's why I tried it, but of course you could be right.
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
You might get some mileage by suggesting to GHC that your Fraction type is strict e.g.
data Fraction = Fraction !Int !Int
which might persuade it to unbox the Ints, giving some space savings.
I already tried so, but this doesn't change anything to the performance. I will however try now to use the provided rational type, maybe this helps.
It will not make any difference to the space used by Fraction unless you also unpack them as I mentioned in my other post. Duncan

On Fri, Dec 19, 2008 at 8:26 AM, Duncan Coutts
On Fri, 2008-12-19 at 15:58 +0100, Daniel Kraft wrote:
How does reverse work in constant space? At the moment I can't imagine it doing so; that's why I tried it, but of course you could be right.
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
I don't think that's true. It must inspect the whole input list to give the first element of the output list, but it cannot garbage collect the input list because it needs to yield every element of it. When I tested: ghci> length $ reverse [1..10^7] It certainly did not run in constant space. I think that if the first half of the output list is unused, then the second half of the input list will be collected (I'm having trouble visualizing the dynamics of this case though). But for the very first cons of the output, the whole input list (spine) needs to be in memory. Luke
You might get some mileage by suggesting to GHC that your Fraction type is strict e.g.
data Fraction = Fraction !Int !Int
which might persuade it to unbox the Ints, giving some space savings.
I already tried so, but this doesn't change anything to the performance. I will however try now to use the provided rational type, maybe this helps.
It will not make any difference to the space used by Fraction unless you also unpack them as I mentioned in my other post.
Duncan
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

How does reverse work in constant space? At the moment I can't imagine it doing so; that's why I tried it, but of course you could be right.
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
I don't think that's true. It must inspect the whole input list to give the first element of the output list, but it cannot garbage collect the input list because it needs to yield every element of it.
reverse creates the output list by pulling items from the head of the input list, and prefixing them to the output list. After each item has been pulled from the input, the list node can be GC'd from the input list. Also, if the output list is itself being consumed by a function which does not require the entire list (like length) then again the list node can be GC'd soon after consumption.
ghci> length $ reverse [1..10^7]
This is a compiler optimisation, I think, so will probably require ghc -O(2?). Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Fri, Dec 19, 2008 at 8:54 AM, Bayley, Alistair < Alistair.Bayley@invesco.com> wrote:
> How does reverse work in constant space? At the moment I can't imagine > it doing so; that's why I tried it, but of course you could be right.
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
I don't think that's true. It must inspect the whole input list to give the first element of the output list, but it cannot garbage collect the input list because it needs to yield every element of it.
reverse creates the output list by pulling items from the head of the input list, and prefixing them to the output list.
*Tail recursively! *That is a very important point.* *Let's have a closer look at an explicitly recursive version. reverse xs = go [] xs where go out [] = out go out (x:xs) = go (x:out) xs * *Now let's do a rewrite chain: reverse (enumFromTo 1 4) go [] (enumFromTo 1 4) go [] (1:enumFromTo 2 4) go (1:[]) (enumFromTo 2 4) go (1:[]) (2:enumFromTo 3 4) go (2:1:[]) (enumFromTo 3 4) go (2:1:[]) (3:enumFromTo 4 4) go (3:2:1:[]) (enumFromTo 4 4) go (3:2:1:[]) (4:enumFromTo 5 4) go (4:3:2:1:[]) (enumFromTo 5 4) go (4:3:2:1:[]) [] 4:3:2:1:[] (For sanity I skipped the number evaluation steps, but enumFromTo would have been forcing them to check for the end, so it ends up the same) We needed to construct the entire reversed list before we could see the first cons cell. There *is* a very strange implementation of reverse whose spine is as lazy as the input spine (but forcing the first element will still force the whole input spine). But it is quite odd, and certainly is not arrived at by the compiler automatically from the definition in the Prelude. I verified with -O2. length . reverse is not constant space in GHC. And there really is no reasonable way it could be (save for specific RULES pragmata). Luke After each item has
been pulled from the input, the list node can be GC'd from the input list. Also, if the output list is itself being consumed by a function which does not require the entire list (like length) then again the list node can be GC'd soon after consumption.
ghci> length $ reverse [1..10^7]
This is a compiler optimisation, I think, so will probably require ghc -O(2?).
Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

reverse creates the output list by pulling items from the head of the input list, and prefixing them to the output list.
Tail recursively! That is a very important point. Let's have a closer look at an explicitly recursive version.
reverse xs = go [] xs where go out [] = out go out (x:xs) = go (x:out) xs
Now let's do a rewrite chain:
reverse (enumFromTo 1 4) go [] (enumFromTo 1 4) go [] (1:enumFromTo 2 4) go (1:[]) (enumFromTo 2 4) go (1:[]) (2:enumFromTo 3 4) go (2:1:[]) (enumFromTo 3 4) go (2:1:[]) (3:enumFromTo 4 4) go (3:2:1:[]) (enumFromTo 4 4) go (3:2:1:[]) (4:enumFromTo 5 4) go (4:3:2:1:[]) (enumFromTo 5 4) go (4:3:2:1:[]) [] 4:3:2:1:[]
(For sanity I skipped the number evaluation steps, but enumFromTo would have been forcing them to check for the end, so it ends up the same)
We needed to construct the entire reversed list before we could see the first cons cell.
There is a very strange implementation of reverse whose spine is as lazy as the input spine (but forcing the first element will still force the whole input spine). But it is quite odd, and certainly is not arrived at by the compiler automatically from the definition in the Prelude.
I verified with -O2. length . reverse is not constant space in GHC. And there really is no reasonable way it could be (save for specific RULES pragmata).
Luke
One could also well imagine a list fusion optimisation that says: length . reverse == length I have no idea if this is applied (or even correct). I compared (with ghc 6.8, --make -O2 -prof -auto-all): main = print (length x) x :: [Int] x = [1..1000000] total alloc = 40,002,288 bytes (excludes profiling overheads) main = print (length (reverse x)) x :: [Int] x = [1..1000000] total alloc = 52,002,296 bytes (excludes profiling overheads) So the reverse has some overhead (25%). Is that what you'd expect if it was entirely constructed? Another comparison: main = print (length x) x :: [Int] x = take 1000000 (repeat 1) total alloc = 24,002,256 bytes (excludes profiling overheads) main = print (length (reverse x)) x :: [Int] x = take 1000000 (repeat 1) total alloc = 36,002,264 bytes (excludes profiling overheads) I'm not sure what this says, exactly (50% overhead?). Alistair ***************************************************************** Confidentiality Note: The information contained in this message, and any attachments, may contain confidential and/or privileged material. It is intended solely for the person(s) or entity to which it is addressed. Any review, retransmission, dissemination, or taking of any action in reliance upon this information by persons or entities other than the intended recipient(s) is prohibited. If you received this in error, please contact the sender and delete the material from any computer. *****************************************************************

On Fri, 2008-12-19 at 08:44 -0700, Luke Palmer wrote:
On Fri, Dec 19, 2008 at 8:26 AM, Duncan Coutts
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
I don't think that's true. It must inspect the whole input list to give the first element of the output list, but it cannot garbage collect the input list because it needs to yield every element of it.
When I tested:
ghci> length $ reverse [1..10^7]
It certainly did not run in constant space.
But that's because the input list took constant not linear space. I said it allocates an element for every element in the input. So it's only constant space if we can offset a linear amount of space used for the output with a linear amount of space saved from collecting the input. Try this: using the helper function: force = foldr (\x xs -> seq xs (x : xs)) [] Then we want to look at the heap space used to evaluate: head (force [1..10^6]) and compare it to: head (reverse (force [1..10^6])) We can do that using $ ghc +RTS -s -RTS -e 'expr' and looking at the "bytes maximum residency" in the GC stats. On my box (64bit) we find that the two examples use almost exactly the same maximum heap size (of about 20Mb). So that's why I was claiming reverse takes constant net memory (when the input list is evaluated and can be subsequently discarded). Duncan

Hmm, okay. I guess there are some subtle technical jargon issues then.
You're talking about space in terms of fully evaluated inputs. But whatever
I used to talk about this, I would want it to distinguish the behavior of
"reverse" and, say, "map id". But I suppose strictness is a better tool to
talk about that difference than space complexity. I.e.:
reverse (xs ++ _|_) = _|_
Luke
On Fri, Dec 19, 2008 at 9:48 AM, Duncan Coutts
On Fri, 2008-12-19 at 08:44 -0700, Luke Palmer wrote:
On Fri, Dec 19, 2008 at 8:26 AM, Duncan Coutts
It allocates a new list cell for every cell it finds in the input list. If the input list can be garbage collected then reverse takes constant space because each time it inspects a list cell from the input list that cell can be garbage collected. If the input list is being retained for some other reason then reverse will take linear space.
I don't think that's true. It must inspect the whole input list to give the first element of the output list, but it cannot garbage collect the input list because it needs to yield every element of it.
When I tested:
ghci> length $ reverse [1..10^7]
It certainly did not run in constant space.
But that's because the input list took constant not linear space. I said it allocates an element for every element in the input. So it's only constant space if we can offset a linear amount of space used for the output with a linear amount of space saved from collecting the input.
Try this:
using the helper function: force = foldr (\x xs -> seq xs (x : xs)) []
Then we want to look at the heap space used to evaluate: head (force [1..10^6])
and compare it to: head (reverse (force [1..10^6]))
We can do that using $ ghc +RTS -s -RTS -e 'expr' and looking at the "bytes maximum residency" in the GC stats.
On my box (64bit) we find that the two examples use almost exactly the same maximum heap size (of about 20Mb).
So that's why I was claiming reverse takes constant net memory (when the input list is evaluated and can be subsequently discarded).
Duncan

On Fri, 2008-12-19 at 14:40 +0100, Daniel Kraft wrote:
Hi,
I'm just a beginner trying to learn a little about Haskell, and as such write some toy programs (e.g. for projecteuler.net) in Haskell.
Currently, I'm experiencing what I would call "strange behaviour":
I've got a data-type
data Fraction = Fraction Int Int
to hold rational numbers (maybe there's already some built-in type for this in Haskell, much like for instance Scheme has a rational type?), and then I compute a list of pairs of those numbers, that is [(Fraction, Fraction)]. Fraction is declared an instance of Ord.
This list has up to 3 million elements. If I do
main = print $ length $ points
then the program prints out the length fine and takes around 6s to finish (compiled with GHC -O3). Ok, but I acknowledge that length isn't quite an expensive function, as I can imagine that Haskell does not compute and hold the entire list for this but instead each element at once and discards it afterwards.
Right.
Doing
main = print $ length $ map (\(x, _) -> x == Fraction 1 2) points
instead, gives a slightly longer runtime (6.6s), but in this case I'm sure that at least each element is computed; right?
Nope. Nothing looks at the result of the comparison so it is not done and so it does not force any of the fractions to be computed.
main = print $ length $ reverse points
gives 11.9s, and here I guess (?) that for this to work, the entire list is computed and hold in memory.
Yes, the list is held in memory but the elements are not computed.
However, trying to do
import List main = print $ length $ sort points
Now it really does have to compute the elements because comparing the elements involves inspecting them.
makes memory usage go up and the program does not finish in 15m, also spending most time waiting for swapped out memory.
Right. Much more memory used this time and that is pushing your machine into swapping which then goes very very slowly.
What am I doing wrong, why is sort this expensive in this case?
Sort itself is not so expensive, the expensive thing was calculating all the elements of your list and sort was the first function that had to do it. If you used something like sum (rather than length) then it'd hit the same issue as it would need to evaluate each element.
I would assume that computing and holding the whole list does not take too much memory, given its size and data type;
That does not seem to be the case. data Fraction = Fraction Int Int This takes 7 words per Fraction. There's 3 words for the Fraction constructor and it's two fields. Each Int also takes 2 words. On a 32bit machine that is 28 bytes, or 56 on a 64bit machine. We can reduce the memory requirements for Fraction by making the Int's strict and unpacking them into the Fraction constructor: data Fraction = Fraction {-# UNPACK #-} !Int {-# UNPACK #-} !Int Now it takes 3 words per Fraction. However it is no longer so lazy. Previously you could have (Fraction 3 (error "not used")) and as long as you never looked at the second Int it would work. Now that we made both fields strict (the ! on the fields) that does not work any more, (Fraction 3 (error "not used")) will produce the error, even if we only look at the first Int.
doing the very same calculation in C should be straight forward.
In an eager language like C the first one would have failed too because it would have had to compute all the elements eagerly and holding them all in memory at once seems to require more memory than your machine has. On the other hand C would use something more like the strict variant I mentioned above so the initial memory requirements would probably be lower.
And sort should be O(n * log n) for time and also not much more expensive in memory, right?
Sort does take a bit more memory than just reversing because it has to construct some intermediate lists while merging.
Am I running into a problem with lazyness?
A problem in your understanding of lazyness.
What can I do to avoid it?
Look at this again: length $ map (\(x, _) -> x == Fraction 1 2) points Try something like: length $ map (\_ -> error "look! never evaluated!") points you'll find it gives the same answer. That's because length never looks at the elements of the list.
As far as I see it though, the reverse or map call above should do nearly the same as sort, except maybe that the list needs to be stored in memory as a whole and sort has an additional *log n factor, but neither of those should matter. What's the problem here?
reverse never looks at the elements of the list, sort does. Duncan
participants (6)
-
Bayley, Alistair
-
Daniel Kraft
-
Duncan Coutts
-
Jake Mcarthur
-
Luke Palmer
-
Lutz Donnerhacke