effectful-core-1.2.0.0: An easy to use, performant extensible effects library.
Safe HaskellNone
LanguageHaskell2010

Effectful.Internal.Env

Synopsis

The environment

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

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

Supports forking, i.e. introduction of local branches for encapsulation of effects specific to effect handlers.

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(1) (amortized).
  • Shrinking: O(1).
  • Indexing via (:>): O(1)
  • Modification of a specific element: O(1).
  • Forking: O(n), where n is the size of the effect stack.
  • Cloning: O(N + Σ(n_i)), where N is the size of the Storage, while i ranges over handlers of dynamically dispatched effects in the Storage and n_i is the size of the effect stack of i-th handler.

Constructors

Env 

data References Source #

An array of references to effects in the Storage.

data Storage Source #

A storage of effects.

Shared between all forks of the environment within the same thread.

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 

Dispatch

data Dispatch Source #

A type of dispatch. For more information consult the documentation in Effectful.Dispatch.Dynamic and Effectful.Dispatch.Static.

Constructors

Dynamic 
Static SideEffects 

data SideEffects Source #

Signifies whether core operations of a statically dispatched effect perform side effects. If an effect is marked as such, the runStaticRep family of functions will require the IOE effect to be in context via the MaybeIOE type family.

type family DispatchOf (e :: Effect) :: Dispatch Source #

Dispatch types of effects.

Instances

Instances details
type DispatchOf Prim Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf IOE Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf Fail Source # 
Instance details

Defined in Effectful.Internal.Monad

type DispatchOf (Error e) Source # 
Instance details

Defined in Effectful.Error.Static

type DispatchOf (Error e) Source # 
Instance details

Defined in Effectful.Error.Dynamic

type DispatchOf (Reader r) Source # 
Instance details

Defined in Effectful.Reader.Static

type DispatchOf (Reader r) Source # 
Instance details

Defined in Effectful.Reader.Dynamic

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Static.Local

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Static.Shared

type DispatchOf (State s) Source # 
Instance details

Defined in Effectful.State.Dynamic

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Static.Local

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Static.Shared

type DispatchOf (Writer w) Source # 
Instance details

Defined in Effectful.Writer.Dynamic

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

Operations

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.

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

Create a fork of the environment.

Forked environment can be updated independently of the original one within the same thread.

sizeEnv :: Env es -> IO Int Source #

Get the current size of the environment.

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

Check that the size of the environment is internally consistent.

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

Access the tail of the environment.

Modification of the effect stack

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 (in place).

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

Shrink the environment by one data type (in place).

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

replaceEnv Source #

Arguments

:: forall e es. e :> es 
=> EffectRep (DispatchOf e) e

The representation of the effect.

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

Replace a specific effect in the stack with a new value.

unreplaceEnv :: forall e es. e :> es => Env es -> IO () Source #

Remove a reference to the replaced effect.

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

subsumeEnv :: forall e es. e :> es => Env es -> IO (Env (e ': es)) Source #

Reference an existing effect from the top of the stack (in place).

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

Remove a reference to an existing effect from the top of the stack.

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

injectEnv :: forall xs es. Subset xs es => Env es -> IO (Env xs) Source #

Construct an environment containing a permutation (with possible duplicates) of a subset of effects from the input environment.

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 -> (a, EffectRep (DispatchOf e) e)) 
-> IO a 

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

modifyEnv Source #

Arguments

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

The environment.

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

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