relude-1.0.0.1: Safe, performant, user-friendly and lightweight Haskell Standard Library
Copyright(c) 2016 Stephen Diehl
(c) 2016-2018 Serokell
(c) 2018-2021 Kowainik
LicenseMIT
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellSafe
LanguageHaskell2010

Relude.Lifted.Concurrent

Description

Lifted MVar and STM functions.

Synopsis

MVar

data MVar a #

An MVar (pronounced "em-var") 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
NFData1 MVar

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> MVar a -> () #

Eq (MVar a)

Since: base-4.1.0.0

Instance details

Defined in GHC.MVar

Methods

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

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

NFData (MVar a)

NOTE: Only strict in the reference and not the referenced value.

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: MVar a -> () #

newEmptyMVar :: MonadIO m => m (MVar a) Source #

Lifted to MonadIO version of newEmptyMVar.

newMVar :: MonadIO m => a -> m (MVar a) Source #

Lifted to MonadIO version of newMVar.

putMVar :: MonadIO m => MVar a -> a -> m () Source #

Lifted to MonadIO version of putMVar.

readMVar :: MonadIO m => MVar a -> m a Source #

Lifted to MonadIO version of readMVar.

swapMVar :: MonadIO m => MVar a -> a -> m a Source #

Lifted to MonadIO version of swapMVar.

takeMVar :: MonadIO m => MVar a -> m a Source #

Lifted to MonadIO version of takeMVar.

tryPutMVar :: MonadIO m => MVar a -> a -> m Bool Source #

Lifted to MonadIO version of tryPutMVar.

tryReadMVar :: MonadIO m => MVar a -> m (Maybe a) Source #

Lifted to MonadIO version of tryReadMVar.

tryTakeMVar :: MonadIO m => MVar a -> m (Maybe a) Source #

Lifted to MonadIO version of tryTakeMVar.

STM

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 #

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

Lifted to MonadIO version of atomically.

throwSTM :: Exception e => e -> STM a #

A variant of throw that can only be used within the STM monad.

Throwing an exception in STM aborts the transaction and propagates the exception. If the exception is caught via catchSTM, only the changes enclosed by the catch are rolled back; changes made outside of catchSTM persist.

If the exception is not caught inside of the STM, it is re-thrown by atomically, and the entire STM is rolled back.

Although throwSTM has a type that is an instance of the type of throw, the two functions are subtly different:

throw e    `seq` x  ===> throw e
throwSTM e `seq` x  ===> x

The first example will cause the exception e to be raised, whereas the second one won't. In fact, throwSTM will only cause an exception to be raised when it is used within the STM monad. The throwSTM variant should be used in preference to throw to raise an exception within the STM monad because it guarantees ordering with respect to other STM operations, whereas throw does not.

catchSTM :: Exception e => STM a -> (e -> STM a) -> STM a #

Exception handling within STM actions.

catchSTM m f catches any exception thrown by m using throwSTM, using the function f to handle the exception. If an exception is thrown, any changes made by m are rolled back, but changes prior to m persist.

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 to MonadIO version of newTVarIO.

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

Lifted to MonadIO version of readTVarIO.

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

Strict version of modifyTVar.

Since: stm-2.3

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.

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 to MonadIO version of newTMVarIO.

newEmptyTMVarIO :: MonadIO m => m (TMVar a) Source #

Lifted to MonadIO version of newEmptyTMVarIO.

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 :: TMVar a -> IO () -> IO (Weak (TMVar a)) #

Make a Weak pointer to a TMVar, using the second argument as a finalizer to run when the TMVar is garbage-collected.

Since: stm-2.4.4