'while' loop on mutable arrays causes stack overflow

Gunnar Kedenburg gunnar at haquebright.de
Thu Apr 20 08:29:29 EDT 2006


Hello,

a friend and I were recently experimenting with mutable arrays. We tried
to implement a simple dot product on STUArrays using a 'while' loop.
Unfortunately, every implementation we produced caused a stack overflow.
Switching to other implementations of 'while' or to IOUArrays did not
help us.

We were using ghc-6.4.1 on Linux x86, with gcc 3.3.6. It runs perfectly,
and is actually quite fast, when we increase the stack space. :)

> import Control.Monad.ST
> import Data.STRef
> import Data.Array.ST
> import Control.Monad.Fix
> import Control.Monad
>
> while :: STRef s Bool -> ST s () -> ST s ()
> while b c = readSTRef b >>= \v -> when v (c >> while b c)
>
> dot :: STUArray s Int Double -> STUArray s Int Double -> ST s Double
> dot x y = do
>           let (l,r) = bounds x
>           a <- newSTRef 0.0
>           e <- newSTRef l
>           b <- newSTRef True
>           while b (do
>                      ev <- readSTRef e
>                      av <- readSTRef a
>                      xe <- readArray x ev
>                      ye <- readArray y ev
>                      writeSTRef b (ev<r)
>                      writeSTRef e (ev+1)
>                      writeSTRef a (av+xe*ye))
>           readSTRef a
>
> main = do
>        let d = runST (do
>                         x <- newArray (1, 1000000) 1.0
>                         y <- newArray (1, 1000000) 2.0
>                         dot x y)
>        putStrLn $ show d

Unfortunately, I did not keep every 'while' implementation we tried,
just this one:

> while b c = fix (\d -> readSTRef b >>=
>               (\v -> if v then c >> d else return ()))

We also changed the 'dot' code to use a 'for' loop instead, using
IOUArrays in this case:

> for :: Int -> IO () -> IO ()
> for 0 c = return ()
> for n c = c >> for (n-1) c

Needless to say, it did not help.

Any hints why the stack overflows would be greatly appreciated.

Thanks,
Gunnar.



More information about the Glasgow-haskell-users mailing list