Safe Haskell | None |
---|---|
Language | Haskell2010 |
Effectful.Internal.Monad
Description
The Eff
monad.
This module is intended for internal use only, and may change without warning in subsequent releases.
Synopsis
- data Eff (es :: [Effect]) a
- runPureEff :: HasCallStack => Eff ('[] :: [Effect]) a -> a
- unEff :: forall (es :: [Effect]) a. Eff es a -> Env es -> IO a
- unsafeEff :: forall (es :: [Effect]) a. (Env es -> IO a) -> Eff es a
- unsafeEff_ :: forall a (es :: [Effect]). IO a -> Eff es a
- data NonDet (a :: Type -> Type) b where
- data Fail (a :: Type -> Type) b where
- data IOE (a :: Type -> Type) b
- runEff :: HasCallStack => Eff '[IOE] a -> IO a
- data Prim (a :: Type -> Type) b
- data PrimStateEff
- runPrim :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Prim ': es) a -> Eff es a
- raise :: forall (e :: Effect) (es :: [Effect]) a. Eff es a -> Eff (e ': es) a
- raiseWith :: forall (e :: Effect) (es :: [Effect]) a. HasCallStack => UnliftStrategy -> ((forall r. Eff (e ': es) r -> Eff es r) -> Eff es a) -> Eff (e ': es) a
- subsume :: forall (e :: Effect) (es :: [Effect]) a. e :> es => Eff (e ': es) a -> Eff es a
- inject :: forall (subEs :: [Effect]) (es :: [Effect]) a. Subset subEs es => Eff subEs a -> Eff es a
- class KnownPrefix es => Subset (subEs :: [Effect]) (es :: [Effect])
- data UnliftStrategy
- data Persistence
- data Limit
- unliftStrategy :: forall (es :: [Effect]). IOE :> es => Eff es UnliftStrategy
- withUnliftStrategy :: forall (es :: [Effect]) a. IOE :> es => UnliftStrategy -> Eff es a -> Eff es a
- withSeqEffToIO :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
- withEffToIO :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => UnliftStrategy -> ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
- reallyUnsafeLiftMapIO :: forall a b (es :: [Effect]). (IO a -> IO b) -> Eff es a -> Eff es b
- reallyUnsafeUnliftIO :: forall (es :: [Effect]) a. ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a
- seqUnliftIO :: forall (es :: [Effect]) a. HasCallStack => Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
- seqForkUnliftIO :: forall (es :: [Effect]) a. HasCallStack => Env es -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
- concUnliftIO :: forall (es :: [Effect]) a. HasCallStack => Env es -> Persistence -> Limit -> ((forall r. Eff es r -> IO r) -> IO a) -> IO a
- type EffectHandler (e :: Effect) (es :: [Effect]) = forall a (localEs :: [Effect]). (HasCallStack, e :> localEs) => LocalEnv localEs es -> e (Eff localEs) a -> Eff es a
- newtype LocalEnv (localEs :: [Effect]) (handlerEs :: [Effect]) = LocalEnv (Env localEs)
- data Handler (a :: Effect) where
- newtype HandlerImpl (e :: Effect) (es :: [Effect]) = HandlerImpl (EffectHandler e es)
- relinkHandler :: forall (e :: Effect). Relinker Handler e
- runHandler :: forall (e :: Effect) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Dynamic) => Handler e -> Eff (e ': es) a -> Eff es a
- send :: forall e (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) => e (Eff es) a -> Eff es a
- data family StaticRep (e :: Effect)
- type family MaybeIOE (sideEffects :: SideEffects) (es :: [Effect]) where ...
- runStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) => StaticRep e -> Eff (e ': es) a -> Eff es (a, StaticRep e)
- evalStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) => StaticRep e -> Eff (e ': es) a -> Eff es a
- execStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) => StaticRep e -> Eff (e ': es) a -> Eff es (StaticRep e)
- getStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]). (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => Eff es (StaticRep e)
- putStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]). (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => StaticRep e -> Eff es ()
- stateStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => (StaticRep e -> (a, StaticRep e)) -> Eff es a
- stateStaticRepM :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => (StaticRep e -> Eff es (a, StaticRep e)) -> Eff es a
- localStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => (StaticRep e -> StaticRep e) -> Eff es a -> Eff es a
The Eff
monad
data Eff (es :: [Effect]) a Source #
The Eff
monad provides the implementation of a computation that performs
an arbitrary set of effects. In
, Eff
es aes
is a type-level list that
contains all the effects that the computation may perform. For example, a
computation that produces an Integer
by consuming a String
from the
global environment and acting upon a single mutable value of type Bool
would have the following type:
(Reader
String
:>
es,State
Bool
:>
es) =>Eff
esInteger
Abstracting over the list of effects with (:>)
:
- Allows the computation to be used in functions that may perform other effects.
- Allows the effects to be handled in any order.
Instances
IOE :> es => MonadBaseControl IO (Eff es) Source # | Instance included for compatibility with existing code. Usage of Note: the unlifting strategy for |
IOE :> es => MonadBase IO (Eff es) Source # | Instance included for compatibility with existing code. Usage of |
Defined in Effectful.Internal.Monad | |
Fail :> es => MonadFail (Eff es) Source # | |
Defined in Effectful.Internal.Monad | |
MonadFix (Eff es) Source # | |
Defined in Effectful.Internal.Monad | |
IOE :> es => MonadIO (Eff es) Source # | |
Defined in Effectful.Internal.Monad | |
NonDet :> es => Alternative (Eff es) Source # | Since: 2.2.0.0 |
Applicative (Eff es) Source # | |
Functor (Eff es) Source # | |
Monad (Eff es) Source # | |
NonDet :> es => MonadPlus (Eff es) Source # | Since: 2.2.0.0 |
MonadCatch (Eff es) Source # | |
Defined in Effectful.Internal.Monad | |
MonadMask (Eff es) Source # | |
Defined in Effectful.Internal.Monad Methods mask :: HasCallStack => ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b # uninterruptibleMask :: HasCallStack => ((forall a. Eff es a -> Eff es a) -> Eff es b) -> Eff es b # generalBracket :: HasCallStack => Eff es a -> (a -> ExitCase b -> Eff es c) -> (a -> Eff es b) -> Eff es (b, c) # | |
MonadThrow (Eff es) Source # | |
Defined in Effectful.Internal.Monad Methods throwM :: (HasCallStack, Exception e) => e -> Eff es a # | |
Prim :> es => PrimMonad (Eff es) Source # | |
IOE :> es => MonadUnliftIO (Eff es) Source # | Instance included for compatibility with existing code. Usage of Note: the unlifting strategy for |
Defined in Effectful.Internal.Monad | |
Monoid a => Monoid (Eff es a) Source # | |
Semigroup a => Semigroup (Eff es a) Source # | |
type PrimState (Eff es) Source # | |
Defined in Effectful.Internal.Monad | |
type StM (Eff es) a Source # | |
Defined in Effectful.Internal.Monad |
runPureEff :: HasCallStack => Eff ('[] :: [Effect]) a -> a Source #
Access to the internal representation
unEff :: forall (es :: [Effect]) a. Eff es a -> Env es -> IO a Source #
Peel off the constructor of Eff
.
NonDet
data NonDet (a :: Type -> Type) b where Source #
Provide the ability to use the Alternative
and MonadPlus
instance for
Eff
.
Note: NonDet
does not backtrack. Formally, it obeys the "left-catch" law
for MonadPlus
, rather than the "left-distribution" law. This means that it
behaves more like Maybe
than []
.
Since: 2.2.0.0
Constructors
Empty :: forall (a :: Type -> Type) b. NonDet a b | |
(:<|>:) :: forall (a :: Type -> Type) b. a b -> a b -> NonDet a b |
Instances
type DispatchOf NonDet Source # | |
Defined in Effectful.Internal.Monad |
Fail
data Fail (a :: Type -> Type) b where Source #
Instances
type DispatchOf Fail Source # | |
Defined in Effectful.Internal.Monad |
IO
data IOE (a :: Type -> Type) b Source #
Run arbitrary IO
computations via MonadIO
or MonadUnliftIO
.
Note: it is not recommended to use this effect in application code as it is too liberal. Ideally, this is only used in handlers of more fine-grained effects.
Instances
type DispatchOf IOE Source # | |
Defined in Effectful.Internal.Monad | |
newtype StaticRep IOE Source # | |
Defined in Effectful.Internal.Monad |
runEff :: HasCallStack => Eff '[IOE] a -> IO a Source #
Run an Eff
computation with side effects.
For running pure computations see runPureEff
.
Prim
data Prim (a :: Type -> Type) b Source #
Provide the ability to perform primitive state-transformer actions.
Instances
type DispatchOf Prim Source # | |
Defined in Effectful.Internal.Monad | |
data StaticRep Prim Source # | |
Defined in Effectful.Internal.Monad |
data PrimStateEff Source #
runPrim :: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) => Eff (Prim ': es) a -> Eff es a Source #
Run an Eff
computation with primitive state-transformer actions.
Lifting
raise :: forall (e :: Effect) (es :: [Effect]) a. Eff es a -> Eff (e ': es) a Source #
Lift an Eff
computation into an effect stack with one more effect.
Arguments
:: forall (e :: Effect) (es :: [Effect]) a. HasCallStack | |
=> UnliftStrategy | |
-> ((forall r. Eff (e ': es) r -> Eff es r) -> Eff es a) | Continuation with the unlifting function in scope. |
-> Eff (e ': es) a |
Lift an Eff
computation into an effect stack with one more effect and
create an unlifting function with the given strategy.
Since: 1.2.0.0
subsume :: forall (e :: Effect) (es :: [Effect]) a. e :> es => Eff (e ': es) a -> Eff es a Source #
Eliminate a duplicate effect from the top of the effect stack.
inject :: forall (subEs :: [Effect]) (es :: [Effect]) a. Subset subEs es => Eff subEs a -> Eff es a Source #
Allow for running an effect stack subEs
within es
as long as subEs
is
a permutation (with possible duplicates) of a subset of es
.
Generalizes raise
and subsume
.
>>>
data E1 :: Effect
>>>
data E2 :: Effect
>>>
data E3 :: Effect
It makes it possible to rearrange the effect stack however you like:
>>>
:{
shuffle :: Eff (E3 : E1 : E2 : es) a -> Eff (E1 : E2 : E3 : es) a shuffle = inject :}
It can also turn a monomorphic effect stack into a polymorphic one:
>>>
:{
toPoly :: (E1 :> es, E2 :> es, E3 :> es) => Eff [E1, E2, E3] a -> Eff es a toPoly = inject :}
Moreover, it allows for hiding specific effects from downstream:
>>>
:{
onlyE1 :: Eff (E1 : es) a -> Eff (E1 : E2 : E3 : es) a onlyE1 = inject :}
>>>
:{
onlyE2 :: Eff (E2 : es) a -> Eff (E1 : E2 : E3 : es) a onlyE2 = inject :}
>>>
:{
onlyE3 :: Eff (E3 : es) a -> Eff (E1 : E2 : E3 : es) a onlyE3 = inject :}
However, it's not possible to inject a computation into an incompatible effect stack:
>>>
:{
coerceEs :: Eff es1 a -> Eff es2 a coerceEs = inject :} ... ...Couldn't match type ‘es1’ with ‘es2’ ...
class KnownPrefix es => Subset (subEs :: [Effect]) (es :: [Effect]) Source #
Provide evidence that subEs
is a subset of es
.
Instances
(KnownPrefix es, IsUnknownSuffixOf subEs es) => Subset subEs es Source # | |
Defined in Effectful.Internal.Effect | |
KnownPrefix es => Subset ('[] :: [Effect]) es Source # | |
Defined in Effectful.Internal.Effect | |
(e :> es, Subset subEs es) => Subset (e ': subEs) es Source # | |
Defined in Effectful.Internal.Effect |
Unlifting
data UnliftStrategy Source #
The strategy to use when unlifting Eff
computations via
withEffToIO
or the localUnlift
family.
Constructors
SeqUnlift | The sequential strategy is the fastest and a default setting for
|
SeqForkUnlift | Like The main consequence is that thread local state is forked at the point of creation of the unlifting function and its modifications in unlifted actions will not affect the main thread of execution (and vice versa):
Because of this it's possible to safely use the unlifting function outside
of the scope of effects it captures, e.g. by creating an
This doesn't work with the
However, it does with the
|
ConcUnlift !Persistence !Limit | The concurrent strategy makes it possible for the unlifting function to
be called in threads distinct from its creator. See |
Instances
data Persistence Source #
Persistence setting for the ConcUnlift
strategy.
Different functions require different persistence strategies. Examples:
- Lifting
pooledMapConcurrentlyN
from theunliftio
library requires theEphemeral
strategy as we don't want jobs to share environment changes made by previous jobs run in the same worker thread. - Lifting
forkIOWithUnmask
requires thePersistent
strategy, otherwise the unmasking function would start with a fresh environment each time it's called.
Constructors
Ephemeral | Don't persist the environment between calls to the unlifting function in threads distinct from its creator. |
Persistent | Persist the environment between calls to the unlifting function within a particular thread. |
Instances
Generic Persistence Source # | |||||
Defined in Effectful.Internal.Unlift Associated Types
| |||||
Show Persistence Source # | |||||
Defined in Effectful.Internal.Unlift Methods showsPrec :: Int -> Persistence -> ShowS # show :: Persistence -> String # showList :: [Persistence] -> ShowS # | |||||
Eq Persistence Source # | |||||
Defined in Effectful.Internal.Unlift | |||||
Ord Persistence Source # | |||||
Defined in Effectful.Internal.Unlift Methods compare :: Persistence -> Persistence -> Ordering # (<) :: Persistence -> Persistence -> Bool # (<=) :: Persistence -> Persistence -> Bool # (>) :: Persistence -> Persistence -> Bool # (>=) :: Persistence -> Persistence -> Bool # max :: Persistence -> Persistence -> Persistence # min :: Persistence -> Persistence -> Persistence # | |||||
type Rep Persistence Source # | |||||
Defined in Effectful.Internal.Unlift |
Limit setting for the ConcUnlift
strategy.
Constructors
Limited !Int | Behavior dependent on the For For |
Unlimited | Unlimited use of the unlifting function. |
Instances
Generic Limit Source # | |||||
Defined in Effectful.Internal.Unlift Associated Types
| |||||
Show Limit Source # | |||||
Eq Limit Source # | |||||
Ord Limit Source # | |||||
type Rep Limit Source # | |||||
Defined in Effectful.Internal.Unlift type Rep Limit = D1 ('MetaData "Limit" "Effectful.Internal.Unlift" "effectful-core-2.6.0.0-2J5EHoJSFqEG0OIwK15iAf" 'False) (C1 ('MetaCons "Limited" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Unlimited" 'PrefixI 'False) (U1 :: Type -> Type)) |
unliftStrategy :: forall (es :: [Effect]). IOE :> es => Eff es UnliftStrategy Source #
Get the current UnliftStrategy
.
Note: this strategy is implicitly used by the MonadUnliftIO
and
MonadBaseControl
instance for Eff
.
withUnliftStrategy :: forall (es :: [Effect]) a. IOE :> es => UnliftStrategy -> Eff es a -> Eff es a Source #
Locally override the current UnliftStrategy
with the given value.
Arguments
:: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) | |
=> ((forall r. Eff es r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create an unlifting function with the SeqUnlift
strategy. For the general
version see withEffToIO
.
Note: usage of this function is preferrable to withRunInIO
because of explicit unlifting strategy and better error reporting.
Since: 2.2.2.0
Arguments
:: forall (es :: [Effect]) a. (HasCallStack, IOE :> es) | |
=> UnliftStrategy | |
-> ((forall r. Eff es r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> Eff es a |
Create an unlifting function with the given strategy.
Note: usage of this function is preferrable to withRunInIO
because of explicit unlifting strategy and better error reporting.
reallyUnsafeLiftMapIO :: forall a b (es :: [Effect]). (IO a -> IO b) -> Eff es a -> Eff es b Source #
Utility for lifting IO
computations of type
IO
a ->IO
b
to
Eff
es a ->Eff
es b
This function is really unsafe because:
- It can be used to introduce arbitrary
IO
actions into pureEff
computations. - The
IO
computation must run its argument in a way that's perceived as sequential to the outside observer, e.g. in the same thread or in a worker thread that finishes before the argument is run again.
Warning: if you disregard the second point, you will experience weird bugs, data races or internal consistency check failures.
When in doubt, use unsafeLiftMapIO
, especially
since this version saves only a simple safety check per call of
reallyUnsafeLiftMapIO f
.
reallyUnsafeUnliftIO :: forall (es :: [Effect]) a. ((forall r. Eff es r -> IO r) -> IO a) -> Eff es a Source #
Create an unlifting function.
This function is really unsafe because:
- It can be used to introduce arbitrary
IO
actions into pureEff
computations. - Unlifted
Eff
computations must be run in a way that's perceived as sequential to the outside observer, e.g. in the same thread as the caller ofreallyUnsafeUnliftIO
or in a worker thread that finishes before another unlifted computation is run.
Warning: if you disregard the second point, you will experience weird bugs, data races or internal consistency check failures.
When in doubt, use unsafeSeqUnliftIO
, especially
since this version saves only a simple safety check per call of the unlifting
function.
Low-level unlifts
Arguments
:: forall (es :: [Effect]) a. HasCallStack | |
=> Env es | The environment. |
-> ((forall r. Eff es r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> IO a |
Create an unlifting function with the SeqUnlift
strategy.
Arguments
:: forall (es :: [Effect]) a. HasCallStack | |
=> Env es | The environment. |
-> ((forall r. Eff es r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> IO a |
Create an unlifting function with the SeqForkUnlift
strategy.
Arguments
:: forall (es :: [Effect]) a. HasCallStack | |
=> Env es | The environment. |
-> Persistence | |
-> Limit | |
-> ((forall r. Eff es r -> IO r) -> IO a) | Continuation with the unlifting function in scope. |
-> IO a |
Create an unlifting function with the ConcUnlift
strategy.
Dispatch
Dynamic dispatch
type EffectHandler (e :: Effect) (es :: [Effect]) Source #
Arguments
= forall a (localEs :: [Effect]). (HasCallStack, e :> localEs) | |
=> LocalEnv localEs es | Capture of the local environment for handling local |
-> e (Eff localEs) a | The operation. |
-> Eff es a |
Type signature of the effect handler.
newtype LocalEnv (localEs :: [Effect]) (handlerEs :: [Effect]) Source #
Opaque representation of the Eff
environment at the point of calling the
send
function, i.e. right before the control is passed to the effect
handler.
The second type variable represents effects of a handler and is needed for
technical reasons to guarantee soundness (see
SharedSuffix
for more information).
data Handler (a :: Effect) where Source #
An internal representation of dynamically dispatched effects, i.e. the effect handler bundled with its environment.
newtype HandlerImpl (e :: Effect) (es :: [Effect]) Source #
Wrapper to prevent a space leak on reconstruction of Handler
in
relinkHandler
(see https://gitlab.haskell.org/ghc/ghc/-/issues/25520).
Constructors
HandlerImpl (EffectHandler e es) |
runHandler :: forall (e :: Effect) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Dynamic) => Handler e -> Eff (e ': es) a -> Eff es a Source #
Run a dynamically dispatched effect with the given handler.
Arguments
:: forall e (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Dynamic, e :> es) | |
=> e (Eff es) a | The operation. |
-> Eff es a |
Send an operation of the given effect to its handler for execution.
Static dispatch
data family StaticRep (e :: Effect) Source #
Internal representations of statically dispatched effects.
Instances
newtype StaticRep IOE Source # | |
Defined in Effectful.Internal.Monad | |
data StaticRep Prim Source # | |
Defined in Effectful.Internal.Monad | |
newtype StaticRep (Error e) Source # | |
Defined in Effectful.Error.Static | |
newtype StaticRep (Reader r) Source # | |
Defined in Effectful.Reader.Static | |
newtype StaticRep (State s) Source # | |
Defined in Effectful.State.Static.Local | |
newtype StaticRep (State s) Source # | |
Defined in Effectful.State.Static.Shared | |
newtype StaticRep (Writer w) Source # | |
Defined in Effectful.Writer.Static.Local | |
newtype StaticRep (Writer w) Source # | |
Defined in Effectful.Writer.Static.Shared | |
data StaticRep (Labeled label e) Source # | |
Defined in Effectful.Labeled | |
data StaticRep (Provider e input f) Source # | |
data StaticRep (ProviderList providedEs input f) Source # | |
Defined in Effectful.Provider.List data StaticRep (ProviderList providedEs input f) where
|
type family MaybeIOE (sideEffects :: SideEffects) (es :: [Effect]) where ... Source #
Require the IOE
effect for running statically dispatched effects whose
operations perform side effects.
Equations
MaybeIOE 'NoSideEffects _1 = () | |
MaybeIOE 'WithSideEffects es = IOE :> es |
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) | |
=> StaticRep e | The initial representation. |
-> Eff (e ': es) a | |
-> Eff es (a, StaticRep e) |
Run a statically dispatched effect with the given initial representation and return the final value along with the final representation.
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) | |
=> StaticRep e | The initial representation. |
-> Eff (e ': es) a | |
-> Eff es a |
Run a statically dispatched effect with the given initial representation and return the final value, discarding the final representation.
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, MaybeIOE sideEffects es) | |
=> StaticRep e | The initial representation. |
-> Eff (e ': es) a | |
-> Eff es (StaticRep e) |
Run a statically dispatched effect with the given initial representation and return the final representation, discarding the final value.
getStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]). (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => Eff es (StaticRep e) Source #
Fetch the current representation of the effect.
putStaticRep :: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]). (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) => StaticRep e -> Eff es () Source #
Set the current representation of the effect to the given value.
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) | |
=> (StaticRep e -> (a, StaticRep e)) | The function to modify the representation. |
-> Eff es a |
Apply the function to the current representation of the effect and return a value.
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) | |
=> (StaticRep e -> Eff es (a, StaticRep e)) | The function to modify the representation. |
-> Eff es a |
Apply the monadic function to the current representation of the effect and return a value.
Arguments
:: forall (e :: Effect) (sideEffects :: SideEffects) (es :: [Effect]) a. (HasCallStack, DispatchOf e ~ 'Static sideEffects, e :> es) | |
=> (StaticRep e -> StaticRep e) | The function to temporarily modify the representation. |
-> Eff es a | |
-> Eff es a |
Execute a computation with a temporarily modified representation of the effect.