Safe Haskell | None |
---|---|
Language | GHC2021 |
Polysemy.Conc.Effect.Sync
Description
Synopsis
- data Sync d (a :: Type -> Type) b where
- Block :: forall d (a :: Type -> Type). Sync d a d
- Wait :: forall u d (a :: Type -> Type). TimeUnit u => u -> Sync d a (Maybe d)
- Try :: forall d (a :: Type -> Type). Sync d a (Maybe d)
- TakeBlock :: forall d (a :: Type -> Type). Sync d a d
- TakeWait :: forall u d (a :: Type -> Type). TimeUnit u => u -> Sync d a (Maybe d)
- TakeTry :: forall d (a :: Type -> Type). Sync d a (Maybe d)
- PutBlock :: forall d (a :: Type -> Type). d -> Sync d a ()
- PutWait :: forall u d (a :: Type -> Type). TimeUnit u => u -> d -> Sync d a Bool
- PutTry :: forall d (a :: Type -> Type). d -> Sync d a Bool
- Empty :: forall d (a :: Type -> Type). Sync d a Bool
- block :: forall d (r :: EffectRow). Member (Sync d) r => Sem r d
- wait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> Sem r (Maybe d)
- try :: forall d (r :: EffectRow). Member (Sync d) r => Sem r (Maybe d)
- takeBlock :: forall d (r :: EffectRow). Member (Sync d) r => Sem r d
- takeWait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> Sem r (Maybe d)
- takeTry :: forall d (r :: EffectRow). Member (Sync d) r => Sem r (Maybe d)
- putBlock :: forall d (r :: EffectRow). Member (Sync d) r => d -> Sem r ()
- putWait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> d -> Sem r Bool
- putTry :: forall d (r :: EffectRow). Member (Sync d) r => d -> Sem r Bool
- empty :: forall d (r :: EffectRow). Member (Sync d) r => Sem r Bool
- type ScopedSync a = Scoped_ (Sync a)
Documentation
data Sync d (a :: Type -> Type) b where Source #
Abstracts an MVar
.
For documentation on the constructors, see the module Polysemy.Conc.Effect.Sync.
import Polysemy.Conc (Sync) import qualified Polysemy.Conc.Effect.Sync as Sync prog :: Member (Sync Int) r => Sem r Int prog = do Sync.putTry 5 Sync.takeBlock
Constructors
Block :: forall d (a :: Type -> Type). Sync d a d | Read the variable, waiting until a value is available. |
Wait :: forall u d (a :: Type -> Type). TimeUnit u => u -> Sync d a (Maybe d) | Read the variable, waiting until a value is available or the timeout has expired. |
Try :: forall d (a :: Type -> Type). Sync d a (Maybe d) | Read the variable, returning |
TakeBlock :: forall d (a :: Type -> Type). Sync d a d | Take the variable, waiting until a value is available. |
TakeWait :: forall u d (a :: Type -> Type). TimeUnit u => u -> Sync d a (Maybe d) | Take the variable, waiting until a value is available or the timeout has expired. |
TakeTry :: forall d (a :: Type -> Type). Sync d a (Maybe d) | Take the variable, returning |
PutBlock :: forall d (a :: Type -> Type). d -> Sync d a () | Write the variable, waiting until it is writable. |
PutWait :: forall u d (a :: Type -> Type). TimeUnit u => u -> d -> Sync d a Bool | Write the variable, waiting until it is writable or the timeout has expired. |
PutTry :: forall d (a :: Type -> Type). d -> Sync d a Bool | Write the variable, returning |
Empty :: forall d (a :: Type -> Type). Sync d a Bool | Indicate whether the variable is empty. |
block :: forall d (r :: EffectRow). Member (Sync d) r => Sem r d Source #
Read the variable, waiting until a value is available.
wait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> Sem r (Maybe d) Source #
Read the variable, waiting until a value is available or the timeout has expired.
try :: forall d (r :: EffectRow). Member (Sync d) r => Sem r (Maybe d) Source #
Read the variable, returning Nothing
immmediately if no value was available.
takeBlock :: forall d (r :: EffectRow). Member (Sync d) r => Sem r d Source #
Take the variable, waiting until a value is available.
takeWait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> Sem r (Maybe d) Source #
Take the variable, waiting until a value is available or the timeout has expired.
takeTry :: forall d (r :: EffectRow). Member (Sync d) r => Sem r (Maybe d) Source #
Take the variable, returning Nothing
immmediately if no value was available.
putBlock :: forall d (r :: EffectRow). Member (Sync d) r => d -> Sem r () Source #
Write the variable, waiting until it is writable.
putWait :: forall d (r :: EffectRow) u. (Member (Sync d) r, TimeUnit u) => u -> d -> Sem r Bool Source #
Write the variable, waiting until it is writable or the timeout has expired.
putTry :: forall d (r :: EffectRow). Member (Sync d) r => d -> Sem r Bool Source #
Write the variable, returning False
immmediately if a value was available.
empty :: forall d (r :: EffectRow). Member (Sync d) r => Sem r Bool Source #
Indicate whether the variable is empty.
type ScopedSync a = Scoped_ (Sync a) Source #
Convenience alias.