| Safe Haskell | Safe-Inferred |
|---|---|
| Language | GHC2021 |
Incipit.Full
Description
A Prelude for Polysemy projects, reexporting names and modules from several basic libraries.
Synopsis
- module IncipitCore
- type Mask = Scoped_ RestoreMask
- data Queue d (a :: Type -> Type) b
- data Events e (a :: Type -> Type) b
- data QueueResult d
- data Interrupt (a :: Type -> Type) b
- type UninterruptibleMask = Scoped_ RestoreMask
- data Race (a :: Type -> Type) b
- data Sync d (a :: Type -> Type) b
- type ScopedSync a = Scoped_ (Sync a)
- type EventConsumer e = Scoped_ (Consume e)
- subscribe :: forall e (r :: EffectRow). Member (Scoped_ (Consume e)) r => InterpreterFor (Consume e) r
- publish :: forall e (r :: EffectRow). Member (Events e) r => e -> Sem r ()
- consume :: forall e (r :: EffectRow). Member (Consume e) r => Sem r e
- runConc :: Sem ConcStack a -> IO a
- data Log (a :: Type -> Type) b
- data DataLog a (b :: Type -> Type) c
- module Polysemy.Resume
- class TimeUnit u
- data Time time date (a :: Type -> Type) b
Documentation
module IncipitCore
type Mask = Scoped_ RestoreMask #
The scoped masking effect.
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 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
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
type UninterruptibleMask = Scoped_ RestoreMask #
The scoped uninterruptible masking 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 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
type ScopedSync a = Scoped_ (Sync a) #
Convenience alias.
type EventConsumer e = Scoped_ (Consume e) #
Convenience alias for the consumer effect.
subscribe :: forall e (r :: EffectRow). Member (Scoped_ (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.
runConc :: Sem ConcStack a -> IO a #
Interprets UninterruptibleMask, Mask and Race in terms of and runs the entire rest of the
stack.Final IO
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.
module Polysemy.Resume
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