Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- clear :: forall a r. Member (Sync a) r => Sem r ()
- modify :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r (a, b)) -> Sem r b
- withSync :: forall d r. Member (ScopedSync d) r => InterpreterFor (Sync d) r
- lock :: forall l r a. Members [Sync l, Resource] r => l -> Sem r a -> Sem r a
- whileEmpty :: forall a r. Member (Sync a) r => Sem r () -> Sem r ()
- use :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r b) -> Sem r b
- whileEmptyInterval :: forall a u t d r. TimeUnit u => Members [Time t d, Sync a] r => u -> Sem r () -> Sem r ()
- modify_ :: forall a r. Members [Sync a, Mask, Resource] r => (a -> Sem r a) -> Sem r ()
- modifyMasked :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r (a, b)) -> Sem r b
- modifyMasked_ :: forall a r. Members [Sync a, Mask, Resource] r => (a -> Sem r a) -> Sem r ()
- useMasked :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r b) -> Sem r b
- module Polysemy.Conc.Effect.Sync
- module Polysemy.Conc.Effect.Sync
Documentation
clear :: forall a r. Member (Sync a) r => Sem r () Source #
Remove the content of the Sync
variable if it is present.
modify :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r (a, b)) -> Sem r b Source #
Modify a Sync
variable with async exceptions masked for the Sync
operations, but not the action.
Allows a value to be returned.
Equivalent to modifyMVar
.
withSync :: forall d r. Member (ScopedSync d) r => InterpreterFor (Sync d) r Source #
lock :: forall l r a. Members [Sync l, Resource] r => l -> Sem r a -> Sem r a Source #
Run the action ma
with an exclusive lock (mutex).
When multiple threads call the action concurrently, only one is allowed to execute it at a time.
The value l
is used to disambiguate the Sync
from other uses of the combinator.
You can pass in something like Proxy
"db-write"@.
Note: The Sync
must be interpreted with an initially full MVar
, e.g. using interpretSyncAs
.
whileEmpty :: forall a r. Member (Sync a) r => Sem r () -> Sem r () Source #
Run an action repeatedly until the Sync
variable is available.
whileEmptyInterval :: forall a u t d r. TimeUnit u => Members [Time t d, Sync a] r => u -> Sem r () -> Sem r () Source #
Run an action repeatedly until the Sync
variable is available, waiting for the specified time between executions.
modify_ :: forall a r. Members [Sync a, Mask, Resource] r => (a -> Sem r a) -> Sem r () Source #
Modify a Sync
variable with async exceptions masked for the Sync
operations, but not the action.
Does not allow a value to be returned.
Equivalent to modifyMVar_
.
modifyMasked :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r (a, b)) -> Sem r b Source #
Modify a Sync
variable with async exceptions masked for the entire procedure.
Allows a value to be returned.
Equivalent to modifyMVarMasked
.
modifyMasked_ :: forall a r. Members [Sync a, Mask, Resource] r => (a -> Sem r a) -> Sem r () Source #
Modify a Sync
variable with async exceptions masked for the entire procedure.
Does not allow a value to be returned.
Equivalent to modifyMVarMasked_
.
useMasked :: forall a b r. Members [Sync a, Mask, Resource] r => (a -> Sem r b) -> Sem r b Source #
Run an action with the current value of the Sync
variable with async exceptions masked for the entire procedure.
Equivalent to withMVarMasked
.
module Polysemy.Conc.Effect.Sync
module Polysemy.Conc.Effect.Sync