[Haskell-cafe] Re: [Haskell] how to 'accumulate' values efficiently (time and space) ?

Donald Bruce Stewart dons at cse.unsw.edu.au
Mon May 8 04:38:19 EDT 2006


noteed:
> Hi all,
> 
> the problem is simple but i can't do it :
> 
> I want to generate some values and 'accumulate' them. The meaning of
> 'accumulating' is not so important. The only point is that to
> 'accumulate' the values, I only have to know one value and the
> accumulator (and not all the values).
> 
> The most simple example is that of adding a list of numbers.
> 
> I thought that I could use a haskell list to represent the values
> so I could use foldr or mapM to do the accumulation (and not an
> imperative-style loop).
> 
> Below are four attempts to solve the problem. It's not solved : in
> ghci, I have '*** Exception: stack overflow' with 'test1 5000000'.
> 
> 5000000 is not so much for my application.
> 
> How can I achieve what I want (and efficiently)?
> ---------------------------------------------------------------------}
> 
> import Control.Monad.State
> import Control.Monad.ST
> import Data.STRef
> 
> acc1, acc2, acc3 :: [Int] -> Int
> 
> ----------------------------------------------------------------------
> 
> acc1 ints = foldr (+) 0 ints

Strictify the accumulator?

    Prelude List Data.List> foldl1 (+) (replicate 5000000 1)
    *** Exception: stack overflow

versus

    Prelude List Data.List> foldl1' (+) (replicate 5000000 1)
    5000000

(Redirected to haskell-cafe@)

-- Don


More information about the Haskell-Cafe mailing list