4.31. ST

This library provides support for strict state threads, as described in the PLDI '94 paper by John Launchbury and Simon Peyton Jones [LazyStateThreads]. In addition to the monad ST, it also provides mutable variables STRef and mutable arrays STArray.

module ST( module ST, module Monad ) where
import Monad

data ST s a        -- abstract type
runST              :: forall a. (forall s. ST s a) -> a
fixST              :: (a -> ST s a) -> ST s a
unsafeInterleaveST :: ST s a -> ST s a
instance Functor (ST s)
instance Monad   (ST s)

data STRef s a     -- mutable variables in state thread s
                   -- containing values of type a.
newSTRef           :: a -> ST s (STRef s a)
readSTRef          :: STRef s a -> ST s a
writeSTRef         :: STRef s a -> a -> ST s ()
modifySTRef        :: STRef s a -> (a -> a) -> ST s ()

-- deprecated, use modifySTRef
updateSTRef        :: STRef s a -> (a -> a) -> ST s ()
instance Eq (STRef s a)

data STArray s ix elt -- mutable arrays in state thread s
                      -- indexed by values of type ix
                      -- containing values of type a.
newSTArray          :: Ix ix => (ix,ix) -> elt -> ST s (STArray s ix elt)
boundsSTArray       :: Ix ix => STArray s ix elt -> (ix, ix)
readSTArray         :: Ix ix => STArray s ix elt -> ix -> ST s elt
writeSTArray        :: Ix ix => STArray s ix elt -> ix -> elt -> ST s ()
thawSTArray         :: Ix ix => Array ix elt -> ST s (STArray s ix elt)
freezeSTArray       :: Ix ix => STArray s ix elt -> ST s (Array ix elt)
unsafeFreezeSTArray :: Ix ix => STArray s ix elt -> ST s (Array ix elt)  
instance Eq (STArray s ix elt)

unsafeIOToST	    :: IO   a -> ST s a
stToIO              :: ST s a -> IO a

Notes: