| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Incipit.Full
Description
A Prelude for Polysemy projects, reexporting names and modules from several basic libraries.
Synopsis
- module IncipitCore
- type EventConsumer e = Scoped_ (Consume e)
- runConc :: Sem ConcStack a -> IO a
- type ScopedSync a = Scoped_ (Sync a)
- data Sync d (a :: Type -> Type) b
- subscribe :: forall e (r :: EffectRow). Member (Scoped_ (Consume e)) r => InterpreterFor (Consume e) r
- consume :: forall e (r :: EffectRow). Member (Consume e) r => Sem r e
- publish :: forall e (r :: EffectRow). Member (Events e) r => e -> Sem r ()
- data Events e (a :: Type -> Type) b
- type Mask = Scoped_ RestoreMask
- type UninterruptibleMask = Scoped_ RestoreMask
- scoped_ :: forall (effect :: Effect) (r :: EffectRow). Member (Scoped_ effect) r => InterpreterFor effect r
- scoped :: forall param (effect :: Effect) (r :: EffectRow). Member (Scoped param effect) r => param -> InterpreterFor effect r
- data Scoped param (effect :: Effect) (a :: Type -> Type) b
- type Scoped_ (effect :: Effect) = Scoped () effect
- data Race (a :: Type -> Type) b
- data Queue d (a :: Type -> Type) b
- data Interrupt (a :: Type -> Type) b
- data QueueResult d
- 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 EventConsumer e = Scoped_ (Consume e) #
Convenience alias for the consumer effect.
runConc :: Sem ConcStack a -> IO a #
Interprets UninterruptibleMask, Mask and Race in terms of and runs the entire rest of the
stack.Final IO
type ScopedSync a = Scoped_ (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 (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.
type Mask = Scoped_ RestoreMask #
The scoped masking effect.
type UninterruptibleMask = Scoped_ RestoreMask #
The scoped uninterruptible masking effect.
scoped_ :: forall (effect :: Effect) (r :: EffectRow). Member (Scoped_ effect) r => InterpreterFor effect r #
scoped :: forall param (effect :: Effect) (r :: EffectRow). Member (Scoped param effect) r => param -> InterpreterFor effect r #
data Scoped param (effect :: Effect) (a :: Type -> Type) b #
Scoped transforms a program so that an interpreter for effect may
perform arbitrary actions, like resource management, before and after the
computation wrapped by a call to scoped is executed.
Note: This effect has been merged to Polysemy and will be released there soon.
An application for this is Polysemy.Conc.Events from
https://hackage.haskell.org/package/polysemy-conc, in which each program
using the effect Polysemy.Conc.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.
For a longer exposition, see https://www.tweag.io/blog/2022-01-05-polysemy-scoped/.
Note that the interface has changed since the blog post was published: The
resource parameter no longer exists.
Resource allocation is performed by a function passed to
interpretScoped.
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.
As an example, imagine an effect for writing lines to a file:
data Write :: Effect where Write :: Text -> Write m () makeSem ''Write
If we now have the following requirements:
- The file should be opened and closed right before and after the part of the program in which we write lines
- The file name should be specifiable at the point in the program where writing begins
- We don't want to commit to IO, lines should be stored in memory when running tests
Then we can take advantage of Scoped to write this program:
prog :: Member (Scoped FilePath Write) r => Sem r ()
prog = do
scoped "file1.txt" do
write "line 1"
write "line 2"
scoped "file2.txt" do
write "line 1"
write "line 2"Here scoped creates a prompt for an interpreter to start allocating a
resource for "file1.txt" and handling Write actions using that resource.
When the scoped block ends, the resource should be freed.
The interpreter may look like this:
interpretWriteFile :: Members '[Resource, Embed IO] => InterpreterFor (Scoped FilePath Write) r
interpretWriteFile =
interpretScoped allocator handler
where
allocator name use = bracket (openFile name WriteMode) hClose use
handler fileHandle (Write line) = embed (Text.hPutStrLn fileHandle line)Essentially, the bracket is executed at the point where scoped was
called, wrapping the following block. When the second scoped is executed,
another call to bracket is performed.
The effect of this is that the operation that uses Embed IO was moved from
the call site to the interpreter, while the interpreter may be executed at
the outermost layer of the app.
This makes it possible to use a pure interpreter for testing:
interpretWriteOutput :: Member (Output (FilePath, Text)) r => InterpreterFor (Scoped FilePath Write) r
interpretWriteOutput =
interpretScoped (\ name use -> use name) \ name -> \case
Write line -> output (name, line)Here we simply pass the name to the interpreter in the resource allocation function.
Now imagine that we drop requirement 2 from the initial list – we still want
the file to be opened and closed as late/early as possible, but the file name
is globally fixed. For this case, the param type is unused, and the API
provides some convenience aliases to make your code more concise:
prog :: Member (Scoped_ Write) r => Sem r ()
prog = do
scoped_ do
write "line 1"
write "line 2"
scoped_ do
write "line 1"
write "line 2"The type Scoped_ and the constructor scoped_ simply fix param to ().
type Scoped_ (effect :: Effect) = Scoped () effect #
A convenience alias for a scope without parameters.
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
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