'while' loop on mutable arrays causes stack overflow

Lemmih lemmih at gmail.com
Thu Apr 20 12:21:15 EDT 2006


On 4/20/06, Gunnar Kedenburg <gunnar at haquebright.de> wrote:
> 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
>

Implementing 'dot' without the 'while' loop and STRefs will make it
shorter and faster, btw.

--
Friendly,
  Lemmih


More information about the Glasgow-haskell-users mailing list