incipit-0.3.1.0: A Prelude for Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

Incipit.Full

Description

A Prelude for Polysemy projects, reexporting names and modules from several basic libraries.

Synopsis

Documentation

type EventConsumer token e = Scoped_ (EventResource token) (Consume e) #

Convenience alias for the consumer effect.

runConc :: Sem ConcStack a -> IO a #

Interprets UninterruptibleMask, Mask and Race in terms of Final IO and runs the entire rest of the stack.

type ScopedSync res a = Scoped_ (SyncResources res) (Sync a) #

Convenience alias.

data Sync d (a :: Type -> Type) b #

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

subscribe :: forall e resource (r :: EffectRow). Member (Scoped_ (EventResource resource) (Consume e)) r => InterpreterFor (Consume e) r #

Create a new scope for Events, causing the nested program to get its own copy of the event stream. To be used with interpretEventsChan.

consume :: forall e (r :: EffectRow). Member (Consume e) r => Sem r e #

Consume one event emitted by Events.

publish :: forall e resource (r :: EffectRow). Member (Events resource e) r => e -> Sem r () #

Publish one event.

data Events resource e (a :: Type -> Type) b #

An event publisher that can be consumed from multiple threads.

type Mask resource = Scoped_ resource RestoreMask #

The scoped masking effect.

type UninterruptibleMask resource = Scoped_ resource RestoreMask #

The scoped uninterruptible masking effect.

scoped_ :: forall resource (effect :: Effect) (r :: EffectRow). Member (Scoped_ resource effect) r => InterpreterFor effect r #

Constructor for Scoped_, taking a nested program and transforming all instances of effect to Scoped_ resource effect and wrapping the result with InScope.

This allows the effective interpreter to bracket the nested program with a resource from a distance.

scoped :: forall param resource (effect :: Effect) (r :: EffectRow). Member (Scoped param resource effect) r => param -> InterpreterFor effect r #

Constructor for Scoped, taking a nested program and transforming all instances of effect to Scoped param resource effect and wrapping the result with InScope.

This allows the effective interpreter to bracket the nested program with a resource from a distance.

The value param is passed to the interpreter.

data Scoped param resource (effect :: Effect) (a :: Type -> Type) b #

Scoped transforms a program so that effect is associated with a resource within that program. This requires the interpreter for effect to be parameterized by resource and constructed for every program using Scoped separately.

An application for this is Events, in which each program using the effect Consume is interpreted with its own copy of the event channel; or a database transaction, in which a transaction handle is created for the wrapped program and passed to the interpreter for the database effect.

Resource creation is performed by the function passed to interpretScoped and its variants.

The constructors are not intended to be used directly; the smart constructor scoped is used like a local interpreter for effect. scoped takes an argument of type param, which will be passed through to the interpreter, to be used by the resource allocation function.

type Scoped_ resource (effect :: Effect) = Scoped () resource effect #

data Race (a :: Type -> Type) b #

Abstract the concept of running two programs concurrently, aborting the other when one terminates. Timeout is a simpler variant, where one thread just sleeps for a given interval.

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

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

data Interrupt (a :: Type -> Type) b #

The interrupt handler effect allows three kinds of interaction for interrupt signals:

  • Execute a callback when a signal is received
  • Block a thread until a signal is received
  • Kill a thread when a signal is received

For documentation on the constructors, see the module Polysemy.Conc.Effect.Interrupt.

import qualified Polysemy.Conc.Effect.Interrupt as Interrupt

prog = do
  Interrupt.register "task 1" (putStrLn "interrupted")
  Interrupt.killOnQuit $ forever do
   doSomeWork

data QueueResult d #

Encodes failure reasons for queues.

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

import qualified Polysemy.Conc.Data.QueueResult as QueueResult

Instances

Instances details
Functor QueueResult 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Methods

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

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

Monoid d => Monoid (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Semigroup d => Semigroup (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Generic (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Associated Types

type Rep (QueueResult d) :: Type -> Type #

Methods

from :: QueueResult d -> Rep (QueueResult d) x #

to :: Rep (QueueResult d) x -> QueueResult d #

Show d => Show (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Eq d => Eq (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

Ord d => Ord (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

type Rep (QueueResult d) 
Instance details

Defined in Polysemy.Conc.Data.QueueResult

type Rep (QueueResult d) = D1 ('MetaData "QueueResult" "Polysemy.Conc.Data.QueueResult" "polysemy-conc-0.9.0.0-JmO56BT1jj7GtyxfwwCJUe" 'False) (C1 ('MetaCons "Success" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 d)) :+: (C1 ('MetaCons "NotAvailable" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Closed" 'PrefixI 'False) (U1 :: Type -> Type)))

data Log (a :: Type -> Type) b #

The default high-level effect for simple text messages. To be used with the severity constructors:

import qualified Polysemy.Log as Log

prog = do
  Log.debug "debugging…"
  Log.warn "warning!"

Interpreters should preprocess and relay the message to DataLog.

data DataLog a (b :: Type -> Type) c #

Structural logs, used as a backend for the simpler Text log effect, Log.

Can also be used on its own, or reinterpreted into an effect like those from co-log or di.

class TimeUnit u #

Types that represent an amount of time that can be converted to each other. The methods are internal, the API function is convert.

Minimal complete definition

nanos

Instances

Instances details
TimeUnit Days 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit Hours 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit MicroSeconds 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit MilliSeconds 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit Minutes 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit NanoSeconds 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit Seconds 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit Weeks 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit DiffTime 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

TimeUnit NominalDiffTime 
Instance details

Defined in Polysemy.Time.Data.TimeUnit

data Time time date (a :: Type -> Type) b #

The Time effect.