multitasking
Safe HaskellNone
LanguageGHC2021

Multitasking.Communication

Synopsis

Variable

newtype Variable a Source #

A Variable holds some value in a concurrency-safe, non-blocking manner.

Constructors

Variable (TVar a) 

newVariable :: MonadSTM m => a -> m (Variable a) Source #

readVariable :: MonadSTM m => Variable a -> m a Source #

Read in a non-blocking manner

writeVariable :: MonadSTM m => Variable a -> a -> m () Source #

Write in a non-blocking manner

Option

newtype Option a Source #

An Option is either empty or contains an a.

Constructors

Option (TMVar a) 

newOption :: MonadSTM m => a -> m (Option a) Source #

Creates a new Option filled with a.

newEmptyOption :: MonadSTM m => m (Option a) Source #

Creates a new empty Option.

writeOption :: MonadSTM m => Option a -> a -> m () Source #

Write in non-blocking manner

putOption :: MonadSTM m => Option a -> a -> m () Source #

Puts in a blocking manner, waiting if the Option is not empty.

offerOption :: MonadSTM m => Option a -> a -> m Bool Source #

Offers a value to the Option in a non-blocking manner. Returns whether the offer was accepted or not.

awaitOption :: MonadSTM m => Option a -> m a Source #

Awaits the value from the Option.

probeOption :: MonadSTM m => Option a -> m (Maybe a) Source #

Probes the Option in a non-blocking manner.

takeOption :: MonadSTM m => Option a -> m a Source #

Takes the element from the Option. Waits if there is no element. Afterwards, the Option is empty.

drainOption :: MonadSTM m => Option a -> m (Maybe a) Source #

Tries to take the element from the Option in a non-blocking manner. Afterwards, the Option is empty.

Gate

newtype Gate Source #

A Gate is initially closed and can be opened with openGate.

Constructors

Gate (TMVar ()) 

awaitGate :: MonadSTM m => Gate -> m () Source #

Wait for the Gate to open.

openGate :: MonadSTM m => Gate -> m () Source #

Open a Gate. You cannot close a Gate.

Switch

newtype Switch Source #

A Switch is either on or off.

Constructors

Switch (TVar Bool) 

awaitSwitch :: MonadSTM m => Switch -> m () Source #

Wait until the Switch is on

setSwitch :: MonadSTM m => Switch -> m () Source #

Turn on the Switch

unsetSwitch :: MonadSTM m => Switch -> m () Source #

Turn off the Switch

toggleSwitch :: MonadSTM m => Switch -> m () Source #

Toggle the Switch between on/off.

Condition,

data Condition a Source #

A Condition puts a constraint on a value that you can wait for

Constructors

Condition (a -> Bool) (STM a) 

newCondition :: (a -> Bool) -> STM a -> Condition a Source #

awaitCondition :: MonadSTM m => Condition a -> m a Source #

Wait for the Condition to be true

probeCondition :: MonadSTM m => Condition a -> m (Maybe a) Source #

Probe the Condition status

Slot

newtype Slot a Source #

A Slot starts out empty and can be filled with putSlot.

Constructors

Slot (TMVar a) 

newSlot :: MonadSTM m => m (Slot a) Source #

putSlot :: MonadSTM m => Slot a -> a -> m Bool Source #

awaitSlot :: MonadSTM m => Slot a -> m a Source #

probeSlot :: MonadSTM m => Slot a -> m (Maybe a) Source #

Counter

newtype Counter Source #

A Counter stores an int.

Constructors

Counter (TVar Int) 

newCounter :: MonadSTM m => Int -> m Counter Source #

Create a new Counter with an initial value.

getCounter :: MonadSTM m => Counter -> m Int Source #

Get the current value of the Counter.

awaitCounter :: MonadSTM m => Counter -> Int -> m () Source #

Wait until the Counter has the value

incrementCounter :: MonadSTM m => Counter -> m () Source #

Increment the Counter by one.

decrementCounter :: MonadSTM m => Counter -> m () Source #

Decrement the Counter by one.

Sink

data Sink a Source #

A Sink represents a channel where you can only push data

Instances

Instances details
Contravariant Sink Source # 
Instance details

Defined in Multitasking.Communication

Methods

contramap :: (a' -> a) -> Sink a -> Sink a' #

(>$) :: b -> Sink b -> Sink a #

newSink :: (a -> STM ()) -> Sink a Source #

putSink :: MonadSTM m => Sink a -> a -> m () Source #

Source

data Source a Source #

A Source represents a channel where you can only read data

Instances

Instances details
Applicative Source Source # 
Instance details

Defined in Multitasking.Communication

Methods

pure :: a -> Source a #

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

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

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

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

Functor Source Source # 
Instance details

Defined in Multitasking.Communication

Methods

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

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

takeSource :: MonadSTM m => Source a -> m a Source #

Queue

newtype Queue a Source #

A Queue holds zero or more values.

Constructors

Queue (TChan a) 

popQueue :: MonadSTM m => Queue a -> m a Source #

Pop the first element of the Queue, removing it from the queue. Waits until an element is available.

peekQueue :: MonadSTM m => Queue a -> m a Source #

Get the first element of the Queue, not removing it from the queue. Waits until an element is available.

putQueue :: MonadSTM m => Queue a -> a -> m () Source #

Push an element to the back of the Queue.

isEmptyQueue :: MonadSTM m => Queue a -> m Bool Source #

Checks if the Queue is empty.