[Haskell] Re: ST/STRef vs. IO/IORef

Iavor Diatchki iavor.diatchki at gmail.com
Wed Aug 3 17:49:48 EDT 2005


Hello, 

On 8/3/05, Srinivas Nedunuri <nedunuri at cs.utexas.edu> wrote:
> > The most obvious disadvantage is that the IO monad has no equivalent
> > of runST.
> OK, I'm missing something here. What is the big deal about runST? Can I not
> get the IO equivalent by simply running the program at the top level
> (assuming I don't have multiple threads going). Do you have a practical
> example of needing runST in several places in your program?

Here is an example (not that I am suggesting that this is how we
should write the function 'fib').  Notice the type of 'fib' --- there
are no monads, even though the implementation internally uses state.

import Control.Monad.ST
import Data.STRef

fib  :: Int -> Int
fib n = runST (do x <- newSTRef 1
                  y <- newSTRef 1
                  let loop n | n < 1 = return ()
                      loop n  = do x' <- readSTRef x
                                   y' <- readSTRef y
                                   writeSTRef x y'
                                   writeSTRef y (x' + y')
                                   loop (n-1)
                  loop n
                  readSTRef x)

-Iavor


More information about the Haskell mailing list