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

Copyright(c) 2016--2017 Michael Walker
LicenseMIT
MaintainerMichael Walker <mike@barrucadu.co.uk>
Stabilityexperimental
PortabilityCPP, RankNTypes, TemplateHaskell, TypeFamilies
Safe HaskellNone
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).

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. 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, 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

Minimal complete definition

(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.

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

Associated Types

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

Methods

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 m => MonadSTM (IsSTM m) Source # 

Associated Types

type TVar (IsSTM m :: * -> *) :: * -> * Source #

Methods

newTVar :: a -> IsSTM m (TVar (IsSTM m) a) Source #

newTVarN :: String -> a -> IsSTM m (TVar (IsSTM m) a) Source #

readTVar :: TVar (IsSTM m) a -> IsSTM m a Source #

writeTVar :: TVar (IsSTM m) a -> a -> IsSTM m () Source #

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

Since: 1.0.0.0

Associated Types

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

Methods

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 (StateT s stm) Source #

Since: 1.0.0.0

Associated Types

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

Methods

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 (IdentityT * stm) Source #

Since: 1.0.0.0

Associated Types

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

Methods

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 (StateT s stm) Source #

Since: 1.0.0.0

Associated Types

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

Methods

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 #

Since: 1.0.0.0

Associated Types

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

Methods

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 (ReaderT * r stm) Source #

Since: 1.0.0.0

Associated Types

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

Methods

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 #

Since: 1.0.0.0

Associated Types

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

Methods

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 #

Since: 1.0.0.0

Associated Types

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

Methods

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 #

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

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

data IsSTM m a Source #

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 # 

Methods

(>>=) :: IsSTM m a -> (a -> IsSTM m b) -> IsSTM m b #

(>>) :: IsSTM m a -> IsSTM m b -> IsSTM m b #

return :: a -> IsSTM m a #

fail :: String -> IsSTM m a #

Functor m => Functor (IsSTM m) Source # 

Methods

fmap :: (a -> b) -> IsSTM m a -> IsSTM m b #

(<$) :: a -> IsSTM m b -> IsSTM m a #

Applicative m => Applicative (IsSTM m) Source # 

Methods

pure :: a -> IsSTM m a #

(<*>) :: IsSTM m (a -> b) -> IsSTM m a -> IsSTM m b #

liftA2 :: (a -> b -> c) -> IsSTM m a -> IsSTM m b -> IsSTM m c #

(*>) :: IsSTM m a -> IsSTM m b -> IsSTM m b #

(<*) :: IsSTM m a -> IsSTM m b -> IsSTM m a #

Alternative m => Alternative (IsSTM m) Source # 

Methods

empty :: IsSTM m a #

(<|>) :: IsSTM m a -> IsSTM m a -> IsSTM m a #

some :: IsSTM m a -> IsSTM m [a] #

many :: IsSTM m a -> IsSTM m [a] #

MonadPlus m => MonadPlus (IsSTM m) Source # 

Methods

mzero :: IsSTM m a #

mplus :: IsSTM m a -> IsSTM m a -> IsSTM m a #

MonadThrow m => MonadThrow (IsSTM m) Source # 

Methods

throwM :: Exception e => e -> IsSTM m a #

MonadCatch m => MonadCatch (IsSTM m) Source # 

Methods

catch :: Exception e => IsSTM m a -> (e -> IsSTM m a) -> IsSTM m a #

MonadSTM m => MonadSTM (IsSTM m) Source # 

Associated Types

type TVar (IsSTM m :: * -> *) :: * -> * Source #

Methods

newTVar :: a -> IsSTM m (TVar (IsSTM m) a) Source #

newTVarN :: String -> a -> IsSTM m (TVar (IsSTM m) a) Source #

readTVar :: TVar (IsSTM m) a -> IsSTM m a Source #

writeTVar :: TVar (IsSTM m) a -> a -> IsSTM m () Source #

type TVar (IsSTM m) Source # 
type TVar (IsSTM m) = TVar m

toIsSTM :: MonadSTM m => m a -> IsSTM m a Source #

Wrap an m a value inside an IsSTM if m has a MonadSTM instance.

Since: 1.2.2.0

fromIsSTM :: MonadSTM m => IsSTM m a -> m a Source #

Unwrap an IsSTM value.

Since: 1.2.2.0