This library provides support for strict state threads, as
described in the PLDI '94 paper by John Launchbury and Simon Peyton
Jones ]. 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 ()
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:
freezeSTArray and thawSTArray convert mutable
arrays to and from immutable arrays. Semantically, they are identical
to copying the array and they are usually implemented that way. The
operation unsafeFreezeSTArray is a faster version of
freezeSTArray which omits the copying step. It's a safe substitute for
freezeSTArray if you don't modify the mutable array after freezing it.
thenLazyST and thenStrictST so that you can
import LazyST (say) and still use the strict instance in those
places where it matters. GHC implements LazyST and ST using different
types, so this isn't possible.ST action into an IO one, and
vice versa are also provided. Notice that coercing an IO action
into an ST action is 'lossy', since any exception raised within the
IO action will not be caught within the ST monad, as it
doesn't support (monadic) exceptions.