Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype ContTSTM r (m :: Type -> Type) a = ContTSTM {
- getContTSTM :: STM m a
Documentation
newtype ContTSTM r (m :: Type -> Type) a Source #
A newtype wrapper for an STM
monad for ContT
ContTSTM | |
|
Instances
(MonadSTM m, MArray e a (STM m)) => MArray e a (ContTSTM r m) Source # | |
Defined in Control.Monad.Class.MonadSTM.Trans getBounds :: Ix i => e i a -> ContTSTM r m (i, i) # getNumElements :: Ix i => e i a -> ContTSTM r m Int newArray :: Ix i => (i, i) -> a -> ContTSTM r m (e i a) # newArray_ :: Ix i => (i, i) -> ContTSTM r m (e i a) # unsafeNewArray_ :: Ix i => (i, i) -> ContTSTM r m (e i a) unsafeRead :: Ix i => e i a -> Int -> ContTSTM r m a unsafeWrite :: Ix i => e i a -> Int -> a -> ContTSTM r m () | |
MonadSTM m => Applicative (ContTSTM r m) Source # | |
Defined in Control.Monad.Class.MonadSTM.Trans | |
MonadSTM m => Functor (ContTSTM r m) Source # | |
MonadSTM m => Monad (ContTSTM r m) Source # | |
(MonadSTM m, MonadThrow (STM m), MonadCatch (STM m)) => MonadCatch (ContTSTM r m) Source # | |
Defined in Control.Monad.Class.MonadSTM.Trans catch :: Exception e => ContTSTM r m a -> (e -> ContTSTM r m a) -> ContTSTM r m a catchJust :: Exception e => (e -> Maybe b) -> ContTSTM r m a -> (b -> ContTSTM r m a) -> ContTSTM r m a try :: Exception e => ContTSTM r m a -> ContTSTM r m (Either e a) tryJust :: Exception e => (e -> Maybe b) -> ContTSTM r m a -> ContTSTM r m (Either b a) handle :: Exception e => (e -> ContTSTM r m a) -> ContTSTM r m a -> ContTSTM r m a handleJust :: Exception e => (e -> Maybe b) -> (b -> ContTSTM r m a) -> ContTSTM r m a -> ContTSTM r m a onException :: ContTSTM r m a -> ContTSTM r m b -> ContTSTM r m a bracketOnError :: ContTSTM r m a -> (a -> ContTSTM r m b) -> (a -> ContTSTM r m c) -> ContTSTM r m c generalBracket :: ContTSTM r m a -> (a -> ExitCase b -> ContTSTM r m c) -> (a -> ContTSTM r m b) -> ContTSTM r m (b, c) | |
(MonadSTM m, MonadThrow (STM m), MonadCatch (STM m)) => MonadThrow (ContTSTM r m) Source # | |
Defined in Control.Monad.Class.MonadSTM.Trans | |
(Monoid a, MonadSTM m) => Monoid (ContTSTM r m a) Source # | |
(Semigroup a, MonadSTM m) => Semigroup (ContTSTM r m a) Source # | |
Orphan instances
MonadSTM m => MonadSTM (ExceptT e m) Source # | The underlying stm monad is also transformed. |
type STM (ExceptT e m) = (stm :: Type -> Type) type TVar (ExceptT e m) :: Type -> Type type TMVar (ExceptT e m) :: Type -> Type type TQueue (ExceptT e m) :: Type -> Type type TBQueue (ExceptT e m) :: Type -> Type type TArray (ExceptT e m) :: Type -> Type -> Type type TSem (ExceptT e m) atomically :: HasCallStack => STM (ExceptT e m) a -> ExceptT e m a newTVar :: a -> STM (ExceptT e m) (TVar (ExceptT e m) a) readTVar :: TVar (ExceptT e m) a -> STM (ExceptT e m) a writeTVar :: TVar (ExceptT e m) a -> a -> STM (ExceptT e m) () orElse :: STM (ExceptT e m) a -> STM (ExceptT e m) a -> STM (ExceptT e m) a modifyTVar :: TVar (ExceptT e m) a -> (a -> a) -> STM (ExceptT e m) () modifyTVar' :: TVar (ExceptT e m) a -> (a -> a) -> STM (ExceptT e m) () stateTVar :: TVar (ExceptT e m) s -> (s -> (a, s)) -> STM (ExceptT e m) a swapTVar :: TVar (ExceptT e m) a -> a -> STM (ExceptT e m) a check :: Bool -> STM (ExceptT e m) () newTMVar :: a -> STM (ExceptT e m) (TMVar (ExceptT e m) a) newEmptyTMVar :: STM (ExceptT e m) (TMVar (ExceptT e m) a) takeTMVar :: TMVar (ExceptT e m) a -> STM (ExceptT e m) a tryTakeTMVar :: TMVar (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) putTMVar :: TMVar (ExceptT e m) a -> a -> STM (ExceptT e m) () tryPutTMVar :: TMVar (ExceptT e m) a -> a -> STM (ExceptT e m) Bool readTMVar :: TMVar (ExceptT e m) a -> STM (ExceptT e m) a tryReadTMVar :: TMVar (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) swapTMVar :: TMVar (ExceptT e m) a -> a -> STM (ExceptT e m) a writeTMVar :: TMVar (ExceptT e m) a -> a -> STM (ExceptT e m) () isEmptyTMVar :: TMVar (ExceptT e m) a -> STM (ExceptT e m) Bool newTQueue :: STM (ExceptT e m) (TQueue (ExceptT e m) a) readTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) a tryReadTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) peekTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) a tryPeekTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) flushTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) [a] writeTQueue :: TQueue (ExceptT e m) a -> a -> STM (ExceptT e m) () isEmptyTQueue :: TQueue (ExceptT e m) a -> STM (ExceptT e m) Bool unGetTQueue :: TQueue (ExceptT e m) a -> a -> STM (ExceptT e m) () newTBQueue :: Natural -> STM (ExceptT e m) (TBQueue (ExceptT e m) a) readTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) a tryReadTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) peekTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) a tryPeekTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) flushTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) [a] writeTBQueue :: TBQueue (ExceptT e m) a -> a -> STM (ExceptT e m) () lengthTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) Natural isEmptyTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) Bool isFullTBQueue :: TBQueue (ExceptT e m) a -> STM (ExceptT e m) Bool unGetTBQueue :: TBQueue (ExceptT e m) a -> a -> STM (ExceptT e m) () newTSem :: Integer -> STM (ExceptT e m) (TSem (ExceptT e m)) waitTSem :: TSem (ExceptT e m) -> STM (ExceptT e m) () signalTSem :: TSem (ExceptT e m) -> STM (ExceptT e m) () signalTSemN :: Natural -> TSem (ExceptT e m) -> STM (ExceptT e m) () newTChan :: STM (ExceptT e m) (TChan (ExceptT e m) a) newBroadcastTChan :: STM (ExceptT e m) (TChan (ExceptT e m) a) dupTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) (TChan (ExceptT e m) a) cloneTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) (TChan (ExceptT e m) a) readTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) a tryReadTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) peekTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) a tryPeekTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) (Maybe a) writeTChan :: TChan (ExceptT e m) a -> a -> STM (ExceptT e m) () unGetTChan :: TChan (ExceptT e m) a -> a -> STM (ExceptT e m) () isEmptyTChan :: TChan (ExceptT e m) a -> STM (ExceptT e m) Bool newTVarIO :: a -> ExceptT e m (TVar (ExceptT e m) a) readTVarIO :: TVar (ExceptT e m) a -> ExceptT e m a newTMVarIO :: a -> ExceptT e m (TMVar (ExceptT e m) a) newEmptyTMVarIO :: ExceptT e m (TMVar (ExceptT e m) a) newTQueueIO :: ExceptT e m (TQueue (ExceptT e m) a) newTBQueueIO :: Natural -> ExceptT e m (TBQueue (ExceptT e m) a) newTChanIO :: ExceptT e m (TChan (ExceptT e m) a) newBroadcastTChanIO :: ExceptT e m (TChan (ExceptT e m) a) | |
MonadSTM m => MonadSTM (StateT s m) Source # | The underlying stm monad is also transformed. |
type STM (StateT s m) = (stm :: Type -> Type) type TVar (StateT s m) :: Type -> Type type TMVar (StateT s m) :: Type -> Type type TQueue (StateT s m) :: Type -> Type type TBQueue (StateT s m) :: Type -> Type type TArray (StateT s m) :: Type -> Type -> Type type TSem (StateT s m) atomically :: HasCallStack => STM (StateT s m) a -> StateT s m a newTVar :: a -> STM (StateT s m) (TVar (StateT s m) a) readTVar :: TVar (StateT s m) a -> STM (StateT s m) a writeTVar :: TVar (StateT s m) a -> a -> STM (StateT s m) () orElse :: STM (StateT s m) a -> STM (StateT s m) a -> STM (StateT s m) a modifyTVar :: TVar (StateT s m) a -> (a -> a) -> STM (StateT s m) () modifyTVar' :: TVar (StateT s m) a -> (a -> a) -> STM (StateT s m) () stateTVar :: TVar (StateT s m) s0 -> (s0 -> (a, s0)) -> STM (StateT s m) a swapTVar :: TVar (StateT s m) a -> a -> STM (StateT s m) a check :: Bool -> STM (StateT s m) () newTMVar :: a -> STM (StateT s m) (TMVar (StateT s m) a) newEmptyTMVar :: STM (StateT s m) (TMVar (StateT s m) a) takeTMVar :: TMVar (StateT s m) a -> STM (StateT s m) a tryTakeTMVar :: TMVar (StateT s m) a -> STM (StateT s m) (Maybe a) putTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) () tryPutTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) Bool readTMVar :: TMVar (StateT s m) a -> STM (StateT s m) a tryReadTMVar :: TMVar (StateT s m) a -> STM (StateT s m) (Maybe a) swapTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) a writeTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) () isEmptyTMVar :: TMVar (StateT s m) a -> STM (StateT s m) Bool newTQueue :: STM (StateT s m) (TQueue (StateT s m) a) readTQueue :: TQueue (StateT s m) a -> STM (StateT s m) a tryReadTQueue :: TQueue (StateT s m) a -> STM (StateT s m) (Maybe a) peekTQueue :: TQueue (StateT s m) a -> STM (StateT s m) a tryPeekTQueue :: TQueue (StateT s m) a -> STM (StateT s m) (Maybe a) flushTQueue :: TQueue (StateT s m) a -> STM (StateT s m) [a] writeTQueue :: TQueue (StateT s m) a -> a -> STM (StateT s m) () isEmptyTQueue :: TQueue (StateT s m) a -> STM (StateT s m) Bool unGetTQueue :: TQueue (StateT s m) a -> a -> STM (StateT s m) () newTBQueue :: Natural -> STM (StateT s m) (TBQueue (StateT s m) a) readTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) a tryReadTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) (Maybe a) peekTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) a tryPeekTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) (Maybe a) flushTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) [a] writeTBQueue :: TBQueue (StateT s m) a -> a -> STM (StateT s m) () lengthTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Natural isEmptyTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Bool isFullTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Bool unGetTBQueue :: TBQueue (StateT s m) a -> a -> STM (StateT s m) () newTSem :: Integer -> STM (StateT s m) (TSem (StateT s m)) waitTSem :: TSem (StateT s m) -> STM (StateT s m) () signalTSem :: TSem (StateT s m) -> STM (StateT s m) () signalTSemN :: Natural -> TSem (StateT s m) -> STM (StateT s m) () newTChan :: STM (StateT s m) (TChan (StateT s m) a) newBroadcastTChan :: STM (StateT s m) (TChan (StateT s m) a) dupTChan :: TChan (StateT s m) a -> STM (StateT s m) (TChan (StateT s m) a) cloneTChan :: TChan (StateT s m) a -> STM (StateT s m) (TChan (StateT s m) a) readTChan :: TChan (StateT s m) a -> STM (StateT s m) a tryReadTChan :: TChan (StateT s m) a -> STM (StateT s m) (Maybe a) peekTChan :: TChan (StateT s m) a -> STM (StateT s m) a tryPeekTChan :: TChan (StateT s m) a -> STM (StateT s m) (Maybe a) writeTChan :: TChan (StateT s m) a -> a -> STM (StateT s m) () unGetTChan :: TChan (StateT s m) a -> a -> STM (StateT s m) () isEmptyTChan :: TChan (StateT s m) a -> STM (StateT s m) Bool newTVarIO :: a -> StateT s m (TVar (StateT s m) a) readTVarIO :: TVar (StateT s m) a -> StateT s m a newTMVarIO :: a -> StateT s m (TMVar (StateT s m) a) newEmptyTMVarIO :: StateT s m (TMVar (StateT s m) a) newTQueueIO :: StateT s m (TQueue (StateT s m) a) newTBQueueIO :: Natural -> StateT s m (TBQueue (StateT s m) a) newTChanIO :: StateT s m (TChan (StateT s m) a) newBroadcastTChanIO :: StateT s m (TChan (StateT s m) a) | |
MonadSTM m => MonadSTM (StateT s m) Source # | The underlying stm monad is also transformed. |
type STM (StateT s m) = (stm :: Type -> Type) type TVar (StateT s m) :: Type -> Type type TMVar (StateT s m) :: Type -> Type type TQueue (StateT s m) :: Type -> Type type TBQueue (StateT s m) :: Type -> Type type TArray (StateT s m) :: Type -> Type -> Type type TSem (StateT s m) atomically :: HasCallStack => STM (StateT s m) a -> StateT s m a newTVar :: a -> STM (StateT s m) (TVar (StateT s m) a) readTVar :: TVar (StateT s m) a -> STM (StateT s m) a writeTVar :: TVar (StateT s m) a -> a -> STM (StateT s m) () orElse :: STM (StateT s m) a -> STM (StateT s m) a -> STM (StateT s m) a modifyTVar :: TVar (StateT s m) a -> (a -> a) -> STM (StateT s m) () modifyTVar' :: TVar (StateT s m) a -> (a -> a) -> STM (StateT s m) () stateTVar :: TVar (StateT s m) s0 -> (s0 -> (a, s0)) -> STM (StateT s m) a swapTVar :: TVar (StateT s m) a -> a -> STM (StateT s m) a check :: Bool -> STM (StateT s m) () newTMVar :: a -> STM (StateT s m) (TMVar (StateT s m) a) newEmptyTMVar :: STM (StateT s m) (TMVar (StateT s m) a) takeTMVar :: TMVar (StateT s m) a -> STM (StateT s m) a tryTakeTMVar :: TMVar (StateT s m) a -> STM (StateT s m) (Maybe a) putTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) () tryPutTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) Bool readTMVar :: TMVar (StateT s m) a -> STM (StateT s m) a tryReadTMVar :: TMVar (StateT s m) a -> STM (StateT s m) (Maybe a) swapTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) a writeTMVar :: TMVar (StateT s m) a -> a -> STM (StateT s m) () isEmptyTMVar :: TMVar (StateT s m) a -> STM (StateT s m) Bool newTQueue :: STM (StateT s m) (TQueue (StateT s m) a) readTQueue :: TQueue (StateT s m) a -> STM (StateT s m) a tryReadTQueue :: TQueue (StateT s m) a -> STM (StateT s m) (Maybe a) peekTQueue :: TQueue (StateT s m) a -> STM (StateT s m) a tryPeekTQueue :: TQueue (StateT s m) a -> STM (StateT s m) (Maybe a) flushTQueue :: TQueue (StateT s m) a -> STM (StateT s m) [a] writeTQueue :: TQueue (StateT s m) a -> a -> STM (StateT s m) () isEmptyTQueue :: TQueue (StateT s m) a -> STM (StateT s m) Bool unGetTQueue :: TQueue (StateT s m) a -> a -> STM (StateT s m) () newTBQueue :: Natural -> STM (StateT s m) (TBQueue (StateT s m) a) readTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) a tryReadTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) (Maybe a) peekTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) a tryPeekTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) (Maybe a) flushTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) [a] writeTBQueue :: TBQueue (StateT s m) a -> a -> STM (StateT s m) () lengthTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Natural isEmptyTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Bool isFullTBQueue :: TBQueue (StateT s m) a -> STM (StateT s m) Bool unGetTBQueue :: TBQueue (StateT s m) a -> a -> STM (StateT s m) () newTSem :: Integer -> STM (StateT s m) (TSem (StateT s m)) waitTSem :: TSem (StateT s m) -> STM (StateT s m) () signalTSem :: TSem (StateT s m) -> STM (StateT s m) () signalTSemN :: Natural -> TSem (StateT s m) -> STM (StateT s m) () newTChan :: STM (StateT s m) (TChan (StateT s m) a) newBroadcastTChan :: STM (StateT s m) (TChan (StateT s m) a) dupTChan :: TChan (StateT s m) a -> STM (StateT s m) (TChan (StateT s m) a) cloneTChan :: TChan (StateT s m) a -> STM (StateT s m) (TChan (StateT s m) a) readTChan :: TChan (StateT s m) a -> STM (StateT s m) a tryReadTChan :: TChan (StateT s m) a -> STM (StateT s m) (Maybe a) peekTChan :: TChan (StateT s m) a -> STM (StateT s m) a tryPeekTChan :: TChan (StateT s m) a -> STM (StateT s m) (Maybe a) writeTChan :: TChan (StateT s m) a -> a -> STM (StateT s m) () unGetTChan :: TChan (StateT s m) a -> a -> STM (StateT s m) () isEmptyTChan :: TChan (StateT s m) a -> STM (StateT s m) Bool newTVarIO :: a -> StateT s m (TVar (StateT s m) a) readTVarIO :: TVar (StateT s m) a -> StateT s m a newTMVarIO :: a -> StateT s m (TMVar (StateT s m) a) newEmptyTMVarIO :: StateT s m (TMVar (StateT s m) a) newTQueueIO :: StateT s m (TQueue (StateT s m) a) newTBQueueIO :: Natural -> StateT s m (TBQueue (StateT s m) a) newTChanIO :: StateT s m (TChan (StateT s m) a) newBroadcastTChanIO :: StateT s m (TChan (StateT s m) a) | |
(Monoid w, MonadSTM m) => MonadSTM (WriterT w m) Source # | The underlying stm monad is also transformed. |
type STM (WriterT w m) = (stm :: Type -> Type) type TVar (WriterT w m) :: Type -> Type type TMVar (WriterT w m) :: Type -> Type type TQueue (WriterT w m) :: Type -> Type type TBQueue (WriterT w m) :: Type -> Type type TArray (WriterT w m) :: Type -> Type -> Type type TSem (WriterT w m) atomically :: HasCallStack => STM (WriterT w m) a -> WriterT w m a newTVar :: a -> STM (WriterT w m) (TVar (WriterT w m) a) readTVar :: TVar (WriterT w m) a -> STM (WriterT w m) a writeTVar :: TVar (WriterT w m) a -> a -> STM (WriterT w m) () orElse :: STM (WriterT w m) a -> STM (WriterT w m) a -> STM (WriterT w m) a modifyTVar :: TVar (WriterT w m) a -> (a -> a) -> STM (WriterT w m) () modifyTVar' :: TVar (WriterT w m) a -> (a -> a) -> STM (WriterT w m) () stateTVar :: TVar (WriterT w m) s -> (s -> (a, s)) -> STM (WriterT w m) a swapTVar :: TVar (WriterT w m) a -> a -> STM (WriterT w m) a check :: Bool -> STM (WriterT w m) () newTMVar :: a -> STM (WriterT w m) (TMVar (WriterT w m) a) newEmptyTMVar :: STM (WriterT w m) (TMVar (WriterT w m) a) takeTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) a tryTakeTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) (Maybe a) putTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) () tryPutTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) Bool readTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) a tryReadTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) (Maybe a) swapTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) a writeTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) Bool newTQueue :: STM (WriterT w m) (TQueue (WriterT w m) a) readTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) a tryReadTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) a tryPeekTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) flushTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) [a] writeTQueue :: TQueue (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) Bool unGetTQueue :: TQueue (WriterT w m) a -> a -> STM (WriterT w m) () newTBQueue :: Natural -> STM (WriterT w m) (TBQueue (WriterT w m) a) readTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) a tryReadTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) a tryPeekTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) flushTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) [a] writeTBQueue :: TBQueue (WriterT w m) a -> a -> STM (WriterT w m) () lengthTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Natural isEmptyTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Bool isFullTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Bool unGetTBQueue :: TBQueue (WriterT w m) a -> a -> STM (WriterT w m) () newTSem :: Integer -> STM (WriterT w m) (TSem (WriterT w m)) waitTSem :: TSem (WriterT w m) -> STM (WriterT w m) () signalTSem :: TSem (WriterT w m) -> STM (WriterT w m) () signalTSemN :: Natural -> TSem (WriterT w m) -> STM (WriterT w m) () newTChan :: STM (WriterT w m) (TChan (WriterT w m) a) newBroadcastTChan :: STM (WriterT w m) (TChan (WriterT w m) a) dupTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (TChan (WriterT w m) a) cloneTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (TChan (WriterT w m) a) readTChan :: TChan (WriterT w m) a -> STM (WriterT w m) a tryReadTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTChan :: TChan (WriterT w m) a -> STM (WriterT w m) a tryPeekTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (Maybe a) writeTChan :: TChan (WriterT w m) a -> a -> STM (WriterT w m) () unGetTChan :: TChan (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTChan :: TChan (WriterT w m) a -> STM (WriterT w m) Bool newTVarIO :: a -> WriterT w m (TVar (WriterT w m) a) readTVarIO :: TVar (WriterT w m) a -> WriterT w m a newTMVarIO :: a -> WriterT w m (TMVar (WriterT w m) a) newEmptyTMVarIO :: WriterT w m (TMVar (WriterT w m) a) newTQueueIO :: WriterT w m (TQueue (WriterT w m) a) newTBQueueIO :: Natural -> WriterT w m (TBQueue (WriterT w m) a) newTChanIO :: WriterT w m (TChan (WriterT w m) a) newBroadcastTChanIO :: WriterT w m (TChan (WriterT w m) a) | |
(Monoid w, MonadSTM m) => MonadSTM (WriterT w m) Source # | The underlying stm monad is also transformed. |
type STM (WriterT w m) = (stm :: Type -> Type) type TVar (WriterT w m) :: Type -> Type type TMVar (WriterT w m) :: Type -> Type type TQueue (WriterT w m) :: Type -> Type type TBQueue (WriterT w m) :: Type -> Type type TArray (WriterT w m) :: Type -> Type -> Type type TSem (WriterT w m) atomically :: HasCallStack => STM (WriterT w m) a -> WriterT w m a newTVar :: a -> STM (WriterT w m) (TVar (WriterT w m) a) readTVar :: TVar (WriterT w m) a -> STM (WriterT w m) a writeTVar :: TVar (WriterT w m) a -> a -> STM (WriterT w m) () orElse :: STM (WriterT w m) a -> STM (WriterT w m) a -> STM (WriterT w m) a modifyTVar :: TVar (WriterT w m) a -> (a -> a) -> STM (WriterT w m) () modifyTVar' :: TVar (WriterT w m) a -> (a -> a) -> STM (WriterT w m) () stateTVar :: TVar (WriterT w m) s -> (s -> (a, s)) -> STM (WriterT w m) a swapTVar :: TVar (WriterT w m) a -> a -> STM (WriterT w m) a check :: Bool -> STM (WriterT w m) () newTMVar :: a -> STM (WriterT w m) (TMVar (WriterT w m) a) newEmptyTMVar :: STM (WriterT w m) (TMVar (WriterT w m) a) takeTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) a tryTakeTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) (Maybe a) putTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) () tryPutTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) Bool readTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) a tryReadTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) (Maybe a) swapTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) a writeTMVar :: TMVar (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTMVar :: TMVar (WriterT w m) a -> STM (WriterT w m) Bool newTQueue :: STM (WriterT w m) (TQueue (WriterT w m) a) readTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) a tryReadTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) a tryPeekTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) flushTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) [a] writeTQueue :: TQueue (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTQueue :: TQueue (WriterT w m) a -> STM (WriterT w m) Bool unGetTQueue :: TQueue (WriterT w m) a -> a -> STM (WriterT w m) () newTBQueue :: Natural -> STM (WriterT w m) (TBQueue (WriterT w m) a) readTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) a tryReadTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) a tryPeekTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) (Maybe a) flushTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) [a] writeTBQueue :: TBQueue (WriterT w m) a -> a -> STM (WriterT w m) () lengthTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Natural isEmptyTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Bool isFullTBQueue :: TBQueue (WriterT w m) a -> STM (WriterT w m) Bool unGetTBQueue :: TBQueue (WriterT w m) a -> a -> STM (WriterT w m) () newTSem :: Integer -> STM (WriterT w m) (TSem (WriterT w m)) waitTSem :: TSem (WriterT w m) -> STM (WriterT w m) () signalTSem :: TSem (WriterT w m) -> STM (WriterT w m) () signalTSemN :: Natural -> TSem (WriterT w m) -> STM (WriterT w m) () newTChan :: STM (WriterT w m) (TChan (WriterT w m) a) newBroadcastTChan :: STM (WriterT w m) (TChan (WriterT w m) a) dupTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (TChan (WriterT w m) a) cloneTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (TChan (WriterT w m) a) readTChan :: TChan (WriterT w m) a -> STM (WriterT w m) a tryReadTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (Maybe a) peekTChan :: TChan (WriterT w m) a -> STM (WriterT w m) a tryPeekTChan :: TChan (WriterT w m) a -> STM (WriterT w m) (Maybe a) writeTChan :: TChan (WriterT w m) a -> a -> STM (WriterT w m) () unGetTChan :: TChan (WriterT w m) a -> a -> STM (WriterT w m) () isEmptyTChan :: TChan (WriterT w m) a -> STM (WriterT w m) Bool newTVarIO :: a -> WriterT w m (TVar (WriterT w m) a) readTVarIO :: TVar (WriterT w m) a -> WriterT w m a newTMVarIO :: a -> WriterT w m (TMVar (WriterT w m) a) newEmptyTMVarIO :: WriterT w m (TMVar (WriterT w m) a) newTQueueIO :: WriterT w m (TQueue (WriterT w m) a) newTBQueueIO :: Natural -> WriterT w m (TBQueue (WriterT w m) a) newTChanIO :: WriterT w m (TChan (WriterT w m) a) newBroadcastTChanIO :: WriterT w m (TChan (WriterT w m) a) | |
MonadSTM m => MonadSTM (ContT r m) Source # |
|
type STM (ContT r m) = (stm :: Type -> Type) type TVar (ContT r m) :: Type -> Type type TMVar (ContT r m) :: Type -> Type type TQueue (ContT r m) :: Type -> Type type TBQueue (ContT r m) :: Type -> Type type TArray (ContT r m) :: Type -> Type -> Type type TSem (ContT r m) atomically :: HasCallStack => STM (ContT r m) a -> ContT r m a newTVar :: a -> STM (ContT r m) (TVar (ContT r m) a) readTVar :: TVar (ContT r m) a -> STM (ContT r m) a writeTVar :: TVar (ContT r m) a -> a -> STM (ContT r m) () orElse :: STM (ContT r m) a -> STM (ContT r m) a -> STM (ContT r m) a modifyTVar :: TVar (ContT r m) a -> (a -> a) -> STM (ContT r m) () modifyTVar' :: TVar (ContT r m) a -> (a -> a) -> STM (ContT r m) () stateTVar :: TVar (ContT r m) s -> (s -> (a, s)) -> STM (ContT r m) a swapTVar :: TVar (ContT r m) a -> a -> STM (ContT r m) a check :: Bool -> STM (ContT r m) () newTMVar :: a -> STM (ContT r m) (TMVar (ContT r m) a) newEmptyTMVar :: STM (ContT r m) (TMVar (ContT r m) a) takeTMVar :: TMVar (ContT r m) a -> STM (ContT r m) a tryTakeTMVar :: TMVar (ContT r m) a -> STM (ContT r m) (Maybe a) putTMVar :: TMVar (ContT r m) a -> a -> STM (ContT r m) () tryPutTMVar :: TMVar (ContT r m) a -> a -> STM (ContT r m) Bool readTMVar :: TMVar (ContT r m) a -> STM (ContT r m) a tryReadTMVar :: TMVar (ContT r m) a -> STM (ContT r m) (Maybe a) swapTMVar :: TMVar (ContT r m) a -> a -> STM (ContT r m) a writeTMVar :: TMVar (ContT r m) a -> a -> STM (ContT r m) () isEmptyTMVar :: TMVar (ContT r m) a -> STM (ContT r m) Bool newTQueue :: STM (ContT r m) (TQueue (ContT r m) a) readTQueue :: TQueue (ContT r m) a -> STM (ContT r m) a tryReadTQueue :: TQueue (ContT r m) a -> STM (ContT r m) (Maybe a) peekTQueue :: TQueue (ContT r m) a -> STM (ContT r m) a tryPeekTQueue :: TQueue (ContT r m) a -> STM (ContT r m) (Maybe a) flushTQueue :: TQueue (ContT r m) a -> STM (ContT r m) [a] writeTQueue :: TQueue (ContT r m) a -> a -> STM (ContT r m) () isEmptyTQueue :: TQueue (ContT r m) a -> STM (ContT r m) Bool unGetTQueue :: TQueue (ContT r m) a -> a -> STM (ContT r m) () newTBQueue :: Natural -> STM (ContT r m) (TBQueue (ContT r m) a) readTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) a tryReadTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) (Maybe a) peekTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) a tryPeekTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) (Maybe a) flushTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) [a] writeTBQueue :: TBQueue (ContT r m) a -> a -> STM (ContT r m) () lengthTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) Natural isEmptyTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) Bool isFullTBQueue :: TBQueue (ContT r m) a -> STM (ContT r m) Bool unGetTBQueue :: TBQueue (ContT r m) a -> a -> STM (ContT r m) () newTSem :: Integer -> STM (ContT r m) (TSem (ContT r m)) waitTSem :: TSem (ContT r m) -> STM (ContT r m) () signalTSem :: TSem (ContT r m) -> STM (ContT r m) () signalTSemN :: Natural -> TSem (ContT r m) -> STM (ContT r m) () newTChan :: STM (ContT r m) (TChan (ContT r m) a) newBroadcastTChan :: STM (ContT r m) (TChan (ContT r m) a) dupTChan :: TChan (ContT r m) a -> STM (ContT r m) (TChan (ContT r m) a) cloneTChan :: TChan (ContT r m) a -> STM (ContT r m) (TChan (ContT r m) a) readTChan :: TChan (ContT r m) a -> STM (ContT r m) a tryReadTChan :: TChan (ContT r m) a -> STM (ContT r m) (Maybe a) peekTChan :: TChan (ContT r m) a -> STM (ContT r m) a tryPeekTChan :: TChan (ContT r m) a -> STM (ContT r m) (Maybe a) writeTChan :: TChan (ContT r m) a -> a -> STM (ContT r m) () unGetTChan :: TChan (ContT r m) a -> a -> STM (ContT r m) () isEmptyTChan :: TChan (ContT r m) a -> STM (ContT r m) Bool newTVarIO :: a -> ContT r m (TVar (ContT r m) a) readTVarIO :: TVar (ContT r m) a -> ContT r m a newTMVarIO :: a -> ContT r m (TMVar (ContT r m) a) newEmptyTMVarIO :: ContT r m (TMVar (ContT r m) a) newTQueueIO :: ContT r m (TQueue (ContT r m) a) newTBQueueIO :: Natural -> ContT r m (TBQueue (ContT r m) a) newTChanIO :: ContT r m (TChan (ContT r m) a) newBroadcastTChanIO :: ContT r m (TChan (ContT r m) a) | |
(Monoid w, MonadSTM m) => MonadSTM (RWST r w s m) Source # | The underlying stm monad is also transformed. |
type STM (RWST r w s m) = (stm :: Type -> Type) type TVar (RWST r w s m) :: Type -> Type type TMVar (RWST r w s m) :: Type -> Type type TQueue (RWST r w s m) :: Type -> Type type TBQueue (RWST r w s m) :: Type -> Type type TArray (RWST r w s m) :: Type -> Type -> Type type TSem (RWST r w s m) atomically :: HasCallStack => STM (RWST r w s m) a -> RWST r w s m a newTVar :: a -> STM (RWST r w s m) (TVar (RWST r w s m) a) readTVar :: TVar (RWST r w s m) a -> STM (RWST r w s m) a writeTVar :: TVar (RWST r w s m) a -> a -> STM (RWST r w s m) () orElse :: STM (RWST r w s m) a -> STM (RWST r w s m) a -> STM (RWST r w s m) a modifyTVar :: TVar (RWST r w s m) a -> (a -> a) -> STM (RWST r w s m) () modifyTVar' :: TVar (RWST r w s m) a -> (a -> a) -> STM (RWST r w s m) () stateTVar :: TVar (RWST r w s m) s0 -> (s0 -> (a, s0)) -> STM (RWST r w s m) a swapTVar :: TVar (RWST r w s m) a -> a -> STM (RWST r w s m) a check :: Bool -> STM (RWST r w s m) () newTMVar :: a -> STM (RWST r w s m) (TMVar (RWST r w s m) a) newEmptyTMVar :: STM (RWST r w s m) (TMVar (RWST r w s m) a) takeTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) a tryTakeTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) putTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) () tryPutTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) Bool readTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) a tryReadTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) swapTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) a writeTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) Bool newTQueue :: STM (RWST r w s m) (TQueue (RWST r w s m) a) readTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) a tryReadTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) flushTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) [a] writeTQueue :: TQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) Bool unGetTQueue :: TQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () newTBQueue :: Natural -> STM (RWST r w s m) (TBQueue (RWST r w s m) a) readTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) a tryReadTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) flushTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) [a] writeTBQueue :: TBQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () lengthTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Natural isEmptyTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Bool isFullTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Bool unGetTBQueue :: TBQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () newTSem :: Integer -> STM (RWST r w s m) (TSem (RWST r w s m)) waitTSem :: TSem (RWST r w s m) -> STM (RWST r w s m) () signalTSem :: TSem (RWST r w s m) -> STM (RWST r w s m) () signalTSemN :: Natural -> TSem (RWST r w s m) -> STM (RWST r w s m) () newTChan :: STM (RWST r w s m) (TChan (RWST r w s m) a) newBroadcastTChan :: STM (RWST r w s m) (TChan (RWST r w s m) a) dupTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (TChan (RWST r w s m) a) cloneTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (TChan (RWST r w s m) a) readTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) a tryReadTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) writeTChan :: TChan (RWST r w s m) a -> a -> STM (RWST r w s m) () unGetTChan :: TChan (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) Bool newTVarIO :: a -> RWST r w s m (TVar (RWST r w s m) a) readTVarIO :: TVar (RWST r w s m) a -> RWST r w s m a newTMVarIO :: a -> RWST r w s m (TMVar (RWST r w s m) a) newEmptyTMVarIO :: RWST r w s m (TMVar (RWST r w s m) a) newTQueueIO :: RWST r w s m (TQueue (RWST r w s m) a) newTBQueueIO :: Natural -> RWST r w s m (TBQueue (RWST r w s m) a) newTChanIO :: RWST r w s m (TChan (RWST r w s m) a) newBroadcastTChanIO :: RWST r w s m (TChan (RWST r w s m) a) | |
(Monoid w, MonadSTM m) => MonadSTM (RWST r w s m) Source # | The underlying stm monad is also transformed. |
type STM (RWST r w s m) = (stm :: Type -> Type) type TVar (RWST r w s m) :: Type -> Type type TMVar (RWST r w s m) :: Type -> Type type TQueue (RWST r w s m) :: Type -> Type type TBQueue (RWST r w s m) :: Type -> Type type TArray (RWST r w s m) :: Type -> Type -> Type type TSem (RWST r w s m) atomically :: HasCallStack => STM (RWST r w s m) a -> RWST r w s m a newTVar :: a -> STM (RWST r w s m) (TVar (RWST r w s m) a) readTVar :: TVar (RWST r w s m) a -> STM (RWST r w s m) a writeTVar :: TVar (RWST r w s m) a -> a -> STM (RWST r w s m) () orElse :: STM (RWST r w s m) a -> STM (RWST r w s m) a -> STM (RWST r w s m) a modifyTVar :: TVar (RWST r w s m) a -> (a -> a) -> STM (RWST r w s m) () modifyTVar' :: TVar (RWST r w s m) a -> (a -> a) -> STM (RWST r w s m) () stateTVar :: TVar (RWST r w s m) s0 -> (s0 -> (a, s0)) -> STM (RWST r w s m) a swapTVar :: TVar (RWST r w s m) a -> a -> STM (RWST r w s m) a check :: Bool -> STM (RWST r w s m) () newTMVar :: a -> STM (RWST r w s m) (TMVar (RWST r w s m) a) newEmptyTMVar :: STM (RWST r w s m) (TMVar (RWST r w s m) a) takeTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) a tryTakeTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) putTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) () tryPutTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) Bool readTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) a tryReadTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) swapTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) a writeTMVar :: TMVar (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTMVar :: TMVar (RWST r w s m) a -> STM (RWST r w s m) Bool newTQueue :: STM (RWST r w s m) (TQueue (RWST r w s m) a) readTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) a tryReadTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) flushTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) [a] writeTQueue :: TQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTQueue :: TQueue (RWST r w s m) a -> STM (RWST r w s m) Bool unGetTQueue :: TQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () newTBQueue :: Natural -> STM (RWST r w s m) (TBQueue (RWST r w s m) a) readTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) a tryReadTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) flushTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) [a] writeTBQueue :: TBQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () lengthTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Natural isEmptyTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Bool isFullTBQueue :: TBQueue (RWST r w s m) a -> STM (RWST r w s m) Bool unGetTBQueue :: TBQueue (RWST r w s m) a -> a -> STM (RWST r w s m) () newTSem :: Integer -> STM (RWST r w s m) (TSem (RWST r w s m)) waitTSem :: TSem (RWST r w s m) -> STM (RWST r w s m) () signalTSem :: TSem (RWST r w s m) -> STM (RWST r w s m) () signalTSemN :: Natural -> TSem (RWST r w s m) -> STM (RWST r w s m) () newTChan :: STM (RWST r w s m) (TChan (RWST r w s m) a) newBroadcastTChan :: STM (RWST r w s m) (TChan (RWST r w s m) a) dupTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (TChan (RWST r w s m) a) cloneTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (TChan (RWST r w s m) a) readTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) a tryReadTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) peekTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) a tryPeekTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) (Maybe a) writeTChan :: TChan (RWST r w s m) a -> a -> STM (RWST r w s m) () unGetTChan :: TChan (RWST r w s m) a -> a -> STM (RWST r w s m) () isEmptyTChan :: TChan (RWST r w s m) a -> STM (RWST r w s m) Bool newTVarIO :: a -> RWST r w s m (TVar (RWST r w s m) a) readTVarIO :: TVar (RWST r w s m) a -> RWST r w s m a newTMVarIO :: a -> RWST r w s m (TMVar (RWST r w s m) a) newEmptyTMVarIO :: RWST r w s m (TMVar (RWST r w s m) a) newTQueueIO :: RWST r w s m (TQueue (RWST r w s m) a) newTBQueueIO :: Natural -> RWST r w s m (TBQueue (RWST r w s m) a) newTChanIO :: RWST r w s m (TChan (RWST r w s m) a) newBroadcastTChanIO :: RWST r w s m (TChan (RWST r w s m) a) |