polysemy-conc-0.14.1.1: Polysemy effects for concurrency
Safe HaskellNone
LanguageGHC2021

Polysemy.Conc.Effect.Queue

Description

 
Synopsis

Documentation

data Queue d (a :: Type -> Type) b where Source #

Abstracts queues like TBQueue.

For documentation on the constructors, see the module Polysemy.Conc.Data.Queue.

import Polysemy.Conc (Queue, QueueResult)
import Polysemy.Conc.Effect.Queue as Queue

prog :: Member (Queue Int) r => Sem r (QueueResult Int)
prog = do
  Queue.write 5
  Queue.write 10
  Queue.read >>= \case
    QueueResult.Success i -> fmap (i +) <$> Queue.read
    r -> pure r

Constructors

Read :: forall d (a :: Type -> Type). Queue d a (QueueResult d)

Read an element from the queue, blocking until one is available.

TryRead :: forall d (a :: Type -> Type). Queue d a (QueueResult d)

Read an element from the queue, immediately returning if none is available.

ReadTimeout :: forall t d (a :: Type -> Type). TimeUnit t => t -> Queue d a (QueueResult d)

Read an element from the queue, blocking until one is available or the timeout expires.

Peek :: forall d (a :: Type -> Type). Queue d a (QueueResult d)

Read an element, leaving it in the queue, blocking until one is available.

TryPeek :: forall d (a :: Type -> Type). Queue d a (QueueResult d)

Read an element, leaving it in the queue, immediately returning if none is available.

Write :: forall d (a :: Type -> Type). d -> Queue d a ()

Write an element to the queue, blocking until a slot is available.

TryWrite :: forall d (a :: Type -> Type). d -> Queue d a (QueueResult ())

Write an element to the queue, immediately returning if no slot is available.

WriteTimeout :: forall t d (a :: Type -> Type). TimeUnit t => t -> d -> Queue d a (QueueResult ())

Write an element to the queue, blocking until a slot is available or the timeout expires.

Closed :: forall d (a :: Type -> Type). Queue d a Bool

Indicate whether the queue is closed.

Close :: forall d (a :: Type -> Type). Queue d a ()

Close the queue.

read :: forall d (r :: EffectRow). Member (Queue d) r => Sem r (QueueResult d) Source #

Read an element from the queue, blocking until one is available.

tryRead :: forall d (r :: EffectRow). Member (Queue d) r => Sem r (QueueResult d) Source #

Read an element from the queue, immediately returning if none is available.

readTimeout :: forall d (r :: EffectRow) t. (Member (Queue d) r, TimeUnit t) => t -> Sem r (QueueResult d) Source #

Read an element from the queue, blocking until one is available or the timeout expires.

peek :: forall d (r :: EffectRow). Member (Queue d) r => Sem r (QueueResult d) Source #

Read an element, leaving it in the queue, blocking until one is available.

tryPeek :: forall d (r :: EffectRow). Member (Queue d) r => Sem r (QueueResult d) Source #

Read an element, leaving it in the queue, immediately returning if none is available.

write :: forall d (r :: EffectRow). Member (Queue d) r => d -> Sem r () Source #

Write an element to the queue, blocking until a slot is available.

tryWrite :: forall d (r :: EffectRow). Member (Queue d) r => d -> Sem r (QueueResult ()) Source #

Write an element to the queue, immediately returning if no slot is available.

writeTimeout :: forall d (r :: EffectRow) t. (Member (Queue d) r, TimeUnit t) => t -> d -> Sem r (QueueResult ()) Source #

Write an element to the queue, blocking until a slot is available or the timeout expires.

closed :: forall d (r :: EffectRow). Member (Queue d) r => Sem r Bool Source #

Indicate whether the queue is closed.

close :: forall d (r :: EffectRow). Member (Queue d) r => Sem r () Source #

Close the queue.