Copyright | (c) 2010 Galois Inc. |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | John Launchbury, john@galois.com |
Stability | experimental |
Portability | concurrency, requires STM |
Safe Haskell | None |
Language | Haskell98 |
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.
Synopsis
- data STM a
- atomically :: MonadIO io => STM a -> io a
- 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
A monad supporting atomic memory transactions.
Instances
Monad STM | Since: base-4.3.0.0 |
Functor STM | Since: base-4.3.0.0 |
Applicative STM | Since: base-4.8.0.0 |
Alternative STM | Since: base-4.8.0.0 |
MonadPlus STM | Since: base-4.3.0.0 |
atomically :: MonadIO io => STM a -> io a Source #
The atomically function allows STM to be called directly from any monad which contains IO, i.e. is a member of MonadIO.
Retry execution of the current memory transaction because it has seen
values in TVar
s which mean that it should not continue (e.g. the TVar
s
represent a shared buffer that is now empty). The implementation may
block the thread until one of the TVar
s that it has read from has been
updated. (GHC only)
Check that the boolean condition is true and, if not, retry
.
In other words, check b = unless b retry
.
Since: stm-2.1.1
Shared memory locations that support atomic memory transactions.
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 a Source #
writeTVarSTM :: TVar a -> a -> STM () Source #
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 Bool Source #
isEmptyTMVar :: MonadIO io => TMVar a -> io Bool Source #
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 a Source #
putTMVarSTM :: TMVar a -> a -> STM () Source #
readTMVarSTM :: TMVar a -> STM a Source #
swapTMVarSTM :: TMVar a -> a -> STM a Source #
tryTakeTMVarSTM :: TMVar a -> STM (Maybe a) Source #
tryPutTMVarSTM :: TMVar a -> a -> STM Bool Source #
isEmptyTMVarSTM :: TMVar a -> STM Bool Source #