[Haskell-cafe] eager/strict eval katas

Dan Weston westondan at imageworks.com
Wed Dec 12 15:46:07 EST 2007


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/average.hs 

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" <felipe.lessa at gmail.com>*
> 
> 12/12/2007 02:24 PM
> 
> 	
> To
> 	Thomas Hartman/ext/dbcom at DBAmericas
> cc
> 	haskell-cafe at haskell.org
> Subject
> 	Re: [Haskell-cafe] eager/strict eval katas
> 
> 
> 	
> 
> 
> 
> 
> 
> On Dec 12, 2007 2:31 PM, Thomas Hartman <thomas.hartman at db.com> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list