Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Env (es :: [Effect]) = Env {}
- data Storage = Storage {
- stSize :: !Int
- stVersion :: !Int
- stVersions :: !(MutablePrimArray RealWorld 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)
- restoreEnv :: Env es -> Env es -> IO ()
- sizeEnv :: Env es -> IO Int
- 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))
- 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 -> IO (a, EffectRep (DispatchOf e) e)) -> IO a
- modifyEnv :: forall e es. e :> es => Env es -> (EffectRep (DispatchOf e) e -> IO (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
.
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:
A storage of effects.
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.
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.
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
type family EffectRep (d :: Dispatch) :: Effect -> Type Source #
Internal representations of effects.
Operations
Restore the environment from its clone.
Since: 2.2.0.0
Modification of the effect stack
:: 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.
:: 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.
Note: unlike in putEnv
the value in not changed in place, so only the new
environment will see it.
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.
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
:: forall e es. e :> es | |
=> Env es | The environment. |
-> IO (EffectRep (DispatchOf e) e) |
Extract a specific data type from the environment.
:: 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).
:: 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).