| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
UnliftIO.STM
Description
Lifted version of Control.Concurrent.STM
Since: 0.2.1.0
Synopsis
- data STM a
- atomically :: MonadIO m => STM a -> m a
- retrySTM :: STM a
- checkSTM :: Bool -> STM ()
- orElse :: STM a -> STM a -> STM a
- data TVar a
- newTVarIO :: MonadIO m => a -> m (TVar a)
- readTVarIO :: MonadIO m => TVar a -> m a
- newTVar :: a -> STM (TVar a)
- readTVar :: TVar a -> STM a
- writeTVar :: TVar a -> a -> STM ()
- modifyTVar :: TVar a -> (a -> a) -> STM ()
- modifyTVar' :: TVar a -> (a -> a) -> STM ()
- stateTVar :: TVar s -> (s -> (a, s)) -> STM a
- swapTVar :: TVar a -> a -> STM a
- registerDelay :: MonadIO m => Int -> m (TVar Bool)
- mkWeakTVar :: MonadUnliftIO m => TVar a -> m () -> m (Weak (TVar a))
- data TMVar a
- newTMVar :: a -> STM (TMVar a)
- newEmptyTMVar :: STM (TMVar a)
- newTMVarIO :: MonadIO m => a -> m (TMVar a)
- newEmptyTMVarIO :: MonadIO m => m (TMVar a)
- takeTMVar :: TMVar a -> STM a
- putTMVar :: TMVar a -> a -> STM ()
- readTMVar :: TMVar a -> STM a
- writeTMVar :: TMVar a -> a -> STM ()
- tryReadTMVar :: TMVar a -> STM (Maybe a)
- swapTMVar :: TMVar a -> a -> STM a
- tryTakeTMVar :: TMVar a -> STM (Maybe a)
- tryPutTMVar :: TMVar a -> a -> STM Bool
- isEmptyTMVar :: TMVar a -> STM Bool
- mkWeakTMVar :: MonadUnliftIO m => TMVar a -> m () -> m (Weak (TMVar a))
- data TChan a
- newTChan :: STM (TChan a)
- newTChanIO :: MonadIO m => m (TChan a)
- newBroadcastTChan :: STM (TChan a)
- newBroadcastTChanIO :: MonadIO m => m (TChan a)
- dupTChan :: TChan a -> STM (TChan a)
- cloneTChan :: TChan a -> STM (TChan a)
- readTChan :: TChan a -> STM a
- tryReadTChan :: TChan a -> STM (Maybe a)
- peekTChan :: TChan a -> STM a
- tryPeekTChan :: TChan a -> STM (Maybe a)
- writeTChan :: TChan a -> a -> STM ()
- unGetTChan :: TChan a -> a -> STM ()
- isEmptyTChan :: TChan a -> STM Bool
- data TQueue a
- newTQueue :: STM (TQueue a)
- newTQueueIO :: MonadIO m => m (TQueue a)
- readTQueue :: TQueue a -> STM a
- tryReadTQueue :: TQueue a -> STM (Maybe a)
- peekTQueue :: TQueue a -> STM a
- tryPeekTQueue :: TQueue a -> STM (Maybe a)
- writeTQueue :: TQueue a -> a -> STM ()
- unGetTQueue :: TQueue a -> a -> STM ()
- isEmptyTQueue :: TQueue a -> STM Bool
- data TBQueue a
- newTBQueue :: Natural -> STM (TBQueue a)
- newTBQueueIO :: MonadIO m => Natural -> m (TBQueue a)
- readTBQueue :: TBQueue a -> STM a
- tryReadTBQueue :: TBQueue a -> STM (Maybe a)
- flushTBQueue :: TBQueue a -> STM [a]
- peekTBQueue :: TBQueue a -> STM a
- tryPeekTBQueue :: TBQueue a -> STM (Maybe a)
- writeTBQueue :: TBQueue a -> a -> STM ()
- unGetTBQueue :: TBQueue a -> a -> STM ()
- lengthTBQueue :: TBQueue a -> STM Natural
- isEmptyTBQueue :: TBQueue a -> STM Bool
- isFullTBQueue :: TBQueue a -> STM Bool
Core
A monad supporting atomic memory transactions.
Instances
| Alternative STM | Takes the first non- Since: base-4.8.0.0 | 
| Applicative STM | Since: base-4.8.0.0 | 
| Functor STM | Since: base-4.3.0.0 | 
| Monad STM | Since: base-4.3.0.0 | 
| MonadPlus STM | Takes the first non- Since: base-4.3.0.0 | 
| MonadCatch STM | |
| Defined in Control.Monad.Catch | |
| MonadThrow STM | |
| Defined in Control.Monad.Catch Methods throwM :: (HasCallStack, Exception e) => e -> STM a # | |
| MArray TArray e STM | |
| Defined in Control.Concurrent.STM.TArray Methods getBounds :: Ix i => TArray i e -> STM (i, i) # getNumElements :: Ix i => TArray i e -> STM Int newArray :: Ix i => (i, i) -> e -> STM (TArray i e) # newArray_ :: Ix i => (i, i) -> STM (TArray i e) # unsafeNewArray_ :: Ix i => (i, i) -> STM (TArray i e) unsafeRead :: Ix i => TArray i e -> Int -> STM e unsafeWrite :: Ix i => TArray i e -> Int -> e -> STM () | |
| Monoid a => Monoid (STM a) | Since: base-4.17.0.0 | 
| Semigroup a => Semigroup (STM a) | Since: base-4.17.0.0 | 
atomically :: MonadIO m => STM a -> m a Source #
Lifted version of atomically
Since: 0.2.1.0
TVar
Shared memory locations that support atomic memory transactions.
readTVarIO :: MonadIO m => TVar a -> m a Source #
Lifted version of readTVarIO
Since: 0.2.1.0
modifyTVar :: TVar a -> (a -> a) -> STM () #
Mutate the contents of a TVar. N.B., this version is
 non-strict.
Since: stm-2.3
modifyTVar' :: TVar a -> (a -> a) -> STM () #
Strict version of modifyTVar.
Since: stm-2.3
stateTVar :: TVar s -> (s -> (a, s)) -> STM a #
Like modifyTVar' but the function is a simple state transition that can
 return a side value which is passed on as the result of the STM.
Since: stm-2.5.0
registerDelay :: MonadIO m => Int -> m (TVar Bool) Source #
Lifted version of registerDelay
Since: 0.2.1.0
mkWeakTVar :: MonadUnliftIO m => TVar a -> m () -> m (Weak (TVar a)) Source #
Lifted version of mkWeakTVar
Since: 0.2.1.0
TMVar
A TMVar is a synchronising variable, used
for communication between concurrent threads.  It can be thought of
as a box, which may be empty or full.
newEmptyTMVar :: STM (TMVar a) #
Create a TMVar which is initially empty.
newTMVarIO :: MonadIO m => a -> m (TMVar a) Source #
Lifted version of newTMVarIO
Since: 0.2.1.0
newEmptyTMVarIO :: MonadIO m => m (TMVar a) Source #
Lifted version of newEmptyTMVarIO
Since: 0.2.1.0
writeTMVar :: TMVar a -> a -> STM () #
Non-blocking write of a new value to a TMVar
 Puts if empty. Replaces if populated.
tryReadTMVar :: TMVar a -> STM (Maybe a) #
A version of readTMVar which does not retry. Instead it
 returns Nothing if no value is available.
Since: stm-2.3
tryTakeTMVar :: TMVar a -> STM (Maybe a) #
A version of takeTMVar that does not retry.  The tryTakeTMVar
 function returns Nothing if the TMVar was empty, or Just aTMVar was full with contents a.  After tryTakeTMVar, the
 TMVar is left empty.
tryPutTMVar :: TMVar a -> a -> STM Bool #
mkWeakTMVar :: MonadUnliftIO m => TMVar a -> m () -> m (Weak (TMVar a)) Source #
Lifted version of mkWeakTMVar
Since: 0.2.1.0
TChan
TChan is an abstract type representing an unbounded FIFO channel.
newTChanIO :: MonadIO m => m (TChan a) Source #
Lifted version of newTChanIO
Since: 0.2.1.0
newBroadcastTChan :: STM (TChan a) #
Create a write-only TChan.  More precisely, readTChan will retry
 even after items have been written to the channel.  The only way to read
 a broadcast channel is to duplicate it with dupTChan.
Consider a server that broadcasts messages to clients:
serve :: TChan Message -> Client -> IO loop
serve broadcastChan client = do
    myChan <- dupTChan broadcastChan
    forever $ do
        message <- readTChan myChan
        send client messageThe problem with using newTChan to create the broadcast channel is that if
 it is only written to and never read, items will pile up in memory.  By
 using newBroadcastTChan to create the broadcast channel, items can be
 garbage collected after clients have seen them.
Since: stm-2.4
newBroadcastTChanIO :: MonadIO m => m (TChan a) Source #
Lifted version of newBroadcastTChanIO
Since: 0.2.1.0
dupTChan :: TChan a -> STM (TChan a) #
Duplicate a TChan: the duplicate channel begins empty, but data written to
 either channel from then on will be available from both.  Hence this creates
 a kind of broadcast channel, where data written by anyone is seen by
 everyone else.
cloneTChan :: TChan a -> STM (TChan a) #
Clone a TChan: similar to dupTChan, but the cloned channel starts with the
 same content available as the original channel.
Since: stm-2.4
tryReadTChan :: TChan a -> STM (Maybe a) #
A version of readTChan which does not retry. Instead it
 returns Nothing if no value is available.
Since: stm-2.3
peekTChan :: TChan a -> STM a #
Get the next value from the TChan without removing it,
 retrying if the channel is empty.
Since: stm-2.3
tryPeekTChan :: TChan a -> STM (Maybe a) #
A version of peekTChan which does not retry. Instead it
 returns Nothing if no value is available.
Since: stm-2.3
writeTChan :: TChan a -> a -> STM () #
Write a value to a TChan.
unGetTChan :: TChan a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
TQueue
TQueue is an abstract type representing an unbounded FIFO channel.
Since: stm-2.4
newTQueueIO :: MonadIO m => m (TQueue a) Source #
Lifted version of newTQueueIO
Since: 0.2.1.0
readTQueue :: TQueue a -> STM a #
Read the next value from the TQueue.
tryReadTQueue :: TQueue a -> STM (Maybe a) #
A version of readTQueue which does not retry. Instead it
 returns Nothing if no value is available.
peekTQueue :: TQueue a -> STM a #
Get the next value from the TQueue without removing it,
 retrying if the channel is empty.
tryPeekTQueue :: TQueue a -> STM (Maybe a) #
A version of peekTQueue which does not retry. Instead it
 returns Nothing if no value is available.
writeTQueue :: TQueue a -> a -> STM () #
Write a value to a TQueue.
unGetTQueue :: TQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read.
TBQueue
TBQueue is an abstract type representing a bounded FIFO channel.
Since: stm-2.4
Builds and returns a new instance of TBQueue.
newTBQueueIO :: MonadIO m => Natural -> m (TBQueue a) Source #
Lifted version of newTBQueueIO
Since: 0.2.1.0
readTBQueue :: TBQueue a -> STM a #
Read the next value from the TBQueue.
tryReadTBQueue :: TBQueue a -> STM (Maybe a) #
A version of readTBQueue which does not retry. Instead it
 returns Nothing if no value is available.
flushTBQueue :: TBQueue a -> STM [a] #
Efficiently read the entire contents of a TBQueue into a list. This
 function never retries.
Since: stm-2.4.5
peekTBQueue :: TBQueue a -> STM a #
Get the next value from the TBQueue without removing it,
 retrying if the channel is empty.
tryPeekTBQueue :: TBQueue a -> STM (Maybe a) #
A version of peekTBQueue which does not retry. Instead it
 returns Nothing if no value is available.
writeTBQueue :: TBQueue a -> a -> STM () #
Write a value to a TBQueue; blocks if the queue is full.
unGetTBQueue :: TBQueue a -> a -> STM () #
Put a data item back onto a channel, where it will be the next item read. Blocks if the queue is full.