concurrency-1.1.1.0: Typeclasses, functions, and data types for concurrency and STM.

Copyright(c) 2016 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityCPP, RankNTypes, TemplateHaskell, TypeFamilies
Safe HaskellSafe
LanguageHaskell2010

Control.Monad.STM.Class

Contents

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 an Alternative, MonadPlus, and MonadFix, unlike STM. The always and alwaysSucceeds functions are not provided; if you need these file an issue and I'll look into it.

Synopsis

Documentation

class MonadCatch 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.

Minimal complete definition

retry, orElse, (newTVar | newTVarN), readTVar, writeTVar

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.

Methods

retry :: 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.

orElse :: stm a -> stm a -> stm a Source #

Run the first transaction and, if it retrys, run the second instead. If the monad is an instance of 'Alternative'/'MonadPlus', orElse should be the '(|)'/'mplus' function.

newTVar :: a -> stm (TVar stm a) Source #

Create a new TVar containing the given value.

newTVar = newTVarN ""

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

readTVar :: TVar stm a -> stm a Source #

Return the current value stored in a TVar.

writeTVar :: TVar stm a -> a -> stm () Source #

Write the supplied value into the TVar.

Instances

MonadSTM STM Source # 

Associated Types

type TVar (STM :: * -> *) :: * -> * Source #

Methods

retry :: STM a Source #

orElse :: STM a -> STM a -> STM a Source #

newTVar :: a -> STM (TVar STM a) Source #

newTVarN :: String -> a -> STM (TVar STM a) Source #

readTVar :: TVar STM a -> STM a Source #

writeTVar :: TVar STM a -> a -> STM () Source #

MonadSTM stm => MonadSTM (StateT s stm) Source # 

Associated Types

type TVar (StateT s stm :: * -> *) :: * -> * Source #

Methods

retry :: StateT s stm a Source #

orElse :: StateT s stm a -> StateT s stm a -> StateT s stm a Source #

newTVar :: a -> StateT s stm (TVar (StateT s stm) a) Source #

newTVarN :: String -> a -> StateT s stm (TVar (StateT s stm) a) Source #

readTVar :: TVar (StateT s stm) a -> StateT s stm a Source #

writeTVar :: TVar (StateT s stm) a -> a -> StateT s stm () Source #

MonadSTM stm => MonadSTM (StateT s stm) Source # 

Associated Types

type TVar (StateT s stm :: * -> *) :: * -> * Source #

Methods

retry :: StateT s stm a Source #

orElse :: StateT s stm a -> StateT s stm a -> StateT s stm a Source #

newTVar :: a -> StateT s stm (TVar (StateT s stm) a) Source #

newTVarN :: String -> a -> StateT s stm (TVar (StateT s stm) a) Source #

readTVar :: TVar (StateT s stm) a -> StateT s stm a Source #

writeTVar :: TVar (StateT s stm) a -> a -> StateT s stm () Source #

(MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # 

Associated Types

type TVar (WriterT w stm :: * -> *) :: * -> * Source #

Methods

retry :: WriterT w stm a Source #

orElse :: WriterT w stm a -> WriterT w stm a -> WriterT w stm a Source #

newTVar :: a -> WriterT w stm (TVar (WriterT w stm) a) Source #

newTVarN :: String -> a -> WriterT w stm (TVar (WriterT w stm) a) Source #

readTVar :: TVar (WriterT w stm) a -> WriterT w stm a Source #

writeTVar :: TVar (WriterT w stm) a -> a -> WriterT w stm () Source #

(MonadSTM stm, Monoid w) => MonadSTM (WriterT w stm) Source # 

Associated Types

type TVar (WriterT w stm :: * -> *) :: * -> * Source #

Methods

retry :: WriterT w stm a Source #

orElse :: WriterT w stm a -> WriterT w stm a -> WriterT w stm a Source #

newTVar :: a -> WriterT w stm (TVar (WriterT w stm) a) Source #

newTVarN :: String -> a -> WriterT w stm (TVar (WriterT w stm) a) Source #

readTVar :: TVar (WriterT w stm) a -> WriterT w stm a Source #

writeTVar :: TVar (WriterT w stm) a -> a -> WriterT w stm () Source #

MonadSTM stm => MonadSTM (IdentityT * stm) Source # 

Associated Types

type TVar (IdentityT * stm :: * -> *) :: * -> * Source #

Methods

retry :: IdentityT * stm a Source #

orElse :: IdentityT * stm a -> IdentityT * stm a -> IdentityT * stm a Source #

newTVar :: a -> IdentityT * stm (TVar (IdentityT * stm) a) Source #

newTVarN :: String -> a -> IdentityT * stm (TVar (IdentityT * stm) a) Source #

readTVar :: TVar (IdentityT * stm) a -> IdentityT * stm a Source #

writeTVar :: TVar (IdentityT * stm) a -> a -> IdentityT * stm () Source #

MonadSTM stm => MonadSTM (ReaderT * r stm) Source # 

Associated Types

type TVar (ReaderT * r stm :: * -> *) :: * -> * Source #

Methods

retry :: ReaderT * r stm a Source #

orElse :: ReaderT * r stm a -> ReaderT * r stm a -> ReaderT * r stm a Source #

newTVar :: a -> ReaderT * r stm (TVar (ReaderT * r stm) a) Source #

newTVarN :: String -> a -> ReaderT * r stm (TVar (ReaderT * r stm) a) Source #

readTVar :: TVar (ReaderT * r stm) a -> ReaderT * r stm a Source #

writeTVar :: TVar (ReaderT * r stm) a -> a -> ReaderT * r stm () Source #

(MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # 

Associated Types

type TVar (RWST r w s stm :: * -> *) :: * -> * Source #

Methods

retry :: RWST r w s stm a Source #

orElse :: RWST r w s stm a -> RWST r w s stm a -> RWST r w s stm a Source #

newTVar :: a -> RWST r w s stm (TVar (RWST r w s stm) a) Source #

newTVarN :: String -> a -> RWST r w s stm (TVar (RWST r w s stm) a) Source #

readTVar :: TVar (RWST r w s stm) a -> RWST r w s stm a Source #

writeTVar :: TVar (RWST r w s stm) a -> a -> RWST r w s stm () Source #

(MonadSTM stm, Monoid w) => MonadSTM (RWST r w s stm) Source # 

Associated Types

type TVar (RWST r w s stm :: * -> *) :: * -> * Source #

Methods

retry :: RWST r w s stm a Source #

orElse :: RWST r w s stm a -> RWST r w s stm a -> RWST r w s stm a Source #

newTVar :: a -> RWST r w s stm (TVar (RWST r w s stm) a) Source #

newTVarN :: String -> a -> RWST r w s stm (TVar (RWST r w s stm) a) Source #

readTVar :: TVar (RWST r w s stm) a -> RWST r w s stm a Source #

writeTVar :: TVar (RWST r w s stm) a -> a -> RWST r w s stm () Source #

check :: MonadSTM stm => Bool -> stm () Source #

Check whether a condition is true and, if not, call retry.

throwSTM :: (MonadSTM stm, Exception e) => e -> stm a Source #

Throw an exception. This aborts the transaction and propagates the exception.

catchSTM :: (MonadSTM stm, Exception e) => stm a -> (e -> stm a) -> stm a Source #

Handling exceptions from throwSTM.

Utilities for instance writers

liftedOrElse :: (MonadTransControl t, MonadSTM stm) => (forall x. StT t x -> x) -> t stm a -> t stm a -> t stm a Source #

Given a function to remove the transformer-specific state, lift an orElse invocation.