Copyright | Josef Svenningsson 2008-2017 (c) The University of Glasgow 1994-2000 |
---|---|
License | BSD |
Maintainer | josef.svenningsson@gmail.com, Andreas Abel |
Stability | stable |
Portability | non-portable (GHC Extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This library provides a monad transformer version of the ST monad.
Warning! This monad transformer should not be used with monads that
can contain multiple answers, like the list monad. The reason is that
the state token will be duplicated across the different answers and
this causes Bad Things to happen (such as loss of referential
transparency). Safe monads include the monads
, State
, Reader
,
Writer
and combinations of their corresponding monad transformers.Maybe
Synopsis
- data STT s m a
- runST :: Monad m => (forall s. STT s m a) -> m a
- runSTT :: Monad m => (forall s. STT s m a) -> m a
- data STRef s a
- newSTRef :: Applicative m => a -> STT s m (STRef s a)
- readSTRef :: Applicative m => STRef s a -> STT s m a
- writeSTRef :: Applicative m => STRef s a -> a -> STT s m ()
- data STArray s i e
- newSTArray :: (Ix i, Applicative m) => (i, i) -> e -> STT s m (STArray s i e)
- readSTArray :: (Ix i, Applicative m) => STArray s i e -> i -> STT s m e
- writeSTArray :: (Ix i, Applicative m) => STArray s i e -> i -> e -> STT s m ()
- boundsSTArray :: STArray s i e -> (i, i)
- numElementsSTArray :: STArray s i e -> Int
- freezeSTArray :: Applicative m => STArray s i e -> STT s m (Array i e)
- thawSTArray :: Applicative m => Array i e -> STT s m (STArray s i e)
- runSTArray :: Monad m => (forall s. STT s m (STArray s i e)) -> m (Array i e)
- unsafeReadSTArray :: Applicative m => STArray s i e -> Int -> STT s m e
- unsafeWriteSTArray :: Applicative m => STArray s i e -> Int -> e -> STT s m ()
- unsafeFreezeSTArray :: Applicative m => STArray s i e -> STT s m (Array i e)
- unsafeThawSTArray :: Applicative m => Array i e -> STT s m (STArray s i e)
- unsafeIOToSTT :: (Monad m, Functor m) => IO a -> STT s m a
- unsafeSTToIO :: STT s IO a -> IO a
- unsafeSTTToIO :: STT s IO a -> IO a
- unsafeSTRefToIORef :: STRef s a -> IORef a
- unsafeIORefToSTRef :: IORef a -> STRef s a
The ST Monad Transformer
STT
is the monad transformer providing polymorphic updateable references
Instances
runST :: Monad m => (forall s. STT s m a) -> m a Source #
Deprecated: Use runSTT instead
Executes a computation in the STT
monad transformer
runSTT :: Monad m => (forall s. STT s m a) -> m a Source #
Executes a computation in the STT
monad transformer
Mutable references
a value of type STRef s a
is a mutable variable in state thread s
,
containing a value of type a
>>>
:{
runST (do ref <- newSTRef "hello" x <- readSTRef ref writeSTRef ref (x ++ "world") readSTRef ref ) :} "helloworld"
writeSTRef :: Applicative m => STRef s a -> a -> STT s m () Source #
Modifies the value of a reference
Mutable arrays
Mutable, boxed, non-strict arrays in the ST
monad. The type
arguments are as follows:
Instances
MArray (STArray s) e (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STArray s i e -> ST s (i, i) # getNumElements :: Ix i => STArray s i e -> ST s Int newArray :: Ix i => (i, i) -> e -> ST s (STArray s i e) # newArray_ :: Ix i => (i, i) -> ST s (STArray s i e) # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STArray s i e) unsafeRead :: Ix i => STArray s i e -> Int -> ST s e unsafeWrite :: Ix i => STArray s i e -> Int -> e -> ST s () | |
MArray (STArray s) e (ST s) | |
Defined in Data.Array.Base getBounds :: Ix i => STArray s i e -> ST s (i, i) # getNumElements :: Ix i => STArray s i e -> ST s Int newArray :: Ix i => (i, i) -> e -> ST s (STArray s i e) # newArray_ :: Ix i => (i, i) -> ST s (STArray s i e) # unsafeNewArray_ :: Ix i => (i, i) -> ST s (STArray s i e) unsafeRead :: Ix i => STArray s i e -> Int -> ST s e unsafeWrite :: Ix i => STArray s i e -> Int -> e -> ST s () | |
(Applicative m, Monad m) => MArray (STArray s) e (STT s m) Source # | |
Defined in Control.Monad.ST.Trans.Internal getBounds :: Ix i => STArray s i e -> STT s m (i, i) # getNumElements :: Ix i => STArray s i e -> STT s m Int newArray :: Ix i => (i, i) -> e -> STT s m (STArray s i e) # newArray_ :: Ix i => (i, i) -> STT s m (STArray s i e) # unsafeNewArray_ :: Ix i => (i, i) -> STT s m (STArray s i e) unsafeRead :: Ix i => STArray s i e -> Int -> STT s m e unsafeWrite :: Ix i => STArray s i e -> Int -> e -> STT s m () | |
Eq (STArray s i e) | Since: base-2.1 |
newSTArray :: (Ix i, Applicative m) => (i, i) -> e -> STT s m (STArray s i e) Source #
Creates a new mutable array
readSTArray :: (Ix i, Applicative m) => STArray s i e -> i -> STT s m e Source #
Retrieves an element from the array
writeSTArray :: (Ix i, Applicative m) => STArray s i e -> i -> e -> STT s m () Source #
Modifies an element in the array
boundsSTArray :: STArray s i e -> (i, i) Source #
Returns the lowest and highest indices of the array
numElementsSTArray :: STArray s i e -> Int Source #
Returns the number of elements in the array
freezeSTArray :: Applicative m => STArray s i e -> STT s m (Array i e) Source #
Copy a mutable array and turn it into an immutable array
thawSTArray :: Applicative m => Array i e -> STT s m (STArray s i e) Source #
Copy an immutable array and turn it into a mutable array
runSTArray :: Monad m => (forall s. STT s m (STArray s i e)) -> m (Array i e) Source #
A safe way to create and work with a mutable array before returning an immutable array for later perusal. This function avoids copying the array before returning it.
Unsafe Operations
unsafeReadSTArray :: Applicative m => STArray s i e -> Int -> STT s m e Source #
unsafeWriteSTArray :: Applicative m => STArray s i e -> Int -> e -> STT s m () Source #
unsafeFreezeSTArray :: Applicative m => STArray s i e -> STT s m (Array i e) Source #
unsafeThawSTArray :: Applicative m => Array i e -> STT s m (STArray s i e) Source #
unsafeSTRefToIORef :: STRef s a -> IORef a Source #
unsafeIORefToSTRef :: IORef a -> STRef s a Source #