unliftio-0.2.20: The MonadUnliftIO typeclass for unlifting monads to IO (batteries included)
Safe HaskellNone
LanguageHaskell2010

UnliftIO.STM

Description

Lifted version of Control.Concurrent.STM

Since: 0.2.1.0

Synopsis

Core

data STM a #

A monad supporting atomic memory transactions.

Instances

Instances details
Monad STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

(>>=) :: STM a -> (a -> STM b) -> STM b #

(>>) :: STM a -> STM b -> STM b #

return :: a -> STM a #

Functor STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

fmap :: (a -> b) -> STM a -> STM b #

(<$) :: a -> STM b -> STM a #

Applicative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

pure :: a -> STM a #

(<*>) :: STM (a -> b) -> STM a -> STM b #

liftA2 :: (a -> b -> c) -> STM a -> STM b -> STM c #

(*>) :: STM a -> STM b -> STM b #

(<*) :: STM a -> STM b -> STM a #

Alternative STM

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

empty :: STM a #

(<|>) :: STM a -> STM a -> STM a #

some :: STM a -> STM [a] #

many :: STM a -> STM [a] #

MonadPlus STM

Since: base-4.3.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

mzero :: STM a #

mplus :: STM a -> STM a -> STM a #

MArray TArray e STM 
Instance details

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

atomically :: MonadIO m => STM a -> m a Source #

Lifted version of atomically

Since: 0.2.1.0

retrySTM :: STM a Source #

Renamed retry for unqualified export

Since: 0.2.1.0

checkSTM :: Bool -> STM () Source #

Renamed check for unqualified export

Since: 0.2.1.0

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

Compose two alternative STM actions (GHC only).

If the first action completes without retrying then it forms the result of the orElse. Otherwise, if the first action retries, then the second action is tried in its place. If both actions retry then the orElse as a whole retries.

TVar

data TVar a #

Shared memory locations that support atomic memory transactions.

Instances

Instances details
Eq (TVar a)

Since: base-4.8.0.0

Instance details

Defined in GHC.Conc.Sync

Methods

(==) :: TVar a -> TVar a -> Bool #

(/=) :: TVar a -> TVar a -> Bool #

newTVarIO :: MonadIO m => a -> m (TVar a) Source #

Lifted version of newTVarIO

Since: 0.2.1.0

readTVarIO :: MonadIO m => TVar a -> m a Source #

Lifted version of readTVarIO

Since: 0.2.1.0

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

Create a new TVar holding a value supplied

readTVar :: TVar a -> STM a #

Return the current value stored in a TVar.

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

Write the supplied value into a TVar.

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

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

Swap the contents of a TVar for a new value.

Since: stm-2.3

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

data TMVar a #

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.

Instances

Instances details
Eq (TMVar a) 
Instance details

Defined in Control.Concurrent.STM.TMVar

Methods

(==) :: TMVar a -> TMVar a -> Bool #

(/=) :: TMVar a -> TMVar a -> Bool #

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

Create a TMVar which contains the supplied value.

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

takeTMVar :: TMVar a -> STM a #

Return the contents of the TMVar. If the TMVar is currently empty, the transaction will retry. After a takeTMVar, the TMVar is left empty.

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

Put a value into a TMVar. If the TMVar is currently full, putTMVar will retry.

readTMVar :: TMVar a -> STM a #

This is a combination of takeTMVar and putTMVar; ie. it takes the value from the TMVar, puts it back, and also returns it.

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

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

Swap the contents of a TMVar for a new value.

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 a if the TMVar was full with contents a. After tryTakeTMVar, the TMVar is left empty.

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

A version of putTMVar that does not retry. The tryPutTMVar function attempts to put the value a into the TMVar, returning True if it was successful, or False otherwise.

isEmptyTMVar :: TMVar a -> STM Bool #

Check whether a given TMVar is empty.

mkWeakTMVar :: MonadUnliftIO m => TMVar a -> m () -> m (Weak (TMVar a)) Source #

Lifted version of mkWeakTMVar

Since: 0.2.1.0

TChan

data TChan a #

TChan is an abstract type representing an unbounded FIFO channel.

Instances

Instances details
Eq (TChan a) 
Instance details

Defined in Control.Concurrent.STM.TChan

Methods

(==) :: TChan a -> TChan a -> Bool #

(/=) :: TChan a -> TChan a -> Bool #

newTChan :: STM (TChan a) #

Build and return a new instance of TChan

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 message

The 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

readTChan :: TChan a -> STM a #

Read the next value from the TChan.

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.

isEmptyTChan :: TChan a -> STM Bool #

Returns True if the supplied TChan is empty.

TQueue

data TQueue a #

TQueue is an abstract type representing an unbounded FIFO channel.

Since: stm-2.4

Instances

Instances details
Eq (TQueue a) 
Instance details

Defined in Control.Concurrent.STM.TQueue

Methods

(==) :: TQueue a -> TQueue a -> Bool #

(/=) :: TQueue a -> TQueue a -> Bool #

newTQueue :: STM (TQueue a) #

Build and returns a new instance of TQueue

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.

isEmptyTQueue :: TQueue a -> STM Bool #

Returns True if the supplied TQueue is empty.

TBQueue

data TBQueue a #

TBQueue is an abstract type representing a bounded FIFO channel.

Since: stm-2.4

Instances

Instances details
Eq (TBQueue a) 
Instance details

Defined in Control.Concurrent.STM.TBQueue

Methods

(==) :: TBQueue a -> TBQueue a -> Bool #

(/=) :: TBQueue a -> TBQueue a -> Bool #

newTBQueue #

Arguments

:: Natural

maximum number of elements the queue can hold

-> STM (TBQueue a) 

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.

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.

isEmptyTBQueue :: TBQueue a -> STM Bool #

Returns True if the supplied TBQueue is empty.

isFullTBQueue :: TBQueue a -> STM Bool #

Returns True if the supplied TBQueue is full.

Since: stm-2.4.3