primal-0.3.0.0: Primeval world of Haskell.
Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Control.Prim.Concurrent.MVar

Description

 
Synopsis

MVar

data MVar a s Source #

Mutable variable that can either be empty or full. Same as MVar, but works with any state token therefore it is also usable within ST monad.

Since: 0.3.0

Constructors

MVar (MVar# s a) 

Instances

Instances details
Eq (MVar a s) Source #

Calls isSameMVar

Instance details

Defined in Control.Prim.Concurrent.MVar

Methods

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

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

isEmptyMVar :: forall a m s. MonadPrim s m => MVar a s -> m Bool Source #

Checks whether supplied MVar is empty.

Since: 0.3.0

isSameMVar :: forall a s. MVar a s -> MVar a s -> Bool Source #

Checks whether supplied MVars refer to the exact same one.

Since: 0.3.0

Create

newMVar :: forall a m s. MonadPrim s m => a -> m (MVar a s) Source #

Construct an MVar with initial value in it, which is evaluated to WHNF

Since: 0.3.0

newLazyMVar :: forall a m s. MonadPrim s m => a -> m (MVar a s) Source #

Construct an MVar with initial value in it.

Same as newMVar from base, but works in any MonadPrim.

Since: 0.3.0

newDeepMVar :: forall a m s. (NFData a, MonadPrim s m) => a -> m (MVar a s) Source #

Construct an MVar with initial value in it.

Since: 0.3.0

newEmptyMVar :: forall a m s. MonadPrim s m => m (MVar a s) Source #

Construct an empty MVar.

Same as newEmptyMVar from base, but works in any MonadPrim.

Since: 0.3.0

Write

putMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m () Source #

Write a value into an MVar. Blocks the current thread if MVar is empty and waits until it gets filled by another thread. Evaluates the argument to WHNF prior to writing it.

Since: 0.3.0

putLazyMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m () Source #

Same as putMVar, but allows to write a thunk into an MVar.

Same as putMVar from base, but works in any MonadPrim.

Since: 0.3.0

putDeepMVar :: forall a m s. (NFData a, MonadPrim s m) => MVar a s -> a -> m () Source #

Same as putMVar, but evaluates the argument to NF prior to writing it.

Since: 0.3.0

tryPutMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m Bool Source #

Attempt to write a value into MVar. Unlike putMVar this function never blocks. It also returns True if MVar was empty and placing the value in it turned out to be successfull and False otherwise. Evaluates the supplied argumetn to WHNF prior to attempting a write operation.

Since: 0.3.0

tryPutLazyMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m Bool Source #

Same as tryPutMVar, but allows to put thunks into an MVar

Same as tryPutMVar from base, but works in any MonadPrim.

Since: 0.3.0

tryPutDeepMVar :: forall a m s. (NFData a, MonadPrim s m) => MVar a s -> a -> m Bool Source #

Same as tryPutMVar, but evaluates the argument to NF prior to attempting to write into the MVar

Since: 0.3.0

writeMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m () Source #

Write a value into the MVar regardless if it is currently empty or not. If there is a currently a value it will in the MVar it will simply b discarded. However, if there is another thread that is blocked on attempt to write into this MVar, current operation will block on attempt to fill the MVar. Therefore writeMVar is not atomic. Argument is evaluated to WHNF prior to clearing the contents of MVar

Since: 0.3.0

Read

readMVar :: forall a m s. MonadPrim s m => MVar a s -> m a Source #

Get the value from MVar atomically without affecting its contents. Blocks the current thread if the MVar is currently empty and waits until another thread fills it with a value.

Same as readMVar from base, but works in any MonadPrim.

Since: 0.3.0

tryReadMVar :: forall a m s. MonadPrim s m => MVar a s -> m (Maybe a) Source #

Get the value from MVar atomically without affecting its contents. It does not block and returns the immediately or Nothing if the supplied MVar was empty.

Same as tryReadMVar from base, but works in any MonadPrim.

Since: 0.3.0

takeMVar :: forall a m s. MonadPrim s m => MVar a s -> m a Source #

Remove the value from MVar and return it. Blocks the cuurent thread if MVar is empty and waits until antoher thread fills it.

Same as takeMVar from base, but works in any MonadPrim.

Since: 0.3.0

tryTakeMVar :: forall a m s. MonadPrim s m => MVar a s -> m (Maybe a) Source #

Remove the value from MVar and return it immediately without blocking. Nothing is returned if MVar was empty.

Same as tryTakeMVar from base, but works in any MonadPrim.

Since: 0.3.0

clearMVar :: forall a m s. MonadPrim s m => MVar a s -> m () Source #

Remove a value from an MVar, unless it was already empty. It effectively empties the MVar however note that by the time this action returns there is a possibility that another thread might have filled it with a different value.

Since: 0.3.0

Modify

swapMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m a Source #

Replace current value in an MVar with a new one. Supplied value is evaluated to WHNF prior to current value being extracted from the MVar. If MVar is currently empty this operation will block the current thread until it gets filled in another thread. Furthermore it is possible for another thread to fill the MVar after the old value is extracted, but before the new one has a chance to placed inside the MVar, thus blocking current thread once more until another thread empties this MVar. In other words this operation is not atomic.

Since: 0.3.0

swapLazyMVar :: forall a m s. MonadPrim s m => MVar a s -> a -> m a Source #

Same as swapMVar, but allows writing thunks into the MVar.

Same as swapMVar from base, but works in any MonadUnliftPrim.

Since: 0.3.0

swapDeepMVar :: forall a m s. (NFData a, MonadPrim s m) => MVar a s -> a -> m a Source #

Same as swapMVar, but evaluates the argument value to NF.

Since: 0.3.0

withMVar :: forall a b m. MonadUnliftPrim RW m => MVar a RW -> (a -> m b) -> m b Source #

Apply an action to the contents of an MVar. Current thread will be blocked if supplied MVar is empty and will wait until another thread fills it with a value. While the action is being appplied other threads should not put anything into the MVar otherwise current thread will get blocked again until another thread empties the MVar. In other words this is not an atomic operation, but it is exception safe, since the contents of MVar are restored regardless of the outcome of supplied action.

Same as withMVar from base, but works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

withMVarMasked :: forall a b m. MonadUnliftPrim RW m => MVar a RW -> (a -> m b) -> m b Source #

Same as withMVar, but with supplied action executed with async exceptions masked, but still interruptable.

Same as withMVarMasked from base, but works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

modifyMVar_ :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m () Source #

Apply a monadic action to the contents of supplied MVar. Provides the same guarantees as withMVar.

Same as modifyMVar_ from base, but is strict with respect to result of the action and works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

modifyMVarMasked_ :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m () Source #

Same as modifyMVarMAsked_, but the supplied action has async exceptions masked.

Same as modifyMVar from base, except that it is strict in the new value and it works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

modifyFetchOldMVar :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m a Source #

Same as modifyMVar_, but also returns the original value that was stored in the MVar

Since: 0.3.0

modifyFetchOldMVarMasked :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m a Source #

Same as modifyFetchOldMVar, but supplied action will run with async exceptions masked, but still interruptible

Since: 0.3.0

modifyFetchNewMVar :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m a Source #

Same as modifyMVar_, but also returns the result of running the supplied action, i.e. the new value that got stored in the MVar.

Since: 0.3.0

modifyFetchNewMVarMasked :: forall a m. MonadUnliftPrim RW m => MVar a RW -> (a -> m a) -> m a Source #

Same as modifyFetchNewMVar, but supplied action will run with async exceptions masked, but still interruptible

Since: 0.3.0

modifyMVar :: forall a b m. MonadUnliftPrim RW m => MVar a RW -> (a -> m (a, b)) -> m b Source #

Apply a monadic action to the contents of supplied MVar. Provides the same guarantees as withMVar.

Same as modifyMVar from base, except that it is strict in the new value and it works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

modifyMVarMasked :: forall a b m. MonadUnliftPrim RW m => MVar a RW -> (a -> m (a, b)) -> m b Source #

Apply a monadic action to the contents of supplied MVar. Provides the same guarantees as withMVar.

Same as modifyMVarMasked from base, except that it is strict in the new value and it works in MonadUnliftPrim with RealWorld state token.

Since: 0.3.0

Weak Pointer

mkWeakMVar Source #

Arguments

:: forall a b m. MonadUnliftPrim RW m 
=> MVar a RW 
-> m b

An action that will get executed whenever MVar gets garbage collected by the runtime.

-> m (Weak (MVar a RW)) 

Create a Weak pointer associated with the supplied MVar.

Same as mkWeakMVar from base, but works in any MonadPrim with RealWorld state token.

Since: 0.3.0

Conversion

toBaseMVar :: MVar a RW -> MVar a Source #

Cast MVar into and the MVar from base

Since: 0.3.0

fromBaseMVar :: MVar a -> MVar a RW Source #

Cast MVar from base into MVar.

Since: 0.3.0