| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Effectful.Internal.Env
Synopsis
- data Env (es :: [Effect]) = Env {- envSize :: !Int
- envRefs :: !(IORef References)
- envStorage :: !(IORef Storage)
 
- data References = References {- refSize :: !Int
- refIndices :: !(MutablePrimArray RealWorld Int)
 
- data Storage = Storage {- stSize :: !Int
- stEffects :: !(SmallMutableArray RealWorld Any)
- stRelinkers :: !(SmallMutableArray RealWorld Any)
 
- newtype Relinker :: (Effect -> Type) -> Effect -> Type where
- dummyRelinker :: Relinker rep e
- data Dispatch
- data SideEffects
- type family DispatchOf (e :: Effect) :: Dispatch
- type family EffectRep (d :: Dispatch) :: Effect -> Type
- emptyEnv :: IO (Env '[])
- cloneEnv :: Env es -> IO (Env es)
- forkEnv :: Env es -> IO (Env es)
- sizeEnv :: Env es -> IO Int
- checkSizeEnv :: Env es -> IO ()
- tailEnv :: Env (e ': es) -> IO (Env es)
- consEnv :: EffectRep (DispatchOf e) e -> Relinker (EffectRep (DispatchOf e)) e -> Env es -> IO (Env (e ': es))
- unconsEnv :: Env (e ': es) -> IO ()
- replaceEnv :: forall e es. e :> es => EffectRep (DispatchOf e) e -> Relinker (EffectRep (DispatchOf e)) e -> Env es -> IO (Env es)
- unreplaceEnv :: forall e es. e :> es => Env es -> IO ()
- subsumeEnv :: forall e es. e :> es => Env es -> IO (Env (e ': es))
- unsubsumeEnv :: e :> es => Env (e ': es) -> IO ()
- injectEnv :: forall xs es. Subset xs es => Env es -> IO (Env xs)
- getEnv :: forall e es. e :> es => Env es -> IO (EffectRep (DispatchOf e) e)
- putEnv :: forall e es. e :> es => Env es -> EffectRep (DispatchOf e) e -> IO ()
- stateEnv :: forall e es a. e :> es => Env es -> (EffectRep (DispatchOf e) e -> (a, EffectRep (DispatchOf e) e)) -> IO a
- modifyEnv :: forall e es. e :> es => Env es -> (EffectRep (DispatchOf e) e -> EffectRep (DispatchOf e) e) -> IO ()
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), wherenis the size of the effect stack.
- Cloning: O(N + Σ(n_i)), whereNis the size of theStorage, whileiranges over handlers of dynamically dispatched effects in theStorageandn_iis the size of the effect stack ofi-th handler.
Constructors
| Env | |
| Fields 
 | |
data References Source #
An array of references to effects in the Storage.
Constructors
| References | |
| Fields 
 | |
A storage of effects.
Shared between all forks of the environment within the same thread.
Constructors
| Storage | |
| Fields 
 | |
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.
dummyRelinker :: Relinker rep e Source #
A dummy Relinker.
Dispatch
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.
Constructors
| NoSideEffects | |
| WithSideEffects | 
type family DispatchOf (e :: Effect) :: Dispatch Source #
Dispatch types of effects.
Instances
| type DispatchOf Prim Source # | |
| Defined in Effectful.Internal.Monad | |
| type DispatchOf IOE Source # | |
| Defined in Effectful.Internal.Monad | |
| type DispatchOf Fail Source # | |
| Defined in Effectful.Internal.Monad | |
| type DispatchOf (Error e) Source # | |
| Defined in Effectful.Error.Static | |
| type DispatchOf (Error e) Source # | |
| Defined in Effectful.Error.Dynamic | |
| type DispatchOf (Reader r) Source # | |
| Defined in Effectful.Reader.Static | |
| type DispatchOf (Reader r) Source # | |
| Defined in Effectful.Reader.Dynamic | |
| type DispatchOf (State s) Source # | |
| Defined in Effectful.State.Static.Local | |
| type DispatchOf (State s) Source # | |
| Defined in Effectful.State.Static.Shared | |
| type DispatchOf (State s) Source # | |
| Defined in Effectful.State.Dynamic | |
| type DispatchOf (Writer w) Source # | |
| Defined in Effectful.Writer.Static.Local | |
| type DispatchOf (Writer w) Source # | |
| Defined in Effectful.Writer.Static.Shared | |
| type DispatchOf (Writer w) Source # | |
| Defined in Effectful.Writer.Dynamic | |
type family EffectRep (d :: Dispatch) :: Effect -> Type Source #
Internal representations of effects.
Operations
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.
checkSizeEnv :: Env es -> IO () Source #
Check that the size of the environment is internally consistent.
Modification of the effect stack
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.
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
Arguments
| :: forall e es. e :> es | |
| => Env es | The environment. | 
| -> IO (EffectRep (DispatchOf e) e) | 
Extract a specific data type from the environment.
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).
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.
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).