Portability | concurrency, requires STM |
---|---|
Stability | experimental |
Maintainer | John Launchbury, john@galois.com |
Safe Haskell | None |
Overloads the standard operations on TVars, and TMVars as defined in Control.Concurrent.STM.
TVars and MVars are often thought of as variables to be used in the STM monad. But in practice, they should be used just as frequently (if not more so) in any IO-like monad, with STM being used purely when a new atomic transaction is being defined. Thus we reverse the naming convention, and use the plain access names when in the IO-like monad, and use an explicit STM suffix when using the variables tentatively within the STM monad itself.
TMVars are particularly valuable when used in an IO-like monad, because operations like readTMVar and modifyTMvar can guarantee the atomicity of the operation (unlike the corresponding operations over MVars).
The standard operations on TVar
and TMVar
(such as
writeTVar
or newEmptyTMVar
) are overloaded over the
MonadIO
class. A monad m
is declared an instance of
MonadIO
by defining a function
liftIO :: IO a -> m a
It also overloads the atomically
function, so that STM transactions
can be defined from within any MonadIO monad.
- data STM a
- atomically :: MonadIO io => STM a -> io a
- always :: STM Bool -> STM ()
- alwaysSucceeds :: STM a -> STM ()
- retry :: STM a
- orElse :: STM a -> STM a -> STM a
- check :: Bool -> STM ()
- catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a
- data TVar a
- newTVar :: MonadIO io => a -> io (TVar a)
- readTVar :: MonadIO io => TVar a -> io a
- writeTVar :: MonadIO io => TVar a -> a -> io ()
- registerDelay :: MonadIO io => Int -> io (TVar Bool)
- modifyTVar :: MonadIO io => TVar a -> (a -> a) -> io (a, a)
- modifyTVar_ :: MonadIO io => TVar a -> (a -> a) -> io ()
- newTVarSTM :: a -> STM (TVar a)
- readTVarSTM :: TVar a -> STM a
- writeTVarSTM :: TVar a -> a -> STM ()
- data TMVar a
- newTMVar :: MonadIO io => a -> io (TMVar a)
- newEmptyTMVar :: MonadIO io => io (TMVar a)
- takeTMVar :: MonadIO io => TMVar a -> io a
- putTMVar :: MonadIO io => TMVar a -> a -> io ()
- readTMVar :: MonadIO io => TMVar a -> io a
- swapTMVar :: MonadIO io => TMVar a -> a -> io a
- tryTakeTMVar :: MonadIO io => TMVar a -> io (Maybe a)
- tryPutTMVar :: MonadIO io => TMVar a -> a -> io Bool
- isEmptyTMVar :: MonadIO io => TMVar a -> io Bool
- modifyTMVar :: MonadIO io => TMVar a -> (a -> a) -> io (a, a)
- modifyTMVar_ :: MonadIO io => TMVar a -> (a -> a) -> io ()
- newTMVarSTM :: a -> STM (TMVar a)
- newEmptyTMVarSTM :: STM (TMVar a)
- takeTMVarSTM :: TMVar a -> STM a
- putTMVarSTM :: TMVar a -> a -> STM ()
- readTMVarSTM :: TMVar a -> STM a
- swapTMVarSTM :: TMVar a -> a -> STM a
- tryTakeTMVarSTM :: TMVar a -> STM (Maybe a)
- tryPutTMVarSTM :: TMVar a -> a -> STM Bool
- isEmptyTMVarSTM :: TMVar a -> STM Bool
Documentation
data STM a
A monad supporting atomic memory transactions.
atomically :: MonadIO io => STM a -> io aSource
The atomically function allows STM to be called directly from any monad which contains IO, i.e. is a member of MonadIO.
always is a variant of alwaysSucceeds in which the invariant is expressed as an STM Bool action that must return True. Returning False or raising an exception are both treated as invariant failures.
alwaysSucceeds :: STM a -> STM ()
alwaysSucceeds adds a new invariant that must be true when passed to alwaysSucceeds, at the end of the current transaction, and at the end of every subsequent transaction. If it fails at any of those points then the transaction violating it is aborted and the exception raised by the invariant is propagated.
Retry execution of the current memory transaction because it has seen values in TVars which mean that it should not continue (e.g. the TVars represent a shared buffer that is now empty). The implementation may block the thread until one of the TVars that it has read from has been udpated. (GHC only)
orElse :: STM a -> STM a -> STM a
Compose two alternative STM actions (GHC only). If the first action completes without retrying then it forms the result of the orElse. Otherwise, if the first action retries, then the second action is tried in its place. If both actions retry then the orElse as a whole retries.
data TVar a
Shared memory locations that support atomic memory transactions.
registerDelay :: MonadIO io => Int -> io (TVar Bool)Source
modifyTVar :: MonadIO io => TVar a -> (a -> a) -> io (a, a)Source
modifyTVar
is an atomic update operation which provides both
the former value and the newly computed value as a result.
modifyTVar_ :: MonadIO io => TVar a -> (a -> a) -> io ()Source
newTVarSTM :: a -> STM (TVar a)Source
readTVarSTM :: TVar a -> STM aSource
writeTVarSTM :: TVar a -> a -> STM ()Source
data TMVar a
A TMVar
is a synchronising variable, used
for communication between concurrent threads. It can be thought of
as a box, which may be empty or full.
newEmptyTMVar :: MonadIO io => io (TMVar a)Source
tryTakeTMVar :: MonadIO io => TMVar a -> io (Maybe a)Source
tryPutTMVar :: MonadIO io => TMVar a -> a -> io BoolSource
isEmptyTMVar :: MonadIO io => TMVar a -> io BoolSource
modifyTMVar :: MonadIO io => TMVar a -> (a -> a) -> io (a, a)Source
modifyTMVar_ :: MonadIO io => TMVar a -> (a -> a) -> io ()Source
newTMVarSTM :: a -> STM (TMVar a)Source
newEmptyTMVarSTM :: STM (TMVar a)Source
takeTMVarSTM :: TMVar a -> STM aSource
putTMVarSTM :: TMVar a -> a -> STM ()Source
readTMVarSTM :: TMVar a -> STM aSource
swapTMVarSTM :: TMVar a -> a -> STM aSource
tryTakeTMVarSTM :: TMVar a -> STM (Maybe a)Source
tryPutTMVarSTM :: TMVar a -> a -> STM BoolSource
isEmptyTMVarSTM :: TMVar a -> STM BoolSource