Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data State s m k
- get :: (Member (State s) sig, Carrier sig m) => m s
- gets :: (Member (State s) sig, Carrier sig m) => (s -> a) -> m a
- put :: (Member (State s) sig, Carrier sig m) => s -> m ()
- modify :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m ()
- modifyLazy :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m ()
- class Member (sub :: (* -> *) -> * -> *) sup
State effect
Instances
Effect (State s) Source # | |
HFunctor (State s) Source # | |
Generic1 (State s m :: Type -> Type) Source # | |
Functor m => Functor (State s m) Source # | |
(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # | |
(Carrier sig m, Effect sig) => Carrier (State s :+: sig) (StateC s m) Source # | |
type Rep1 (State s m :: Type -> Type) Source # | |
Defined in Control.Effect.State.Internal type Rep1 (State s m :: Type -> Type) = D1 ('MetaData "State" "Control.Effect.State.Internal" "fused-effects-0.5.0.1-inplace" 'False) (C1 ('MetaCons "Get" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (((->) s :: Type -> Type) :.: Rec1 m)) :+: C1 ('MetaCons "Put" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 m))) |
get :: (Member (State s) sig, Carrier sig m) => m s Source #
Get the current state value.
snd (run (runState a get)) === a
gets :: (Member (State s) sig, Carrier sig m) => (s -> a) -> m a Source #
Project a function out of the current state value.
snd (run (runState a (gets (applyFun f)))) === applyFun f a
put :: (Member (State s) sig, Carrier sig m) => s -> m () Source #
Replace the state value with a new value.
fst (run (runState a (put b))) === b
snd (run (runState a (get <* put b))) === a
snd (run (runState a (put b *> get))) === b
modify :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #
Replace the state value with the result of applying a function to the current state value. This is strict in the new state.
fst (run (runState a (modify (+1)))) === (1 + a :: Integer)
modifyLazy :: (Member (State s) sig, Carrier sig m) => (s -> s) -> m () Source #
Replace the state value with the result of applying a function to the current state value. This is lazy in the new state; injudicious use of this function may lead to space leaks.