eager/strict eval katas

I'm trying to get a better handle on eager/strict eval in haskell, and a great way to do this is by building up from simple exercises to harder exercises. So far I have exercise 1) add the integers [1..10^6] (stack overflows if you do a naive fold, as described on wiki) exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.) anybody got other suggestions, or links to places where eager eval is required to solve simply stated problems? or exercises that demystify doing eager IO/eager whatever monad, where that is required? Also am I correct that the terms eager and strict can be used more or less interchangeably in this problem space? Tired of this folk wisdom that haskell is only for the elite because getting around stack overflow from lazy eval is impossible to teach to newbies. t. --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

On Dec 12, 2007 2:31 PM, Thomas Hartman
exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
What is wrong with Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]] 1999999.0 Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2. The naive Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs) Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg [1..n], n) | n <- [1..]] works for me as well, only terribly slower (of course). Note that I used foldl' for sum assuming the exercise 1 was already done =). How did you solve this problem with a fold? I see you can use unfoldr: Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing else Just (x, (x+1,s+x,k+10^6))) (2,1,10^6) I'm thinking about a way of folding [1..], but this can't be a left fold (or else it would never stop), nor can it be a right fold (or else we wouldn't get the sums already done). What am I missing? Cheers, -- Felipe.

Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2
fair enough.
But I believe if I restate the problem so that you need to find the
average of an arbitrary list, your clever trick doesn't work and we need
eager eval or we blow the stack.
Also... on second thought, I actually solved a slightly different problem
than what I originally said: the problem of detecting when the moving
average of an increasing list is greater than 10^6; but my solution
doesn't give the index of the list element that bumped the list over the
average. However I suspect my code could be tweaked to do that (still
playing around with it):
Also I actually used a strict scan not a strict fold and... ach, oh well.
As you see I wrote a customized version of foldl' that is strict on the
tuple for this to work. I don't think this is necessarily faster than what
you did (haven't quite grokked your use of unfold), but it does have the
nice property of doing everything in one one fold step (or one scan step I
guess, but isn't a scan
http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict...
t.
t1 = average_greater_than (10^7) [1..]
average_greater_than max xs = find (>max) $ averages xs
averages = map fst . myscanl' lAccumAvg (0,0)
average = fst . myfoldl' lAccumAvg (0,0)
lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1))
where n1 = n+1
myfoldl' f (!l,!r) [] = (l,r)
myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs )
where q = (l,r) `f` x
myscanl f z [] = z : []
myscanl f z (x:xs) = z : myscanl f (f z x) xs
myscanl' f (!l,!r) [] = (l,r) : []
myscanl' f (!l,!r) (x:xs) = (l,r) : myscanl' f q xs
where q = (l,r) `f` x
"Felipe Lessa"
exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
What is wrong with Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]] 1999999.0 Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2. The naive Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs) Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg [1..n], n) | n <- [1..]] works for me as well, only terribly slower (of course). Note that I used foldl' for sum assuming the exercise 1 was already done =). How did you solve this problem with a fold? I see you can use unfoldr: Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing else Just (x, (x+1,s+x,k+10^6))) (2,1,10^6) I'm thinking about a way of folding [1..], but this can't be a left fold (or else it would never stop), nor can it be a right fold (or else we wouldn't get the sums already done). What am I missing? Cheers, -- Felipe. --- This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.

Thomas Hartman wrote:
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2
fair enough.
But I believe if I restate the problem so that you need to find the average of an arbitrary list, your clever trick doesn't work and we need eager eval or we blow the stack.
Not true: Prelude Data.List> let f a = (\(a,b,c)->c) . head . dropWhile (\(s,n,_) -> s <=n*a) . scanl (\(s,n,_) x ->(s+x,n+1,x)) (0,0,0) in f (10^5) [1,3..] 200001
Also... on second thought, I actually solved a slightly different problem than what I originally said: the problem of detecting when the moving average of an increasing list is greater than 10^6; but my solution doesn't give the index of the list element that bumped the list over the average. However I suspect my code could be tweaked to do that (still playing around with it):
Also I actually used a strict scan not a strict fold and... ach, oh well.
scanl above is not strict in its second argument. The data dependencies cause the strictness. Cf: Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined)) 1
As you see I wrote a customized version of foldl' that is strict on the tuple for this to work. I don't think this is necessarily faster than what you did (haven't quite grokked your use of unfold), but it does have the nice property of doing everything in one one fold step (or one scan step I guess, but isn't a scan
http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict...
You have Prelude Control.Arrow Data.List> let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000] *** Exception: stack overflow -- This fails in 100 sec Try this. It is not foldl' that needs to be strict, but the function folded: Prelude Data.List> let avg5 = uncurry (/) . foldl' (\(!s,!n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000] You will need -fbang-patterns for this (there are other ways to do this in Haskell 98 though).
t.
t1 = average_greater_than (10^7) [1..]
average_greater_than max xs = find (>max) $ averages xs
averages = map fst . myscanl' lAccumAvg (0,0) average = fst . myfoldl' lAccumAvg (0,0) lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1)) where n1 = n+1
myfoldl' f (!l,!r) [] = (l,r) myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs ) where q = (l,r) `f` x
myscanl f z [] = z : [] myscanl f z (x:xs) = z : myscanl f (f z x) xs
myscanl' f (!l,!r) [] = (l,r) : [] myscanl' f (!l,!r) (x:xs) = (l,r) : myscanl' f q xs where q = (l,r) `f` x
*"Felipe Lessa"
* 12/12/2007 02:24 PM
To Thomas Hartman/ext/dbcom@DBAmericas cc haskell-cafe@haskell.org Subject Re: [Haskell-cafe] eager/strict eval katas
On Dec 12, 2007 2:31 PM, Thomas Hartman
wrote: exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
What is wrong with
Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]] 1999999.0
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2. The naive
Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs) Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg [1..n], n) | n <- [1..]]
works for me as well, only terribly slower (of course). Note that I used foldl' for sum assuming the exercise 1 was already done =). How did you solve this problem with a fold? I see you can use unfoldr:
Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing else Just (x, (x+1,s+x,k+10^6))) (2,1,10^6)
I'm thinking about a way of folding [1..], but this can't be a left fold (or else it would never stop), nor can it be a right fold (or else we wouldn't get the sums already done). What am I missing?
Cheers,
-- Felipe.
---
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Dan Weston wrote:
scanl above is not strict in its second argument. The data dependencies cause the strictness. Cf:
Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined)) 1
The first claim is of course false, nore would the example show it anyway. scanl is not strict in its third argument (I forgot about the initial value as the second argument): Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (\x y -> 5) 8 z [8,5,5,5,5,5] It is the data dependence in the first argument of scanl that would make the above strict: Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (+) 8 z [8,9,13,*** Exception: Prelude.undefined Also note that it is better not to introduce the / operator in your test, as it fails with large numbers. Multiply both sides by the denominator before the comparison and leave everything as Num a instead of Floating a. You can do the division at the end.
Thomas Hartman wrote:
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2
fair enough.
But I believe if I restate the problem so that you need to find the average of an arbitrary list, your clever trick doesn't work and we need eager eval or we blow the stack.
Not true:
Prelude Data.List> let f a = (\(a,b,c)->c) . head . dropWhile (\(s,n,_) -> s <=n*a) . scanl (\(s,n,_) x ->(s+x,n+1,x)) (0,0,0) in f (10^5) [1,3..] 200001
Also... on second thought, I actually solved a slightly different problem than what I originally said: the problem of detecting when the moving average of an increasing list is greater than 10^6; but my solution doesn't give the index of the list element that bumped the list over the average. However I suspect my code could be tweaked to do that (still playing around with it):
Also I actually used a strict scan not a strict fold and... ach, oh well.
scanl above is not strict in its second argument. The data dependencies cause the strictness. Cf:
Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined)) 1
As you see I wrote a customized version of foldl' that is strict on the tuple for this to work. I don't think this is necessarily faster than what you did (haven't quite grokked your use of unfold), but it does have the nice property of doing everything in one one fold step (or one scan step I guess, but isn't a scan
http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict...
You have
Prelude Control.Arrow Data.List> let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000] *** Exception: stack overflow -- This fails in 100 sec
Try this. It is not foldl' that needs to be strict, but the function folded:
Prelude Data.List> let avg5 = uncurry (/) . foldl' (\(!s,!n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000]
You will need -fbang-patterns for this (there are other ways to do this in Haskell 98 though).
t.
t1 = average_greater_than (10^7) [1..]
average_greater_than max xs = find (>max) $ averages xs
averages = map fst . myscanl' lAccumAvg (0,0) average = fst . myfoldl' lAccumAvg (0,0) lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1)) where n1 = n+1
myfoldl' f (!l,!r) [] = (l,r) myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs ) where q = (l,r) `f` x
myscanl f z [] = z : [] myscanl f z (x:xs) = z : myscanl f (f z x) xs
myscanl' f (!l,!r) [] = (l,r) : [] myscanl' f (!l,!r) (x:xs) = (l,r) : myscanl' f q xs where q = (l,r) `f` x
*"Felipe Lessa"
* 12/12/2007 02:24 PM
To Thomas Hartman/ext/dbcom@DBAmericas cc haskell-cafe@haskell.org Subject Re: [Haskell-cafe] eager/strict eval katas
On Dec 12, 2007 2:31 PM, Thomas Hartman
wrote: exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
What is wrong with
Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]] 1999999.0
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2. The naive
Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs) Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg [1..n], n) | n <- [1..]]
works for me as well, only terribly slower (of course). Note that I used foldl' for sum assuming the exercise 1 was already done =). How did you solve this problem with a fold? I see you can use unfoldr:
Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing else Just (x, (x+1,s+x,k+10^6))) (2,1,10^6)
I'm thinking about a way of folding [1..], but this can't be a left fold (or else it would never stop), nor can it be a right fold (or else we wouldn't get the sums already done). What am I missing?
Cheers,
-- Felipe.
---
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

great advice. I played with this a bit, desugared to haskell 98, and got
-- okay for 1..10^6, not ok (stack overflows) if either the fold or g
is left lazy.
-- Thanks, Dan Weston.
avg6 = uncurry (/) . foldl' g (0,0)
where g (!sum,!count) next = ( (sum+next),(count+1))
-- same thing, in haskell98 (works without LANGUAGE BangPatterns)
-- thanks #haskell.oerjan
avg7 = uncurry (/) . foldl' g (0,0)
where g (sum,count) next = sum `seq` count `seq` ( (sum+next),(count+1))
t = avg7 testlist
testlist = [1..10^6]
2007/12/12, Dan Weston
Dan Weston wrote:
scanl above is not strict in its second argument. The data dependencies cause the strictness. Cf:
Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined)) 1
The first claim is of course false, nore would the example show it anyway.
scanl is not strict in its third argument (I forgot about the initial value as the second argument):
Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (\x y -> 5) 8 z [8,5,5,5,5,5]
It is the data dependence in the first argument of scanl that would make the above strict:
Prelude Data.List> let z = [1,4,undefined,8,9] in scanl (+) 8 z [8,9,13,*** Exception: Prelude.undefined
Also note that it is better not to introduce the / operator in your test, as it fails with large numbers. Multiply both sides by the denominator before the comparison and leave everything as Num a instead of Floating a. You can do the division at the end.
Thomas Hartman wrote:
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2
fair enough.
But I believe if I restate the problem so that you need to find the average of an arbitrary list, your clever trick doesn't work and we need eager eval or we blow the stack.
Not true:
Prelude Data.List> let f a = (\(a,b,c)->c) . head . dropWhile (\(s,n,_) -> s <=n*a) . scanl (\(s,n,_) x ->(s+x,n+1,x)) (0,0,0) in f (10^5) [1,3..] 200001
Also... on second thought, I actually solved a slightly different problem than what I originally said: the problem of detecting when the moving average of an increasing list is greater than 10^6; but my solution doesn't give the index of the list element that bumped the list over the average. However I suspect my code could be tweaked to do that (still playing around with it):
Also I actually used a strict scan not a strict fold and... ach, oh well.
scanl above is not strict in its second argument. The data dependencies cause the strictness. Cf:
Prelude> head ([1,3] ++ head ((scanl undefined undefined) undefined)) 1
As you see I wrote a customized version of foldl' that is strict on the tuple for this to work. I don't think this is necessarily faster than what you did (haven't quite grokked your use of unfold), but it does have the nice property of doing everything in one one fold step (or one scan step I guess, but isn't a scan
http://thomashartman-learning.googlecode.com/svn/trunk/haskell/lazy-n-strict...
You have
Prelude Control.Arrow Data.List> let avg5 = uncurry (/) . foldl' (\(s,n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000] *** Exception: stack overflow -- This fails in 100 sec
Try this. It is not foldl' that needs to be strict, but the function folded:
Prelude Data.List> let avg5 = uncurry (/) . foldl' (\(!s,!n) x -> (s + x,n + 1)) (0,0) in avg5 [1..10000000]
You will need -fbang-patterns for this (there are other ways to do this in Haskell 98 though).
t.
t1 = average_greater_than (10^7) [1..]
average_greater_than max xs = find (>max) $ averages xs
averages = map fst . myscanl' lAccumAvg (0,0) average = fst . myfoldl' lAccumAvg (0,0) lAccumAvg (!avg,!n) r = ( (avg*n/n1) + (r/n1),(n1)) where n1 = n+1
myfoldl' f (!l,!r) [] = (l,r) myfoldl' f (!l,!r) (x:xs) = ( myfoldl' f q xs ) where q = (l,r) `f` x
myscanl f z [] = z : [] myscanl f z (x:xs) = z : myscanl f (f z x) xs
myscanl' f (!l,!r) [] = (l,r) : [] myscanl' f (!l,!r) (x:xs) = (l,r) : myscanl' f q xs where q = (l,r) `f` x
*"Felipe Lessa"
* 12/12/2007 02:24 PM
To Thomas Hartman/ext/dbcom@DBAmericas cc haskell-cafe@haskell.org Subject Re: [Haskell-cafe] eager/strict eval katas
On Dec 12, 2007 2:31 PM, Thomas Hartman
wrote: exercise 2) find the first integer such that average of [1..n] is > [10^6] (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
What is wrong with
Prelude> snd . head $ dropWhile ((< 10^6) . fst) [((n+1) / 2, n) | n <- [1..]] 1999999.0
Note that 1 + ··· + n = n * (n+1) / 2, so the average of [1..n] is (n+1) / 2. The naive
Prelude Data.List> let avg xs = foldl' (+) 0 xs / (fromIntegral $ length xs) Prelude Data.List> snd . head $ dropWhile ((< 10^6) . fst) [(avg [1..n], n) | n <- [1..]]
works for me as well, only terribly slower (of course). Note that I used foldl' for sum assuming the exercise 1 was already done =). How did you solve this problem with a fold? I see you can use unfoldr:
Prelude Data.List> last $ unfoldr (\(x,s,k) -> if s >= k then Nothing else Just (x, (x+1,s+x,k+10^6))) (2,1,10^6)
I'm thinking about a way of folding [1..], but this can't be a left fold (or else it would never stop), nor can it be a right fold (or else we wouldn't get the sums already done). What am I missing?
Cheers,
-- Felipe.
---
This e-mail may contain confidential and/or privileged information. If you are not the intended recipient (or have received this e-mail in error) please notify the sender immediately and destroy this e-mail. Any unauthorized copying, disclosure or distribution of the material in this e-mail is strictly forbidden.
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi Thomas,
On Dec 12, 2007 5:31 PM, Thomas Hartman
(solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
Might it be worthwhile considering the use of a custom strict pair type instead of rewriting the strict fold functions? I.e., define data Pair a b = Pair !a !b and then use ordinary foldl' and foldr' on that. Best, - Benja

benja.fallenstein:
Hi Thomas,
On Dec 12, 2007 5:31 PM, Thomas Hartman
wrote: (solution involves building an accum list of (average,listLength) tuples. again you can't do a naive fold due to stack overflow, but in this case even strict foldl' from data.list isn't "strict enough", I had to define my own custom fold to be strict on the tuples.)
Might it be worthwhile considering the use of a custom strict pair type instead of rewriting the strict fold functions? I.e., define
data Pair a b = Pair !a !b
and then use ordinary foldl' and foldr' on that.
And no need to even use custom ones, just use the library strict pairs, http://hackage.haskell.org/packages/archive/strict/0.2/doc/html/Data-Strict-... Reuse! Reuse!

On Dec 12, 2007 9:58 PM, Don Stewart
And no need to even use custom ones, just use the library strict pairs,
http://hackage.haskell.org/packages/archive/strict/0.2/doc/html/Data-Strict-...
Oh, good! :) 'nother Haskell lesson learned. Thanks, - Benja
participants (6)
-
Benja Fallenstein
-
Dan Weston
-
Don Stewart
-
Felipe Lessa
-
Thomas Hartman
-
Thomas Hartman