effectful-core-2.3.0.1: An easy to use, performant extensible effects library.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Effectful.Dispatch.Static.Primitive

Description

Primitive API for statically dispatched effects.

This module exposes internal implementation details of the Eff monad. Most of the time functions from Effectful.Dispatch.Static are sufficient.

Warning: playing the so called "type tetris" with functions from this module is not enough. Their misuse might lead to data races or internal consistency check failures, so make sure you understand what you're doing.

Synopsis

The environment

data Env (es :: [Effect]) Source #

A strict (WHNF), thread local, mutable, extensible record indexed by types of kind Effect.

Warning: the environment is a mutable data structure and cannot be simultaneously used from multiple threads under any circumstances.

In order to pass it to a different thread, you need to perform a deep copy with the cloneEnv funtion.

Offers very good performance characteristics for most often performed operations:

  • Extending: O(n), where n is the size of the effect stack.
  • Shrinking: O(1).
  • Indexing via (:>): O(1)
  • Modification of a specific element: O(1).
  • Getting a tail: O(1).
  • Cloning: O(N), where N is the size of the Storage.

Relinker

newtype Relinker :: (Effect -> Type) -> Effect -> Type where Source #

A function for relinking Env objects stored in the handlers and/or making a deep copy of the representation of the effect when cloning the environment.

Constructors

Relinker :: ((forall es. Env es -> IO (Env es)) -> rep e -> IO (rep e)) -> Relinker rep e 

Representation of effects

type family EffectRep (d :: Dispatch) :: Effect -> Type Source #

Internal representations of effects.

Instances

Instances details
type EffectRep 'Dynamic Source # 
Instance details

Defined in Effectful.Internal.Monad

type EffectRep ('Static sideEffects) Source # 
Instance details

Defined in Effectful.Internal.Monad

type EffectRep ('Static sideEffects) = StaticRep

Extending and shrinking

consEnv Source #

Arguments

:: EffectRep (DispatchOf e) e

The representation of the effect.

-> Relinker (EffectRep (DispatchOf e)) e 
-> Env es 
-> IO (Env (e ': es)) 

Extend the environment with a new data type.

unconsEnv :: Env (e ': es) -> IO () Source #

Shrink the environment by one data type.

Note: after calling this function e from the input environment is no longer usable.

Data retrieval and update

getEnv Source #

Arguments

:: forall e es. e :> es 
=> Env es

The environment.

-> IO (EffectRep (DispatchOf e) e) 

Extract a specific data type from the environment.

putEnv Source #

Arguments

:: forall e es. e :> es 
=> Env es

The environment.

-> EffectRep (DispatchOf e) e 
-> IO () 

Replace the data type in the environment with a new value (in place).

stateEnv Source #

Arguments

:: forall e es a. e :> es 
=> Env es

The environment.

-> (EffectRep (DispatchOf e) e -> IO (a, EffectRep (DispatchOf e) e)) 
-> IO a 

Modify the data type in the environment and return a value (in place).

modifyEnv Source #

Arguments

:: forall e es. e :> es 
=> Env es

The environment.

-> (EffectRep (DispatchOf e) e -> IO (EffectRep (DispatchOf e) e)) 
-> IO () 

Modify the data type in the environment (in place).

Utils

emptyEnv :: IO (Env '[]) Source #

Create an empty environment.

cloneEnv :: Env es -> IO (Env es) Source #

Clone the environment to use it in a different thread.

restoreEnv Source #

Arguments

:: Env es

Destination.

-> Env es

Source.

-> IO () 

Restore the environment from its clone.

Since: 2.2.0.0

sizeEnv :: Env es -> IO Int Source #

Get the current size of the environment.

tailEnv :: Env (e ': es) -> IO (Env es) Source #

Access the tail of the environment.