Safe Haskell | None |
---|---|
Language | GHC2021 |
ConIO.Communication
Synopsis
- newtype Gate = Gate (TMVar ())
- newGate :: MonadSTM m => m Gate
- waitGate :: MonadSTM m => Gate -> m ()
- openGate :: MonadSTM m => Gate -> m ()
- newtype Switch = Switch (TVar Bool)
- newSwitch :: MonadSTM m => Bool -> m Switch
- waitSwitch :: MonadSTM m => Switch -> STM a -> m a
- setSwitch :: MonadSTM m => Switch -> m ()
- unsetSwitch :: MonadSTM m => Switch -> m ()
- toggleSwitch :: MonadSTM m => Switch -> m ()
- newtype Variable a = Variable (TVar a)
- newVariable :: MonadSTM m => a -> m (Variable a)
- waitVariable :: MonadSTM m => (a -> Bool) -> Variable a -> m a
- writeVariable :: MonadSTM m => Variable a -> a -> m ()
- getVariable :: MonadSTM m => Variable a -> m a
- newtype Slot a = Slot (TMVar a)
- newSlot :: MonadSTM m => a -> m (Slot a)
- newEmptySlot :: MonadSTM m => m (Slot a)
- takeSlot :: MonadSTM m => Slot a -> m a
- tryTakeSlot :: MonadSTM m => Slot a -> m (Maybe a)
- readSlot :: MonadSTM m => Slot a -> m a
- tryReadSlot :: MonadSTM m => Slot a -> m (Maybe a)
- putSlot :: MonadSTM m => Slot a -> a -> m ()
- tryPutSlot :: MonadSTM m => Slot a -> a -> m Bool
- newtype Counter = Counter (TVar Int)
- newCounter :: MonadSTM m => m Counter
- getCounter :: MonadSTM m => Counter -> m Int
- setCounter :: MonadSTM m => Counter -> Int -> m ()
- incrementCounter :: MonadSTM m => Counter -> m ()
- decrementCounter :: MonadSTM m => Counter -> m ()
- newtype Queue a = Queue (TChan a)
- newQueue :: MonadSTM m => m (Queue a)
- popQueue :: MonadSTM m => Queue a -> m a
- peekQueue :: MonadSTM m => Queue a -> m a
- tryPopQueue :: MonadSTM m => Queue a -> m (Maybe a)
- tryPeekQueue :: MonadSTM m => Queue a -> m (Maybe a)
- pushQueue :: MonadSTM m => Queue a -> a -> m ()
- isEmptyQueue :: MonadSTM m => Queue a -> m Bool
Gate
Switch
Variable
A Variable
holds some value in a concurrency-safe manner.
newVariable :: MonadSTM m => a -> m (Variable a) Source #
waitVariable :: MonadSTM m => (a -> Bool) -> Variable a -> m a Source #
Wait until the value within the Variable
fulfills some condition
writeVariable :: MonadSTM m => Variable a -> a -> m () Source #
getVariable :: MonadSTM m => Variable a -> m a Source #
Slot
putSlot :: MonadSTM m => Slot a -> a -> m () Source #
Puts an element into the slot if there is space. Waits until the Slot
is empty to fill it.
tryPutSlot :: MonadSTM m => Slot a -> a -> m Bool Source #
Tries to put an element into the Slot
if there is space.
Returns whether the putting was successful.
Counter
newCounter :: MonadSTM m => m Counter Source #
Queue
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.
tryPopQueue :: MonadSTM m => Queue a -> m (Maybe a) Source #
Pop the first element of the Queue
, removing it from the queue.
Does not wait and returns immediately, if no element is available.