Copyright | (c) 2016--2017 Michael Walker |
---|---|
License | MIT |
Maintainer | Michael Walker <mike@barrucadu.co.uk> |
Stability | experimental |
Portability | CPP, RankNTypes, StandaloneDeriving, TemplateHaskell, TypeFamilies |
Safe Haskell | None |
Language | Haskell2010 |
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).
Deriving instances: If you have a newtype wrapper around a type
with an existing MonadSTM
instance, you should be able to derive
an instance for your type automatically, in simple cases.
For example:
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE UndecidableInstances #-} data Env = Env newtype MyMonad m a = MyMonad { runMyMonad :: ReaderT Env m a } deriving (Functor, Applicative, Monad, Alternative, MonadPlus) deriving instance MonadThrow m => MonadThrow (MyMonad m) deriving instance MonadCatch m => MonadCatch (MyMonad m) deriving instance MonadSTM m => MonadSTM (MyMonad m)
Do not be put off by the use of UndecidableInstances
, it is safe
here.
Deviations: An instance of MonadSTM
is not required to be a
MonadFix
, unlike STM
.
Synopsis
- 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
- data IsSTM m a
- toIsSTM :: MonadSTM m => m a -> IsSTM m a
- fromIsSTM :: MonadSTM m => IsSTM m a -> m 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
type TVar stm :: * -> * Source #
The mutable reference type. These behave like TVar
s, in that
they always contain a value and updates are non-blocking and
synchronised.
Since: 1.0.0.0
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 TVar
s 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 m => MonadSTM (IsSTM m) Source # | |
Defined in Control.Monad.STM.Class | |
(MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
MonadSTM stm => MonadSTM (StateT s stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
MonadSTM stm => MonadSTM (IdentityT stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
MonadSTM stm => MonadSTM (StateT s stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
(MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
MonadSTM stm => MonadSTM (ReaderT r stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
(MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class | |
(MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # | Since: 1.0.0.0 |
Defined in Control.Monad.STM.Class |
retry :: MonadSTM stm => stm a Source #
Retry execution of this transaction because it has seen values in
TVar
s that it shouldn't have. This will result in the thread
running the transaction being blocked until any TVar
s 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 retry
s, run the second
instead.
This is just mplus
.
Since: 1.2.0.0
throwSTM :: (MonadSTM stm, Exception e) => e -> stm a Source #
Throw an exception. This aborts the transaction and propagates the exception.
Since: 1.0.0.0
catchSTM :: (MonadSTM stm, Exception e) => stm a -> (e -> stm a) -> stm a Source #
Handling exceptions from throwSTM
.
Since: 1.0.0.0
Utilities for type shenanigans
A value of type IsSTM m a
can only be constructed if m
has a
MonadSTM
instance.
Since: 1.2.2.0
Instances
Monad m => Monad (IsSTM m) Source # | |
Functor m => Functor (IsSTM m) Source # | |
MonadFail m => MonadFail (IsSTM m) Source # | Since: 1.8.0.0 |
Defined in Control.Monad.STM.Class | |
Applicative m => Applicative (IsSTM m) Source # | |
Alternative m => Alternative (IsSTM m) Source # | |
MonadPlus m => MonadPlus (IsSTM m) Source # | |
MonadThrow m => MonadThrow (IsSTM m) Source # | |
Defined in Control.Monad.STM.Class | |
MonadCatch m => MonadCatch (IsSTM m) Source # | |
MonadSTM m => MonadSTM (IsSTM m) Source # | |
Defined in Control.Monad.STM.Class | |
type TVar (IsSTM m) Source # | |
Defined in Control.Monad.STM.Class |