[Haskell-cafe] multiple computations, same input

Greg Buchholz haskell at sleepingsquirrel.org
Mon Mar 27 19:59:19 EST 2006


Neil Mitchell wrote:
> I suspected that you actually wanted to do something "cleverer" with
> the list, for the sake of argument, I'm going to change >1 to p1 and
> >2 to p2 - to show how this can be done in the general case. With the
> specific information you know about >1 vs >2 you can do better, but
> this gets across the general point:
> 
> f lst = show (sumPairs (>1) (>2) lst)
> 
> sumPairs :: (Int -> Bool) -> (Int -> Bool) -> [Int] -> (Int, Int)
> sumPairs p1 p2 [] = (0, 0)
> sumPairs p1 p2 (x:xs) = (add p1 a, add p2 b)
>     where
>        (a,b) = sumPairs xs
>        add pred value = if pred x then x+value else value
> 
> [Untested, something like this should work]

    Nope.  That won't work because you end up creating huge "add" thunks
which cause end up causing a stack overflow (tested with GHC -O2).  I
think you are probably going to need strictness in order to skin this
cat in Haskell.  Here's an example that does work...

import Data.List
main = print $ para_filter_sum (> 1) (> 2) lst

twos = 2: twos
lst = take 10000000 $ [1,2,3,4,5] ++ twos

-- f lst = show (filter (> 1) lst, filter (> 2) lst)
para_filter_sum f g xs =
    foldl' (\(n,m) elem -> seq n $ seq m $
             (n+if f elem then elem else 0,
              m+if g elem then elem else 0 ) ) (0,0) xs


Greg Buchholz



More information about the Haskell-Cafe mailing list