
When advocating functional languages like Haskell, one of the claims I've tended to make is that referential transparency allows the language to be much more aggressive about things like common subexpression elimination (CSE) than traditional imperative languages (which need to worry about preserving proper side-effect sequencing). But a recent example has left me thinking that maybe I've gone too far in my claims. First, lets consider a simple consumer program, such as:
printEveryNth c l n = do print (c', x) printEveryNth c' xs n where c' = c+n x:xs = drop (n-1) l
Note that we can pass this function an infinite list, such as [1..], and it won't retain the whole list as it prints out every nth element of the list. Now let's consider two possible infinite lists we might pass to our consumer function. We'll use a list of primes (inspired by the recent discussion of primes, but you can ignore the exact function being computed). Here's the first version:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where factorsToTry x = takeWhile (\p -> p*p <= x) primes
As you might expect, at the point where we print the nth prime from our infinite list, we will be retaining a list that requires O(n) space. But this simple modification allows us to use only O(sqrt(n)) space at the point we print the nth prime:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where slowerPrimes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] factorsToTry x = takeWhile (\p -> p*p <= x) slowerPrimes
Notice the gigantic common subexpression -- both primes and slowerPrimes define exactly the same list, but at the point where we're examining the nth element of primes, we'll only have advanced to the sqrt(n)th element of slowerPrimes. Clearly, "simplifying" the second version of primes into the first by performing CSE actually makes the code much *worse*. This "CSE- makes-it-worse" property strikes me as "interesting". So, is it "interesting"...? Has anyone worked on characterizing CSE space leaks (and avoiding CSE in those cases)? FWIW, it looks like others have run into the same problem, since bug #947 in GHC (from October 2006) seems to be along similar lines. Melissa. P.S. These issues do make massive difference in practice. There is a huge difference between taking O(n) and O(sqrt(n)) space -- the difference between a couple of megabytes for the heap and tens or hundreds of megabytes.

But this simple modification allows us to use only O(sqrt(n)) space at the point we print the nth prime:
I wouldn't call your modification simple. It appears that you are trying to put smarts into the garbage collector and memoization logic, the first step towards a priority queue of memoized results. Suppose you had data Nat = Zero | Succ Nat firstNprimes :: Nat -> [Integer] firstNprimes Zero = [] firstNprimes ( Succ $ Zero) = 2 : firstNprimes Zero firstNprimes (Succ . Succ $ Zero) = 3 : firstNprimes (Succ $ Zero) ... The resulting sublists should be shared, so that each memoized partial evaluation is just a head and a pointer, with space O(2*n). Suppose further you could tell the garbage collector to discard the highest Nat firstNprimes sublists first, forcing a recomputation whenever needed again. Then, assuming you use only the one (outer) primes function, your primes function (which needs all the firstNprimes) has the lowest priority and gets recalculated on memory exhaustion, but only back to the highest known prime, which will eventually (and forever thereafter) be the highest firstNprimes that fits in memory. The code uses the most memory it can for efficiency, then continues on maximally efficiently from there on the fly. This is the sort of control you are getting on the cheap with your non-trivial use of two primes functions. It is the kind of logic that might be difficult to automate. Dan Weston Melissa O'Neill wrote:
When advocating functional languages like Haskell, one of the claims I've tended to make is that referential transparency allows the language to be much more aggressive about things like common subexpression elimination (CSE) than traditional imperative languages (which need to worry about preserving proper side-effect sequencing).
But a recent example has left me thinking that maybe I've gone too far in my claims.
First, lets consider a simple consumer program, such as:
printEveryNth c l n = do print (c', x) printEveryNth c' xs n where c' = c+n x:xs = drop (n-1) l
Note that we can pass this function an infinite list, such as [1..], and it won't retain the whole list as it prints out every nth element of the list.
Now let's consider two possible infinite lists we might pass to our consumer function. We'll use a list of primes (inspired by the recent discussion of primes, but you can ignore the exact function being computed). Here's the first version:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where factorsToTry x = takeWhile (\p -> p*p <= x) primes
As you might expect, at the point where we print the nth prime from our infinite list, we will be retaining a list that requires O(n) space.
But this simple modification allows us to use only O(sqrt(n)) space at the point we print the nth prime:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where slowerPrimes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] factorsToTry x = takeWhile (\p -> p*p <= x) slowerPrimes
Notice the gigantic common subexpression -- both primes and slowerPrimes define exactly the same list, but at the point where we're examining the nth element of primes, we'll only have advanced to the sqrt(n)th element of slowerPrimes.
Clearly, "simplifying" the second version of primes into the first by performing CSE actually makes the code much *worse*. This "CSE-makes-it-worse" property strikes me as "interesting".
So, is it "interesting"...? Has anyone worked on characterizing CSE space leaks (and avoiding CSE in those cases)? FWIW, it looks like others have run into the same problem, since bug #947 in GHC (from October 2006) seems to be along similar lines.
Melissa.
P.S. These issues do make massive difference in practice. There is a huge difference between taking O(n) and O(sqrt(n)) space -- the difference between a couple of megabytes for the heap and tens or hundreds of megabytes.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

I think I might not have been lazy enough to get proper memoization. This might be needed: firstNprimes :: Nat -> [Integer] firstNprimes Zero = [] firstNprimes ( Succ $ Zero) = let p = firstNprimes Zero in 2 : p firstNprimes (Succ . Succ $ Zero) = let p = firstNprimes (Succ $ Zero) in 3 : p ... Dan Weston wrote:
But this simple modification allows us to use only O(sqrt(n)) space at the point we print the nth prime:
I wouldn't call your modification simple. It appears that you are trying to put smarts into the garbage collector and memoization logic, the first step towards a priority queue of memoized results.
Suppose you had
data Nat = Zero | Succ Nat
firstNprimes :: Nat -> [Integer] firstNprimes Zero = [] firstNprimes ( Succ $ Zero) = 2 : firstNprimes Zero firstNprimes (Succ . Succ $ Zero) = 3 : firstNprimes (Succ $ Zero) ...
The resulting sublists should be shared, so that each memoized partial evaluation is just a head and a pointer, with space O(2*n).
Suppose further you could tell the garbage collector to discard the highest Nat firstNprimes sublists first, forcing a recomputation whenever needed again.
Then, assuming you use only the one (outer) primes function, your primes function (which needs all the firstNprimes) has the lowest priority and gets recalculated on memory exhaustion, but only back to the highest known prime, which will eventually (and forever thereafter) be the highest firstNprimes that fits in memory.
The code uses the most memory it can for efficiency, then continues on maximally efficiently from there on the fly.
This is the sort of control you are getting on the cheap with your non-trivial use of two primes functions. It is the kind of logic that might be difficult to automate.
Dan Weston
Melissa O'Neill wrote:
When advocating functional languages like Haskell, one of the claims I've tended to make is that referential transparency allows the language to be much more aggressive about things like common subexpression elimination (CSE) than traditional imperative languages (which need to worry about preserving proper side-effect sequencing).
But a recent example has left me thinking that maybe I've gone too far in my claims.
First, lets consider a simple consumer program, such as:
printEveryNth c l n = do print (c', x) printEveryNth c' xs n where c' = c+n x:xs = drop (n-1) l
Note that we can pass this function an infinite list, such as [1..], and it won't retain the whole list as it prints out every nth element of the list.
Now let's consider two possible infinite lists we might pass to our consumer function. We'll use a list of primes (inspired by the recent discussion of primes, but you can ignore the exact function being computed). Here's the first version:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where factorsToTry x = takeWhile (\p -> p*p <= x) primes
As you might expect, at the point where we print the nth prime from our infinite list, we will be retaining a list that requires O(n) space.
But this simple modification allows us to use only O(sqrt(n)) space at the point we print the nth prime:
primes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] where slowerPrimes = 2 : [x | x <- [3,5..], all (\p -> x `mod` p > 0) (factorsToTry x)] factorsToTry x = takeWhile (\p -> p*p <= x) slowerPrimes
Notice the gigantic common subexpression -- both primes and slowerPrimes define exactly the same list, but at the point where we're examining the nth element of primes, we'll only have advanced to the sqrt(n)th element of slowerPrimes.
Clearly, "simplifying" the second version of primes into the first by performing CSE actually makes the code much *worse*. This "CSE-makes-it-worse" property strikes me as "interesting".
So, is it "interesting"...? Has anyone worked on characterizing CSE space leaks (and avoiding CSE in those cases)? FWIW, it looks like others have run into the same problem, since bug #947 in GHC (from October 2006) seems to be along similar lines.
Melissa.
P.S. These issues do make massive difference in practice. There is a huge difference between taking O(n) and O(sqrt(n)) space -- the difference between a couple of megabytes for the heap and tens or hundreds of megabytes.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Melissa You might find chapter 23 "The pragmatics of graph reduction" in my 1987 book worth a look. It gives other examples where CSE can be harmful. Simon | -----Original Message----- | From: haskell-cafe-bounces@haskell.org [mailto:haskell-cafe- | bounces@haskell.org] On Behalf Of Melissa O'Neill | Sent: 24 July 2007 23:36 | To: Haskell Cafe | Subject: [Haskell-cafe] Space usage and CSE in Haskell | | When advocating functional languages like Haskell, one of the claims | I've tended to make is that referential transparency allows the | language to be much more aggressive about things like common | subexpression elimination (CSE) than traditional imperative languages | (which need to worry about preserving proper side-effect sequencing). | | But a recent example has left me thinking that maybe I've gone too | far in my claims.

I wrote:
This "CSE-makes-it-worse" property strikes me as "interesting". Has anyone worked on characterizing CSE space leaks (and avoiding CSE in those cases)?
and Simon replied:
You might find chapter 23 "The pragmatics of graph reduction" in my 1987 book worth a look. It gives other examples where CSE can be harmful.
There are some great examples there. Specifically, 23.4.2 "Excessive Sharing" (viewable at http://research.microsoft.com/~simonpj/papers/ slpj-book-1987/PAGES/405.HTM) gives a neat example, the powerList function. In short, it contrasts two definitions. The first uses sharing: powerList [] = [ [] ] powerList (x:xs) = pxs ++ map (x :) pxs where pxs = powerList xs and a space-efficient one (that does more reductions): powerList [] = [ [] ] powerList (x:xs) = (powerList xs) ++ map (x :) (powerList xs) ... when running length(powerList [1..20]). But my original question was whether this problem is considered "interesting", etc. As Simon points out above, its an issue that has existed for at least 20 years, but Simon also wrote for GHC bug #947 (which looked like a related issue):
I don't know any way to solve this problem automatically. But I do think it should be under your control.
To me, problems that Simon doesn't know how to solve are by definition at least a little interesting, but probably likely to be rather hard... :-) Melissa. P.S. GHC bug #947 can be viewed at http://hackage.haskell.org/trac/ ghc/ticket/947 (Simon's bandaid for GHC bug #947 was -fno-cse.)

On 25 Jul 2007, at 6:50 pm, Melissa O'Neill wrote: [section 23.4.2 of Simon's 1987 book]. The really scary thing about this example is that so much depends on the order in which the subsets are returned, which in many cases does not matter. Here's code that I tried with GHC on a 500MHz SPARC. With today's memory we might be willing to put up with the O(2**N) space cost (as long as N isn't too big), because that saves us more than a factor of 3 in time. But changing the order of the results gives us a nice bounded space solution which is nearly 9 times faster than the naive sharing code. In a non-trivial program, we wouldn't have a hope of spotting issues like this without memory use profiling. Unless someone has some ideas about how to design code so that it's not a problem? main = print (length (power_list [1..20])) power_list :: [Int] -> [[Int]] power_list [] = [[]] {- Classic 23.4.2 first definition of power_list with space sharing and therefore "O(2**N) transient residency". power_list (x:xs) = pxs ++ map (x :) pxs where pxs = power_list xs -- 3.540 user + 0.220 system = 3.760 total seconds. -} {- Classic 23.4.2 second definition, with recomputing, "constant residency", but poor run-time. power_list (x:xs) = power_list xs ++ map (x :) (power_list xs) -- 12.130 user + 0.110 system = 12.240 total seconds. -} {- A fairly obvious variant of the first definition. The order is changed to eliminate wasted appends, but the space behaviour doesn't change that much. power_list (x:xs) = map (x :) pxs ++ pxs where pxs = power_list xs -- 2.020 user + 0.240 system = 2.260 total seconds. -} {- Another change to the order to give us MORE sharing takes less time AND less space. The surprise is how much less time. -} power_list (x:xs) = foo (power_list xs) x where foo [] _ = [] foo (y:ys) x = (x:y) : y : foo ys x -- 0.370 user + 0.060 system = 0.430 total seconds.

Maybe it behooves writers of GHC libraries who create list generating functions f where the complexity of length . f is strictly less than the complexity of f itself to provide an fLength function and a rewrite rule for it: {-# RULES "listLength" length . f = fLength #-} Then people like me could mindlessly write
main = print (length (power_list [1..20]))
and get
main = print (power_list_length [1..20])
without worrying about efficiency. Dan ok wrote:
On 25 Jul 2007, at 6:50 pm, Melissa O'Neill wrote: [section 23.4.2 of Simon's 1987 book].
The really scary thing about this example is that so much depends on the order in which the subsets are returned, which in many cases does not matter. Here's code that I tried with GHC on a 500MHz SPARC.
With today's memory we might be willing to put up with the O(2**N) space cost (as long as N isn't too big), because that saves us more than a factor of 3 in time. But changing the order of the results gives us a nice bounded space solution which is nearly 9 times faster than the naive sharing code.
In a non-trivial program, we wouldn't have a hope of spotting issues like this without memory use profiling. Unless someone has some ideas about how to design code so that it's not a problem?
main = print (length (power_list [1..20]))
power_list :: [Int] -> [[Int]]
power_list [] = [[]] {- Classic 23.4.2 first definition of power_list with space sharing and therefore "O(2**N) transient residency".
power_list (x:xs) = pxs ++ map (x :) pxs where pxs = power_list xs
-- 3.540 user + 0.220 system = 3.760 total seconds. -}
{- Classic 23.4.2 second definition, with recomputing, "constant residency", but poor run-time.
power_list (x:xs) = power_list xs ++ map (x :) (power_list xs)
-- 12.130 user + 0.110 system = 12.240 total seconds. -}
{- A fairly obvious variant of the first definition. The order is changed to eliminate wasted appends, but the space behaviour doesn't change that much.
power_list (x:xs) = map (x :) pxs ++ pxs where pxs = power_list xs
-- 2.020 user + 0.240 system = 2.260 total seconds. -}
{- Another change to the order to give us MORE sharing takes less time AND less space. The surprise is how much less time. -} power_list (x:xs) = foo (power_list xs) x where foo [] _ = [] foo (y:ys) x = (x:y) : y : foo ys x
-- 0.370 user + 0.060 system = 0.430 total seconds.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Richard O'Keefe
Another change to the order to give us MORE sharing takes less time AND less space. The surprise is how much less time.
Interesting stuff. My students and I briefly chatted about powerset this morning and came up with the same function, but the very significant time differences you pointed out aren't something that shows up on a whiteboard, so thanks for all those timings.
The really scary thing about this example is that so much depends on the order in which the subsets are returned, which in many cases does not matter.
(I'm going a bit off main topic from Richard's (informative) post here, but hey...) Saying something like "let's improve space performance by doing it backwards and then reversing the list", while great in ML, won't (always) cut it in Haskell. The need to preserve laziness/strictness can tie our hands. For example, consider yet another variant of power_list: power_list l = [] : pow [[]] l where pow acc [] = [] pow acc (x:xs) = acc_x ++ pow (acc ++ acc_x) xs where acc_x = map (++ [x]) acc By many standards, this version is inefficient, with plenty of appends and lots of transient space usage. BUT, it generates the output in an order that'll accommodate infinite lists, thus we can say: power_list [1..] (none of the other versions had this property -- they'd just die here) So, the moral for optimizations is that any transformation we do to improve space performance shouldn't make our program stricter than it was before. (I think the paper by David Sands and Joergen Gustavsson that Janis Voigtlaender mentioned covers this too, but I haven't had a chance to look at it closely yet.) Melissa. P.S. For fun, I'll also note that yes, it *is* possible to code a lazy-list-friendly power_list function in a way that doesn't drag saved lists around, although it doesn't run as nearly as quickly as some of the others seen. -- Count in binary and use that to create power set power_list xs = loop zero where loop n = case select xs n of Nothing -> [] Just set -> set : loop (inc n) select xs [] = Just [] select [] nat = Nothing select (x:xs) (True:nat') = select xs nat' >>= \l -> Just (x:l) select (x:xs) (False:nat') = select xs nat' zero = [] inc [] = [True] inc (False:bits) = True : bits inc (True :bits) = False : inc bits No doubt this can be coded better yet...

Melissa O'Neill wrote:
For example, consider yet another variant of power_list:
power_list l = [] : pow [[]] l where pow acc [] = [] pow acc (x:xs) = acc_x ++ pow (acc ++ acc_x) xs where acc_x = map (++ [x]) acc
By many standards, this version is inefficient, with plenty of appends and lots of transient space usage.
BUT, it generates the output in an order that'll accommodate infinite lists, thus we can say:
power_list [1..]
(none of the other versions had this property -- they'd just die here)
So, the moral for optimizations is that any transformation we do to improve space performance shouldn't make our program stricter than it was before. (I think the paper by David Sands and Joergen Gustavsson that Janis Voigtlaender mentioned covers this too, but I haven't had a chance to look at it closely yet.)
Melissa.
P.S. For fun, I'll also note that yes, it *is* possible to code a lazy-list-friendly power_list function in a way that doesn't drag saved lists around, although it doesn't run as nearly as quickly as some of the others seen.
-- Count in binary and use that to create power set power_list xs = loop zero where loop n = case select xs n of Nothing -> [] Just set -> set : loop (inc n)
select xs [] = Just [] select [] nat = Nothing select (x:xs) (True:nat') = select xs nat' >>= \l -> Just (x:l) select (x:xs) (False:nat') = select xs nat'
zero = [] inc [] = [True] inc (False:bits) = True : bits inc (True :bits) = False : inc bits
No doubt this can be coded better yet...
And it can. Though the speed depends on whether you use and Int or Integer to keep track of the length of the input list. (If you want a power set of a list with 2^31 elements then you can change to Integer). Your code for power_list and mine for powerBin and powerBin2 work in infinite lists:
*Main> take 10 (power_list [1..]) [[],[1],[2],[1,2],[3],[1,3],[2,3],[1,2,3],[4],[1,4]] *Main> take 10 (powerBin [1..]) [[],[1],[2],[1,2],[3],[2,3],[1,3],[1,2,3],[4],[3,4]] *Main> take 10 (powerBin2 [1..]) [[],[1],[1,2],[2],[1,2,3],[1,3],[2,3],[3],[1,2,3,4],[1,2,4]]
Though they all disagree about the order involved. My actual code:
powerBin [] = [[]] powerBin xs = [] : upto (0 :: Int) where upto limit = fromTo limit id (upto (succ limit)) xs where fromTo n acc cont [] = [] -- reached past end of input list, now done fromTo 0 acc cont (y:_) = (acc . (y:) $ []) : cont fromTo n acc cont (y:ys) = let n' = pred n acc' = acc . (y:) cont' = fromTo n' acc' cont ys in fromTo n' acc cont' ys
And a version with acc' and acc switched:
powerBin2 [] = [[]] powerBin2 xs = [] : upto (0 :: Int) where upto limit = fromTo limit id (upto (succ limit)) xs where fromTo n acc cont [] = [] -- reached past end of input list, now done fromTo 0 acc cont (y:_) = (acc . (y:) $ []) : cont fromTo n acc cont (y:ys) = let n' = pred n acc' = acc . (y:) cont' = fromTo n' acc cont ys in fromTo n' acc' cont' ys
The above never uses (++) or 'reverse' but does build a DList of (y:) for 'acc'. If you do not care if the returned lists are individually reversed then you can use List for acc with (acc' = (y:acc)). The performance on ghc-6.6.1 with -O2 on PPC G4 applied to
main = print (length (power_list [1..22]))
real 0m8.592s user 0m7.017s sys 0m0.687s
main = print (length (powerBin [1..22]))
real 0m3.245s user 0m2.768s sys 0m0.073s
main = print (length (powerBin2 [1..22]))
real 0m3.305s user 0m2.835s sys 0m0.071s -- Chris Kuklewicz

Melissa O'Neill wrote:
BUT, it generates the output in an order that'll accommodate infinite lists, thus we can say:
power_list [1..]
-- Count in binary and use that to create power set power_list xs = loop zero where
[snip code that works lazily without wasting memory and supporting infinite lists.]
No doubt this can be coded better yet...
How about this: Start with power_list :: [a] -> [[a]] power_list [] = [[]] power_list (x:xs) = add_x (power_list xs) where add_x [] = [] add_x (y:ys) = y : (x:y) : foo ys Note that this puts the empty list first. The only change that is necessary to make this work for infinite list is to tell the compiler to assert that the recursive call does the same thing - this can be done with a lazy pattern: power_list :: [a] -> [[a]] power_list [] = [[]] power_list (x:xs) = add_x (assert_first_empty $ power_list xs) x where assert_first_empty ~([]:xs) = []:xs add_x [] _ = [] add_x (y:ys) x = y : (x:y) : add_x ys x It's safe to replace the ~([]:xs) by ~(_:xs) - this should result in slightly more efficient code (but I did no timings). Finally for lovers of oneliners, here's the same code with foldr, slightly obscured by using >>= for concatMap: power_list :: [a] -> [[a]] power_list = foldr (\x ~(_:xs) -> []:xs >>= \ys -> [ys, x:ys]) [[]] Enjoy, Bertram

Bertram Felgenhauer wrote two wonderful implementations of power_list:
power_list :: [a] -> [[a]] power_list [] = [[]] power_list (x:xs) = add_x (assert_first_empty $ power_list xs) x where assert_first_empty ~([]:xs) = []:xs add_x [] _ = [] add_x (y:ys) x = y : (x:y) : add_x ys x
It's safe to replace the ~([]:xs) by ~(_:xs) - this should result in slightly more efficient code (but I did no timings).
With GHC, it seems to make no observable difference.
Finally for lovers of oneliners, here's the same code with foldr, slightly obscured by using >>= for concatMap:
power_list :: [a] -> [[a]] power_list = foldr (\x ~(_:xs) -> []:xs >>= \ys -> [ys, x:ys]) [[]]
I loved how short and sweet this version is, but sadly with GHC it's noticeably slower than Bertram's first, more directly coded, version (1.32 seconds vs 0.55 seconds for power_list [1..24]). The two-line variant below is just over 25% faster than the above oneliner under GHC, but at 1.04 seconds, it's still bested by the explicit version: power_list :: [a] -> [[a]] power_list [] = [[]] power_list (x:xs) = [] : tail [y | ps <- power_list xs, y <- [ps, x:ps]] Anyway, we're now far from our original topic, but thanks to Bertram, we can see that power_list can be coded in a way that is memory efficient, lazy-list friendly, and (relatively) easy to read. Best Regards, Melissa.

| > power_list :: [a] -> [[a]] | > power_list = foldr (\x ~(_:xs) -> []:xs >>= \ys -> [ys, x:ys]) [[]] | | I loved how short and sweet this version is, but sadly with GHC it's | noticeably slower than Bertram's first, more directly coded, version | (1.32 seconds vs 0.55 seconds for power_list [1..24]). | | The two-line variant below is just over 25% faster than the above | oneliner under GHC, but at 1.04 seconds, it's still bested by the | explicit version: | | power_list :: [a] -> [[a]] | power_list [] = [[]] | power_list (x:xs) = [] : tail [y | ps <- power_list xs, y <- [ps, | x:ps]] | | Anyway, we're now far from our original topic, but thanks to Bertram, | we can see that power_list can be coded in a way that is memory | efficient, lazy-list friendly, and (relatively) easy to read. I wonder if it'd be worth writing up this thread into a Wiki page? Some neat programming here! Simon

Melissa O'Neill wrote:
Clearly, "simplifying" the second version of primes into the first by performing CSE actually makes the code much *worse*. This "CSE- makes-it-worse" property strikes me as "interesting".
So, is it "interesting"...? Has anyone worked on characterizing CSE space leaks (and avoiding CSE in those cases)? FWIW, it looks like others have run into the same problem, since bug #947 in GHC (from October 2006) seems to be along similar lines.
Another must-advertise-work-by-David-Sands incident. Actually, joint work with Joergen Gustavsson: Possibilities and limitations of call-by-need space improvement, ICFP'01. http://doi.acm.org/10.1145/507635.507667 Also references [9] and [10] therein. Ciao, Janis. -- Dr. Janis Voigtlaender http://wwwtcs.inf.tu-dresden.de/~voigt/ mailto:voigt@tcs.inf.tu-dresden.de
participants (7)
-
Bertram Felgenhauer
-
ChrisK
-
Dan Weston
-
Janis Voigtlaender
-
Melissa O'Neill
-
ok
-
Simon Peyton-Jones