| Copyright | (c) 2016 Michael Walker |
|---|---|
| License | MIT |
| Maintainer | Michael Walker <mike@barrucadu.co.uk> |
| Stability | experimental |
| Portability | CPP, RankNTypes, TemplateHaskell, TypeFamilies |
| Safe Haskell | Safe |
| Language | Haskell2010 |
Control.Monad.STM.Class
Description
This module provides an abstraction over STM, which can be used
with MonadConc.
This module only defines the STM class; you probably want to
import Control.Concurrent.Classy.STM (which exports
Control.Monad.STM.Class).
Deviations: An instance of MonadSTM is not required to be a
MonadFix, unlike STM. The always and alwaysSucceeds
functions are not provided; if you need these file an issue and
I'll look into it.
- class (MonadCatch stm, MonadPlus stm) => MonadSTM stm where
- retry :: MonadSTM stm => stm a
- check :: MonadSTM stm => Bool -> stm ()
- orElse :: MonadSTM stm => stm a -> stm a -> stm a
- throwSTM :: (MonadSTM stm, Exception e) => e -> stm a
- catchSTM :: (MonadSTM stm, Exception e) => stm a -> (e -> stm a) -> stm a
Documentation
class (MonadCatch stm, MonadPlus stm) => MonadSTM stm where Source #
MonadSTM is an abstraction over STM.
This class does not provide any way to run transactions, rather
each MonadConc has an associated MonadSTM from which it can
atomically run a transaction.
Since: 1.2.0.0
Associated Types
type TVar stm :: * -> * Source #
The mutable reference type. These behave like TVars, in that
they always contain a value and updates are non-blocking and
synchronised.
Since: 1.0.0.0
Methods
newTVar :: a -> stm (TVar stm a) Source #
Create a new TVar containing the given value.
newTVar = newTVarN ""
Since: 1.0.0.0
newTVarN :: String -> a -> stm (TVar stm a) Source #
Create a new TVar containing the given value, but it is
given a name which may be used to present more useful debugging
information.
If an empty name is given, a counter starting from 0 is used. If
names conflict, successive TVars with the same name are given
a numeric suffix, counting up from 1.
newTVarN _ = newTVar
Since: 1.0.0.0
readTVar :: TVar stm a -> stm a Source #
Return the current value stored in a TVar.
Since: 1.0.0.0
writeTVar :: TVar stm a -> a -> stm () Source #
Write the supplied value into the TVar.
Since: 1.0.0.0
Instances
| MonadSTM STM Source # | Since: 1.0.0.0 |
| (MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # | Since: 1.0.0.0 |
| MonadSTM stm => MonadSTM (StateT s stm) Source # | Since: 1.0.0.0 |
| MonadSTM stm => MonadSTM (IdentityT * stm) Source # | Since: 1.0.0.0 |
| MonadSTM stm => MonadSTM (StateT s stm) Source # | Since: 1.0.0.0 |
| (MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # | Since: 1.0.0.0 |
| MonadSTM stm => MonadSTM (ReaderT * r stm) Source # | Since: 1.0.0.0 |
| (MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # | Since: 1.0.0.0 |
| (MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # | Since: 1.0.0.0 |
retry :: MonadSTM stm => stm a Source #
Retry execution of this transaction because it has seen values in
TVars that it shouldn't have. This will result in the thread
running the transaction being blocked until any TVars referenced
in it have been mutated.
This is just mzero.
Since: 1.2.0.0
check :: MonadSTM stm => Bool -> stm () Source #
Check whether a condition is true and, if not, call retry.
Since: 1.0.0.0
orElse :: MonadSTM stm => stm a -> stm a -> stm a Source #
Run the first transaction and, if it retrys, run the second
instead.
This is just mplus.
Since: 1.2.0.0