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

----------------------------------------------------------------------

acc2 ints = execState (mapM add2 ints) 0

add2 :: Int -> State Int ()
add2 i = do
    acc <- get
    put (acc + i)

----------------------------------------------------------------------

acc3 ints = runST (acc3' ints :: ST s Int)

acc3' ints = do
    accRef <- newSTRef 0
    mapM (add3 accRef) ints
    acc <- readSTRef accRef
    return acc

add3 accRef i = do
    modifySTRef accRef (+ i)


----------------------------------------------------------------------

test4' n = do
    let g = gen n
    accRef <- newSTRef 0
    sRef   <- newSTRef 1
    acc    <- acc4 g sRef accRef
    return acc

acc4 g sRef accRef = do
    ret <- g sRef
    case ret of
     Nothing -> do acc <- readSTRef accRef
                   return acc
     Just i  -> do add3 accRef i
                   acc4 g sRef accRef

gen n sRef = do
    s <- readSTRef sRef
    let ret = if s > n then Nothing else Just 1
    writeSTRef sRef (s + 1)
    return ret

----------------------------------------------------------------------

test1 n = acc1 $ replicate n 1
test2 n = acc2 $ replicate n 1
test3 n = acc3 $ replicate n 1
test4 n = runST (test4' n :: ST s Int)

Thanks a lot,
VO Minh Thu
_______________________________________________
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell

Reply via email to