Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Env (es :: [Effect]) = Env {}
- data Ref = Ref !Int !Version
- data Version
- data Storage = Storage {
- stVersion :: !Version
- stData :: !StorageData
- data StorageData = StorageData {}
- copyStorageData :: HasCallStack => StorageData -> IO StorageData
- restoreStorageData :: HasCallStack => StorageData -> Env es -> IO ()
- data AnyRelinker
- toAnyRelinker :: Relinker (EffectRep (DispatchOf e)) e -> AnyRelinker
- fromAnyRelinker :: AnyRelinker -> Relinker (EffectRep (DispatchOf e)) e
- data AnyEffect
- toAnyEffect :: EffectRep (DispatchOf e) e -> AnyEffect
- fromAnyEffect :: AnyEffect -> EffectRep (DispatchOf e) e
- 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 :: HasCallStack => IO (Env '[])
- cloneEnv :: HasCallStack => Env es -> IO (Env es)
- sizeEnv :: Env es -> IO Int
- tailEnv :: Env (e : es) -> IO (Env es)
- consEnv :: HasCallStack => EffectRep (DispatchOf e) e -> Relinker (EffectRep (DispatchOf e)) e -> Env es -> IO (Env (e : es))
- unconsEnv :: HasCallStack => Env (e : es) -> IO ()
- replaceEnv :: forall e es. (HasCallStack, e :> es) => EffectRep (DispatchOf e) e -> Relinker (EffectRep (DispatchOf e)) e -> Env es -> IO (Env es)
- unreplaceEnv :: forall e es. (HasCallStack, e :> es) => Env es -> IO ()
- subsumeEnv :: forall e es. e :> es => Env es -> IO (Env (e : es))
- injectEnv :: forall subEs es. Subset subEs es => Env es -> IO (Env subEs)
- getEnv :: forall e es. (HasCallStack, e :> es) => Env es -> IO (EffectRep (DispatchOf e) e)
- putEnv :: forall e es. (HasCallStack, e :> es) => Env es -> EffectRep (DispatchOf e) e -> IO ()
- stateEnv :: forall e es a. (HasCallStack, e :> es) => Env es -> (EffectRep (DispatchOf e) e -> (a, EffectRep (DispatchOf e) e)) -> IO a
- modifyEnv :: forall e es. (HasCallStack, 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
.
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:
Reference to the effect in Storage
.
Instances
Prim Ref Source # | |
Defined in Effectful.Internal.Env sizeOfType# :: Proxy Ref -> Int# # alignmentOfType# :: Proxy Ref -> Int# # alignment# :: Ref -> Int# # indexByteArray# :: ByteArray# -> Int# -> Ref # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Ref #) # writeByteArray# :: MutableByteArray# s -> Int# -> Ref -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Ref -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Ref # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Ref #) # writeOffAddr# :: Addr# -> Int# -> Ref -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Ref -> State# s -> State# s # |
Version of the effect.
Instances
Show Version Source # | |
Eq Version Source # | |
Ord Version Source # | |
Prim Version Source # | |
Defined in Effectful.Internal.Env sizeOfType# :: Proxy Version -> Int# # alignmentOfType# :: Proxy Version -> Int# # alignment# :: Version -> Int# # indexByteArray# :: ByteArray# -> Int# -> Version # readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, Version #) # writeByteArray# :: MutableByteArray# s -> Int# -> Version -> State# s -> State# s # setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Version -> State# s -> State# s # indexOffAddr# :: Addr# -> Int# -> Version # readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, Version #) # writeOffAddr# :: Addr# -> Int# -> Version -> State# s -> State# s # setOffAddr# :: Addr# -> Int# -> Int# -> Version -> State# s -> State# s # |
StorageData
data StorageData Source #
copyStorageData :: HasCallStack => StorageData -> IO StorageData Source #
Make a shallow copy of the StorageData
.
Since: 2.5.0.0
restoreStorageData :: HasCallStack => StorageData -> Env es -> IO () Source #
Restore a shallow copy of the StorageData
.
The copy needs to be from the same Env
as the target.
Since: 2.5.0.0
Utils
data AnyRelinker Source #
Relinker in Storage
.
toAnyRelinker :: Relinker (EffectRep (DispatchOf e)) e -> AnyRelinker Source #
fromAnyRelinker :: AnyRelinker -> Relinker (EffectRep (DispatchOf e)) e Source #
toAnyEffect :: EffectRep (DispatchOf e) e -> AnyEffect Source #
fromAnyEffect :: AnyEffect -> EffectRep (DispatchOf e) e Source #
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
cloneEnv :: HasCallStack => Env es -> IO (Env es) Source #
Clone the environment to use it in a different thread.
Modification of the effect stack
:: HasCallStack | |
=> 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 :: HasCallStack => 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. (HasCallStack, 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. (HasCallStack, 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 subEs es. Subset subEs es => Env es -> IO (Env subEs) 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. (HasCallStack, e :> es) | |
=> Env es | The environment. |
-> IO (EffectRep (DispatchOf e) e) |
Extract a specific data type from the environment.
:: forall e es. (HasCallStack, 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. (HasCallStack, e :> es) | |
=> Env es | The environment. |
-> (EffectRep (DispatchOf e) e -> (a, EffectRep (DispatchOf e) e)) | |
-> IO a |
Modify the data type in the environment and return a value (in place).
:: forall e es. (HasCallStack, e :> es) | |
=> Env es | The environment. |
-> (EffectRep (DispatchOf e) e -> EffectRep (DispatchOf e) e) | |
-> IO () |
Modify the data type in the environment (in place).