ouroboros-consensus-0.1.0.1: Consensus layer for the Ouroboros blockchain protocol
Safe Haskell None
Language Haskell2010

Ouroboros.Consensus.Util.MonadSTM.NormalForm

Contents

Synopsis

Documentation

catchSTM :: forall (m :: Type -> Type ) e a. ( MonadSTM m, MonadCatch ( STM m), Exception e) => STM m a -> (e -> STM m a) -> STM m a Source #

catch specialized for an stm monad.

throwSTM :: forall (m :: Type -> Type ) e a. ( MonadSTM m, MonadThrow ( STM m), Exception e) => e -> STM m a Source #

throwIO specialised to stm monad.

type family TBQueue (m :: Type -> Type ) :: Type -> Type Source #

Instances

Instances details
type TBQueue IO
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( WithEarlyExit m) Source #
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TBQueue ( StateT s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( ReaderT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( ExceptT e m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( WriterT w m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( ContT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( RWST r w s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TBQueue ( RWST r w s m) = TBQueue m

type family TQueue (m :: Type -> Type ) :: Type -> Type Source #

Instances

Instances details
type TQueue IO
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( WithEarlyExit m) Source #
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type TQueue ( StateT s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( ReaderT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( ExceptT e m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( WriterT w m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( ContT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( RWST r w s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type TQueue ( RWST r w s m) = TQueue m

type family STM (m :: Type -> Type ) = (stm :: Type -> Type ) | stm -> m Source #

Instances

Instances details
type STM IO
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( WithEarlyExit m) Source #
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

type STM ( StateT s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( StateT s m) = WrappedSTM 'State s m
type STM ( ReaderT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( ReaderT r m) = WrappedSTM 'Reader r m
type STM ( ExceptT e m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( ExceptT e m) = WrappedSTM 'Except e m
type STM ( WriterT w m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( WriterT w m) = WrappedSTM 'Writer w m
type STM ( ContT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( ContT r m) = WrappedSTM 'Cont r m
type STM ( RWST r w s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

type STM ( RWST r w s m) = WrappedSTM 'RWS (r, w, s) m

class ( Monad m, Alternative ( STM m), MonadPlus ( STM m)) => MonadSTM (m :: Type -> Type ) where Source #

Instances

Instances details
MonadSTM IO
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM IO a -> IO a Source #

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

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

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

retry :: STM IO a Source #

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

modifyTVar :: TVar IO a -> (a -> a) -> STM IO () Source #

modifyTVar' :: TVar IO a -> (a -> a) -> STM IO () Source #

stateTVar :: TVar IO s -> (s -> (a, s)) -> STM IO a Source #

swapTVar :: TVar IO a -> a -> STM IO a Source #

check :: Bool -> STM IO () Source #

newTMVar :: a -> STM IO ( TMVar IO a) Source #

newEmptyTMVar :: STM IO ( TMVar IO a) Source #

takeTMVar :: TMVar IO a -> STM IO a Source #

tryTakeTMVar :: TMVar IO a -> STM IO ( Maybe a) Source #

putTMVar :: TMVar IO a -> a -> STM IO () Source #

tryPutTMVar :: TMVar IO a -> a -> STM IO Bool Source #

readTMVar :: TMVar IO a -> STM IO a Source #

tryReadTMVar :: TMVar IO a -> STM IO ( Maybe a) Source #

swapTMVar :: TMVar IO a -> a -> STM IO a Source #

isEmptyTMVar :: TMVar IO a -> STM IO Bool Source #

newTQueue :: STM IO ( TQueue IO a) Source #

readTQueue :: TQueue IO a -> STM IO a Source #

tryReadTQueue :: TQueue IO a -> STM IO ( Maybe a) Source #

peekTQueue :: TQueue IO a -> STM IO a Source #

tryPeekTQueue :: TQueue IO a -> STM IO ( Maybe a) Source #

writeTQueue :: TQueue IO a -> a -> STM IO () Source #

isEmptyTQueue :: TQueue IO a -> STM IO Bool Source #

newTBQueue :: Natural -> STM IO ( TBQueue IO a) Source #

readTBQueue :: TBQueue IO a -> STM IO a Source #

tryReadTBQueue :: TBQueue IO a -> STM IO ( Maybe a) Source #

peekTBQueue :: TBQueue IO a -> STM IO a Source #

tryPeekTBQueue :: TBQueue IO a -> STM IO ( Maybe a) Source #

flushTBQueue :: TBQueue IO a -> STM IO [a] Source #

writeTBQueue :: TBQueue IO a -> a -> STM IO () Source #

lengthTBQueue :: TBQueue IO a -> STM IO Natural Source #

isEmptyTBQueue :: TBQueue IO a -> STM IO Bool Source #

isFullTBQueue :: TBQueue IO a -> STM IO Bool Source #

newTVarIO :: a -> IO ( TVar IO a) Source #

readTVarIO :: TVar IO a -> IO a Source #

newTMVarIO :: a -> IO ( TMVar IO a) Source #

newEmptyTMVarIO :: IO ( TMVar IO a) Source #

newTQueueIO :: IO ( TQueue IO a) Source #

newTBQueueIO :: Natural -> IO ( TBQueue IO a) Source #

MonadSTM m => MonadSTM ( WithEarlyExit m) Source #
Instance details

Defined in Ouroboros.Consensus.Util.EarlyExit

Methods

atomically :: HasCallStack => STM ( WithEarlyExit m) a -> WithEarlyExit m a Source #

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

readTVar :: TVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

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

retry :: STM ( WithEarlyExit m) a Source #

orElse :: STM ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

modifyTVar :: TVar ( WithEarlyExit m) a -> (a -> a) -> STM ( WithEarlyExit m) () Source #

modifyTVar' :: TVar ( WithEarlyExit m) a -> (a -> a) -> STM ( WithEarlyExit m) () Source #

stateTVar :: TVar ( WithEarlyExit m) s -> (s -> (a, s)) -> STM ( WithEarlyExit m) a Source #

swapTVar :: TVar ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) a Source #

check :: Bool -> STM ( WithEarlyExit m) () Source #

newTMVar :: a -> STM ( WithEarlyExit m) ( TMVar ( WithEarlyExit m) a) Source #

newEmptyTMVar :: STM ( WithEarlyExit m) ( TMVar ( WithEarlyExit m) a) Source #

takeTMVar :: TMVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryTakeTMVar :: TMVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

putTMVar :: TMVar ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) () Source #

tryPutTMVar :: TMVar ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) Bool Source #

readTMVar :: TMVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryReadTMVar :: TMVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

swapTMVar :: TMVar ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) a Source #

isEmptyTMVar :: TMVar ( WithEarlyExit m) a -> STM ( WithEarlyExit m) Bool Source #

newTQueue :: STM ( WithEarlyExit m) ( TQueue ( WithEarlyExit m) a) Source #

readTQueue :: TQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryReadTQueue :: TQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

peekTQueue :: TQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryPeekTQueue :: TQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

writeTQueue :: TQueue ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) () Source #

isEmptyTQueue :: TQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) Bool Source #

newTBQueue :: Natural -> STM ( WithEarlyExit m) ( TBQueue ( WithEarlyExit m) a) Source #

readTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryReadTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) a Source #

tryPeekTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) [a] Source #

writeTBQueue :: TBQueue ( WithEarlyExit m) a -> a -> STM ( WithEarlyExit m) () Source #

lengthTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) Natural Source #

isEmptyTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) Bool Source #

isFullTBQueue :: TBQueue ( WithEarlyExit m) a -> STM ( WithEarlyExit m) Bool Source #

newTVarIO :: a -> WithEarlyExit m ( TVar ( WithEarlyExit m) a) Source #

readTVarIO :: TVar ( WithEarlyExit m) a -> WithEarlyExit m a Source #

newTMVarIO :: a -> WithEarlyExit m ( TMVar ( WithEarlyExit m) a) Source #

newEmptyTMVarIO :: WithEarlyExit m ( TMVar ( WithEarlyExit m) a) Source #

newTQueueIO :: WithEarlyExit m ( TQueue ( WithEarlyExit m) a) Source #

newTBQueueIO :: Natural -> WithEarlyExit m ( TBQueue ( WithEarlyExit m) a) Source #

MonadSTM m => MonadSTM ( StateT s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( StateT s m) a -> StateT s m a Source #

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

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

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

retry :: STM ( StateT s m) a Source #

orElse :: STM ( StateT s m) a -> STM ( StateT s m) a -> STM ( StateT s m) a Source #

modifyTVar :: TVar ( StateT s m) a -> (a -> a) -> STM ( StateT s m) () Source #

modifyTVar' :: TVar ( StateT s m) a -> (a -> a) -> STM ( StateT s m) () Source #

stateTVar :: TVar ( StateT s m) s0 -> (s0 -> (a, s0)) -> STM ( StateT s m) a Source #

swapTVar :: TVar ( StateT s m) a -> a -> STM ( StateT s m) a Source #

check :: Bool -> STM ( StateT s m) () Source #

newTMVar :: a -> STM ( StateT s m) ( TMVar ( StateT s m) a) Source #

newEmptyTMVar :: STM ( StateT s m) ( TMVar ( StateT s m) a) Source #

takeTMVar :: TMVar ( StateT s m) a -> STM ( StateT s m) a Source #

tryTakeTMVar :: TMVar ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

putTMVar :: TMVar ( StateT s m) a -> a -> STM ( StateT s m) () Source #

tryPutTMVar :: TMVar ( StateT s m) a -> a -> STM ( StateT s m) Bool Source #

readTMVar :: TMVar ( StateT s m) a -> STM ( StateT s m) a Source #

tryReadTMVar :: TMVar ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

swapTMVar :: TMVar ( StateT s m) a -> a -> STM ( StateT s m) a Source #

isEmptyTMVar :: TMVar ( StateT s m) a -> STM ( StateT s m) Bool Source #

newTQueue :: STM ( StateT s m) ( TQueue ( StateT s m) a) Source #

readTQueue :: TQueue ( StateT s m) a -> STM ( StateT s m) a Source #

tryReadTQueue :: TQueue ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

peekTQueue :: TQueue ( StateT s m) a -> STM ( StateT s m) a Source #

tryPeekTQueue :: TQueue ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

writeTQueue :: TQueue ( StateT s m) a -> a -> STM ( StateT s m) () Source #

isEmptyTQueue :: TQueue ( StateT s m) a -> STM ( StateT s m) Bool Source #

newTBQueue :: Natural -> STM ( StateT s m) ( TBQueue ( StateT s m) a) Source #

readTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) a Source #

tryReadTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) a Source #

tryPeekTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) [a] Source #

writeTBQueue :: TBQueue ( StateT s m) a -> a -> STM ( StateT s m) () Source #

lengthTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) Natural Source #

isEmptyTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) Bool Source #

isFullTBQueue :: TBQueue ( StateT s m) a -> STM ( StateT s m) Bool Source #

newTVarIO :: a -> StateT s m ( TVar ( StateT s m) a) Source #

readTVarIO :: TVar ( StateT s m) a -> StateT s m a Source #

newTMVarIO :: a -> StateT s m ( TMVar ( StateT s m) a) Source #

newEmptyTMVarIO :: StateT s m ( TMVar ( StateT s m) a) Source #

newTQueueIO :: StateT s m ( TQueue ( StateT s m) a) Source #

newTBQueueIO :: Natural -> StateT s m ( TBQueue ( StateT s m) a) Source #

MonadSTM m => MonadSTM ( ReaderT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( ReaderT r m) a -> ReaderT r m a Source #

newTVar :: a -> STM ( ReaderT r m) ( TVar ( ReaderT r m) a) Source #

readTVar :: TVar ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

writeTVar :: TVar ( ReaderT r m) a -> a -> STM ( ReaderT r m) () Source #

retry :: STM ( ReaderT r m) a Source #

orElse :: STM ( ReaderT r m) a -> STM ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

modifyTVar :: TVar ( ReaderT r m) a -> (a -> a) -> STM ( ReaderT r m) () Source #

modifyTVar' :: TVar ( ReaderT r m) a -> (a -> a) -> STM ( ReaderT r m) () Source #

stateTVar :: TVar ( ReaderT r m) s -> (s -> (a, s)) -> STM ( ReaderT r m) a Source #

swapTVar :: TVar ( ReaderT r m) a -> a -> STM ( ReaderT r m) a Source #

check :: Bool -> STM ( ReaderT r m) () Source #

newTMVar :: a -> STM ( ReaderT r m) ( TMVar ( ReaderT r m) a) Source #

newEmptyTMVar :: STM ( ReaderT r m) ( TMVar ( ReaderT r m) a) Source #

takeTMVar :: TMVar ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryTakeTMVar :: TMVar ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

putTMVar :: TMVar ( ReaderT r m) a -> a -> STM ( ReaderT r m) () Source #

tryPutTMVar :: TMVar ( ReaderT r m) a -> a -> STM ( ReaderT r m) Bool Source #

readTMVar :: TMVar ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryReadTMVar :: TMVar ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

swapTMVar :: TMVar ( ReaderT r m) a -> a -> STM ( ReaderT r m) a Source #

isEmptyTMVar :: TMVar ( ReaderT r m) a -> STM ( ReaderT r m) Bool Source #

newTQueue :: STM ( ReaderT r m) ( TQueue ( ReaderT r m) a) Source #

readTQueue :: TQueue ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryReadTQueue :: TQueue ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

peekTQueue :: TQueue ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryPeekTQueue :: TQueue ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

writeTQueue :: TQueue ( ReaderT r m) a -> a -> STM ( ReaderT r m) () Source #

isEmptyTQueue :: TQueue ( ReaderT r m) a -> STM ( ReaderT r m) Bool Source #

newTBQueue :: Natural -> STM ( ReaderT r m) ( TBQueue ( ReaderT r m) a) Source #

readTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryReadTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) a Source #

tryPeekTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) [a] Source #

writeTBQueue :: TBQueue ( ReaderT r m) a -> a -> STM ( ReaderT r m) () Source #

lengthTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) Natural Source #

isEmptyTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) Bool Source #

isFullTBQueue :: TBQueue ( ReaderT r m) a -> STM ( ReaderT r m) Bool Source #

newTVarIO :: a -> ReaderT r m ( TVar ( ReaderT r m) a) Source #

readTVarIO :: TVar ( ReaderT r m) a -> ReaderT r m a Source #

newTMVarIO :: a -> ReaderT r m ( TMVar ( ReaderT r m) a) Source #

newEmptyTMVarIO :: ReaderT r m ( TMVar ( ReaderT r m) a) Source #

newTQueueIO :: ReaderT r m ( TQueue ( ReaderT r m) a) Source #

newTBQueueIO :: Natural -> ReaderT r m ( TBQueue ( ReaderT r m) a) Source #

MonadSTM m => MonadSTM ( ExceptT e m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( ExceptT e m) a -> ExceptT e m a Source #

newTVar :: a -> STM ( ExceptT e m) ( TVar ( ExceptT e m) a) Source #

readTVar :: TVar ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

writeTVar :: TVar ( ExceptT e m) a -> a -> STM ( ExceptT e m) () Source #

retry :: STM ( ExceptT e m) a Source #

orElse :: STM ( ExceptT e m) a -> STM ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

modifyTVar :: TVar ( ExceptT e m) a -> (a -> a) -> STM ( ExceptT e m) () Source #

modifyTVar' :: TVar ( ExceptT e m) a -> (a -> a) -> STM ( ExceptT e m) () Source #

stateTVar :: TVar ( ExceptT e m) s -> (s -> (a, s)) -> STM ( ExceptT e m) a Source #

swapTVar :: TVar ( ExceptT e m) a -> a -> STM ( ExceptT e m) a Source #

check :: Bool -> STM ( ExceptT e m) () Source #

newTMVar :: a -> STM ( ExceptT e m) ( TMVar ( ExceptT e m) a) Source #

newEmptyTMVar :: STM ( ExceptT e m) ( TMVar ( ExceptT e m) a) Source #

takeTMVar :: TMVar ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryTakeTMVar :: TMVar ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

putTMVar :: TMVar ( ExceptT e m) a -> a -> STM ( ExceptT e m) () Source #

tryPutTMVar :: TMVar ( ExceptT e m) a -> a -> STM ( ExceptT e m) Bool Source #

readTMVar :: TMVar ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryReadTMVar :: TMVar ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

swapTMVar :: TMVar ( ExceptT e m) a -> a -> STM ( ExceptT e m) a Source #

isEmptyTMVar :: TMVar ( ExceptT e m) a -> STM ( ExceptT e m) Bool Source #

newTQueue :: STM ( ExceptT e m) ( TQueue ( ExceptT e m) a) Source #

readTQueue :: TQueue ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryReadTQueue :: TQueue ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

peekTQueue :: TQueue ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryPeekTQueue :: TQueue ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

writeTQueue :: TQueue ( ExceptT e m) a -> a -> STM ( ExceptT e m) () Source #

isEmptyTQueue :: TQueue ( ExceptT e m) a -> STM ( ExceptT e m) Bool Source #

newTBQueue :: Natural -> STM ( ExceptT e m) ( TBQueue ( ExceptT e m) a) Source #

readTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryReadTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) a Source #

tryPeekTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) [a] Source #

writeTBQueue :: TBQueue ( ExceptT e m) a -> a -> STM ( ExceptT e m) () Source #

lengthTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) Natural Source #

isEmptyTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) Bool Source #

isFullTBQueue :: TBQueue ( ExceptT e m) a -> STM ( ExceptT e m) Bool Source #

newTVarIO :: a -> ExceptT e m ( TVar ( ExceptT e m) a) Source #

readTVarIO :: TVar ( ExceptT e m) a -> ExceptT e m a Source #

newTMVarIO :: a -> ExceptT e m ( TMVar ( ExceptT e m) a) Source #

newEmptyTMVarIO :: ExceptT e m ( TMVar ( ExceptT e m) a) Source #

newTQueueIO :: ExceptT e m ( TQueue ( ExceptT e m) a) Source #

newTBQueueIO :: Natural -> ExceptT e m ( TBQueue ( ExceptT e m) a) Source #

( Monoid w, MonadSTM m) => MonadSTM ( WriterT w m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( WriterT w m) a -> WriterT w m a Source #

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

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

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

retry :: STM ( WriterT w m) a Source #

orElse :: STM ( WriterT w m) a -> STM ( WriterT w m) a -> STM ( WriterT w m) a Source #

modifyTVar :: TVar ( WriterT w m) a -> (a -> a) -> STM ( WriterT w m) () Source #

modifyTVar' :: TVar ( WriterT w m) a -> (a -> a) -> STM ( WriterT w m) () Source #

stateTVar :: TVar ( WriterT w m) s -> (s -> (a, s)) -> STM ( WriterT w m) a Source #

swapTVar :: TVar ( WriterT w m) a -> a -> STM ( WriterT w m) a Source #

check :: Bool -> STM ( WriterT w m) () Source #

newTMVar :: a -> STM ( WriterT w m) ( TMVar ( WriterT w m) a) Source #

newEmptyTMVar :: STM ( WriterT w m) ( TMVar ( WriterT w m) a) Source #

takeTMVar :: TMVar ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryTakeTMVar :: TMVar ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

putTMVar :: TMVar ( WriterT w m) a -> a -> STM ( WriterT w m) () Source #

tryPutTMVar :: TMVar ( WriterT w m) a -> a -> STM ( WriterT w m) Bool Source #

readTMVar :: TMVar ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryReadTMVar :: TMVar ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

swapTMVar :: TMVar ( WriterT w m) a -> a -> STM ( WriterT w m) a Source #

isEmptyTMVar :: TMVar ( WriterT w m) a -> STM ( WriterT w m) Bool Source #

newTQueue :: STM ( WriterT w m) ( TQueue ( WriterT w m) a) Source #

readTQueue :: TQueue ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryReadTQueue :: TQueue ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

peekTQueue :: TQueue ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryPeekTQueue :: TQueue ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

writeTQueue :: TQueue ( WriterT w m) a -> a -> STM ( WriterT w m) () Source #

isEmptyTQueue :: TQueue ( WriterT w m) a -> STM ( WriterT w m) Bool Source #

newTBQueue :: Natural -> STM ( WriterT w m) ( TBQueue ( WriterT w m) a) Source #

readTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryReadTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) a Source #

tryPeekTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) [a] Source #

writeTBQueue :: TBQueue ( WriterT w m) a -> a -> STM ( WriterT w m) () Source #

lengthTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) Natural Source #

isEmptyTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) Bool Source #

isFullTBQueue :: TBQueue ( WriterT w m) a -> STM ( WriterT w m) Bool Source #

newTVarIO :: a -> WriterT w m ( TVar ( WriterT w m) a) Source #

readTVarIO :: TVar ( WriterT w m) a -> WriterT w m a Source #

newTMVarIO :: a -> WriterT w m ( TMVar ( WriterT w m) a) Source #

newEmptyTMVarIO :: WriterT w m ( TMVar ( WriterT w m) a) Source #

newTQueueIO :: WriterT w m ( TQueue ( WriterT w m) a) Source #

newTBQueueIO :: Natural -> WriterT w m ( TBQueue ( WriterT w m) a) Source #

MonadSTM m => MonadSTM ( ContT r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( ContT r m) a -> ContT r m a Source #

newTVar :: a -> STM ( ContT r m) ( TVar ( ContT r m) a) Source #

readTVar :: TVar ( ContT r m) a -> STM ( ContT r m) a Source #

writeTVar :: TVar ( ContT r m) a -> a -> STM ( ContT r m) () Source #

retry :: STM ( ContT r m) a Source #

orElse :: STM ( ContT r m) a -> STM ( ContT r m) a -> STM ( ContT r m) a Source #

modifyTVar :: TVar ( ContT r m) a -> (a -> a) -> STM ( ContT r m) () Source #

modifyTVar' :: TVar ( ContT r m) a -> (a -> a) -> STM ( ContT r m) () Source #

stateTVar :: TVar ( ContT r m) s -> (s -> (a, s)) -> STM ( ContT r m) a Source #

swapTVar :: TVar ( ContT r m) a -> a -> STM ( ContT r m) a Source #

check :: Bool -> STM ( ContT r m) () Source #

newTMVar :: a -> STM ( ContT r m) ( TMVar ( ContT r m) a) Source #

newEmptyTMVar :: STM ( ContT r m) ( TMVar ( ContT r m) a) Source #

takeTMVar :: TMVar ( ContT r m) a -> STM ( ContT r m) a Source #

tryTakeTMVar :: TMVar ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

putTMVar :: TMVar ( ContT r m) a -> a -> STM ( ContT r m) () Source #

tryPutTMVar :: TMVar ( ContT r m) a -> a -> STM ( ContT r m) Bool Source #

readTMVar :: TMVar ( ContT r m) a -> STM ( ContT r m) a Source #

tryReadTMVar :: TMVar ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

swapTMVar :: TMVar ( ContT r m) a -> a -> STM ( ContT r m) a Source #

isEmptyTMVar :: TMVar ( ContT r m) a -> STM ( ContT r m) Bool Source #

newTQueue :: STM ( ContT r m) ( TQueue ( ContT r m) a) Source #

readTQueue :: TQueue ( ContT r m) a -> STM ( ContT r m) a Source #

tryReadTQueue :: TQueue ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

peekTQueue :: TQueue ( ContT r m) a -> STM ( ContT r m) a Source #

tryPeekTQueue :: TQueue ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

writeTQueue :: TQueue ( ContT r m) a -> a -> STM ( ContT r m) () Source #

isEmptyTQueue :: TQueue ( ContT r m) a -> STM ( ContT r m) Bool Source #

newTBQueue :: Natural -> STM ( ContT r m) ( TBQueue ( ContT r m) a) Source #

readTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) a Source #

tryReadTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) a Source #

tryPeekTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) [a] Source #

writeTBQueue :: TBQueue ( ContT r m) a -> a -> STM ( ContT r m) () Source #

lengthTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) Natural Source #

isEmptyTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) Bool Source #

isFullTBQueue :: TBQueue ( ContT r m) a -> STM ( ContT r m) Bool Source #

newTVarIO :: a -> ContT r m ( TVar ( ContT r m) a) Source #

readTVarIO :: TVar ( ContT r m) a -> ContT r m a Source #

newTMVarIO :: a -> ContT r m ( TMVar ( ContT r m) a) Source #

newEmptyTMVarIO :: ContT r m ( TMVar ( ContT r m) a) Source #

newTQueueIO :: ContT r m ( TQueue ( ContT r m) a) Source #

newTBQueueIO :: Natural -> ContT r m ( TBQueue ( ContT r m) a) Source #

( Monoid w, MonadSTM m) => MonadSTM ( RWST r w s m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

atomically :: HasCallStack => STM ( RWST r w s m) a -> RWST r w s m a Source #

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

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

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

retry :: STM ( RWST r w s m) a Source #

orElse :: STM ( RWST r w s m) a -> STM ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

modifyTVar :: TVar ( RWST r w s m) a -> (a -> a) -> STM ( RWST r w s m) () Source #

modifyTVar' :: TVar ( RWST r w s m) a -> (a -> a) -> STM ( RWST r w s m) () Source #

stateTVar :: TVar ( RWST r w s m) s0 -> (s0 -> (a, s0)) -> STM ( RWST r w s m) a Source #

swapTVar :: TVar ( RWST r w s m) a -> a -> STM ( RWST r w s m) a Source #

check :: Bool -> STM ( RWST r w s m) () Source #

newTMVar :: a -> STM ( RWST r w s m) ( TMVar ( RWST r w s m) a) Source #

newEmptyTMVar :: STM ( RWST r w s m) ( TMVar ( RWST r w s m) a) Source #

takeTMVar :: TMVar ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryTakeTMVar :: TMVar ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

putTMVar :: TMVar ( RWST r w s m) a -> a -> STM ( RWST r w s m) () Source #

tryPutTMVar :: TMVar ( RWST r w s m) a -> a -> STM ( RWST r w s m) Bool Source #

readTMVar :: TMVar ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryReadTMVar :: TMVar ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

swapTMVar :: TMVar ( RWST r w s m) a -> a -> STM ( RWST r w s m) a Source #

isEmptyTMVar :: TMVar ( RWST r w s m) a -> STM ( RWST r w s m) Bool Source #

newTQueue :: STM ( RWST r w s m) ( TQueue ( RWST r w s m) a) Source #

readTQueue :: TQueue ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryReadTQueue :: TQueue ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

peekTQueue :: TQueue ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryPeekTQueue :: TQueue ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

writeTQueue :: TQueue ( RWST r w s m) a -> a -> STM ( RWST r w s m) () Source #

isEmptyTQueue :: TQueue ( RWST r w s m) a -> STM ( RWST r w s m) Bool Source #

newTBQueue :: Natural -> STM ( RWST r w s m) ( TBQueue ( RWST r w s m) a) Source #

readTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryReadTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

peekTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) a Source #

tryPeekTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) ( Maybe a) Source #

flushTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) [a] Source #

writeTBQueue :: TBQueue ( RWST r w s m) a -> a -> STM ( RWST r w s m) () Source #

lengthTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) Natural Source #

isEmptyTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) Bool Source #

isFullTBQueue :: TBQueue ( RWST r w s m) a -> STM ( RWST r w s m) Bool Source #

newTVarIO :: a -> RWST r w s m ( TVar ( RWST r w s m) a) Source #

readTVarIO :: TVar ( RWST r w s m) a -> RWST r w s m a Source #

newTMVarIO :: a -> RWST r w s m ( TMVar ( RWST r w s m) a) Source #

newEmptyTMVarIO :: RWST r w s m ( TMVar ( RWST r w s m) a) Source #

newTQueueIO :: RWST r w s m ( TQueue ( RWST r w s m) a) Source #

newTBQueueIO :: Natural -> RWST r w s m ( TBQueue ( RWST r w s m) a) Source #

type family InspectMonad (m :: Type -> Type ) :: Type -> Type Source #

Instances

Instances details
type InspectMonad IO
Instance details

Defined in Control.Monad.Class.MonadSTM

class ( MonadSTM m, Monad ( InspectMonad m)) => MonadInspectSTM (m :: Type -> Type ) where Source #

This type class is indented for 'io-sim', where one might want to access TVar in the underlying ST monad.

Associated Types

type InspectMonad (m :: Type -> Type ) :: Type -> Type Source #

data TraceValue where Source #

A GADT which instructs how to trace the value. The traceDynamic will use dynamic tracing, e.g. traceM ; while traceString will be traced with EventSay .

Bundled Patterns

pattern TraceDynamic :: () => Typeable tr => tr -> TraceValue

Use only dynamic tracer.

pattern TraceString :: String -> TraceValue

Use only string tracing.

pattern DontTrace :: TraceValue

Do not trace the value.

class MonadInspectSTM m => MonadTraceSTM (m :: Type -> Type ) where Source #

MonadTraceSTM allows to trace values of stm variables when stm transaction is committed. This allows to verify invariants when a variable is committed.

Minimal complete definition

traceTVar , traceTQueue , traceTBQueue

data TQueueDefault (m :: Type -> Type ) a Source #

Constructors

TQueue !( TVar m [a]) !( TVar m [a])

newtype WrappedSTM (t :: Trans) r (m :: Type -> Type ) a Source #

A newtype wrapper for an STM monad for monad transformers.

Constructors

WrappedSTM

Instances

Instances details
MonadSTM m => Monad ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

MonadSTM m => Functor ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

Methods

fmap :: (a -> b) -> WrappedSTM t r m a -> WrappedSTM t r m b Source #

(<$) :: a -> WrappedSTM t r m b -> WrappedSTM t r m a Source #

MonadSTM m => Applicative ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

MonadSTM m => MonadPlus ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

MonadSTM m => Alternative ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

( MonadSTM m, MonadThrow ( STM m), MonadCatch ( STM m)) => MonadThrow ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

( MonadSTM m, MonadThrow ( STM m), MonadCatch ( STM m)) => MonadCatch ( WrappedSTM t r m)
Instance details

Defined in Control.Monad.Class.MonadSTM

checkInvariant :: HasCallStack => Maybe String -> a -> a Source #

Check invariant (if enabled) before continuing

checkInvariant mErr x is equal to x if mErr == Nothing , and throws an error err if mErr == Just err .

This is exported so that other code that wants to conditionally check invariants can reuse the same logic, rather than having to introduce new per-package flags.

updateTVar :: forall (m :: Type -> Type ) s a. MonadSTM m => StrictTVar m s -> (s -> (a, s)) -> STM m a Source #

stateTVar :: forall (m :: Type -> Type ) s a. MonadSTM m => StrictTVar m s -> (s -> (a, s)) -> STM m a Source #

modifyTVar :: forall (m :: Type -> Type ) a. MonadSTM m => StrictTVar m a -> (a -> a) -> STM m () Source #

newTVarWithInvariant Source #

Arguments

:: forall (m :: Type -> Type ) a. ( MonadSTM m, HasCallStack )
=> (a -> Maybe String )

Invariant (expect Nothing )

-> a
-> STM m ( StrictTVar m a)

toLazyTVar :: forall (m :: Type -> Type ) a. StrictTVar m a -> LazyTVar m a Source #

Get the underlying TVar

Since we obviously cannot guarantee that updates to this LazyTVar will be strict, this should be used with caution.

traceTVar :: forall (m :: Type -> Type ) proxy a. MonadTraceSTM m => proxy m -> StrictTVar m a -> ( Maybe a -> a -> InspectMonad m TraceValue ) -> STM m () Source #

data StrictMVar m a Source #

Strict MVar (modelled using a lazy TMVar under the hood)

The StrictMVar API is slightly stronger than the usual MVar one, as we offer a primitive to read the value of the MVar even if it is empty (in which case we will return the oldest known stale one). See readMVarSTM .

There is a weaker invariant for a StrictMVar than for a StrictTVar : although all functions that modify the StrictMVar check the invariant, we do not guarantee that the value inside the StrictMVar always satisfies the invariant. Instead, we do guarantee that if the StrictMVar is updated with a value that does not satisfy the invariant, an exception is thrown. The reason for this weaker guarantee is that leaving an MVar empty can lead to very hard to debug "blocked indefinitely" problems.

This is also the reason we do not offer support for an invariant in StrictTMVar : if we throw an exception from an STM transaction, the STM transaction is not executed, and so we would not even be able to provide the weaker guarantee that we provide for StrictMVar .

Constructors

StrictMVar

Fields

readMVarSTM :: MonadSTM m => StrictMVar m a -> STM m a Source #

Read the possibly-stale value of the MVar

Will return the current value of the MVar if it non-empty, or the last known value otherwise.

swapMVar :: ( MonadSTM m, HasCallStack ) => StrictMVar m a -> a -> m a Source #

Swap value of a StrictMVar

NOTE: Since swapping the value can't leave the StrictMVar empty, we could check the invariant first and only then swap. We nonetheless swap first and check the invariant after to keep the semantics the same with putMVar , otherwise it will be difficult to understand when a StrictMVar is updated and when it is not.

Temporary