Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Support for access to a mutable value of a particular type.
The value is thread local. If you want it to be shared between threads, use Effectful.State.Static.Shared.
Note: unlike the StateT
monad transformer from
the transformers
library, the State
effect doesn't discard state updates
when an exception is received:
>>>
import Control.Exception (ErrorCall)
>>>
import Control.Monad.Catch
>>>
import Control.Monad.Trans.State.Strict qualified as S
>>>
:{
(`S.execStateT` "Hi") . handle (\(_::ErrorCall) -> pure ()) $ do S.modify (++ " there!") error "oops" :} "Hi"
>>>
:{
runEff . execState "Hi" . handle (\(_::ErrorCall) -> pure ()) $ do modify (++ " there!") error "oops" :} "Hi there!"
Synopsis
- data State (s :: Type) :: Effect
- runState :: HasCallStack => s -> Eff (State s : es) a -> Eff es (a, s)
- evalState :: HasCallStack => s -> Eff (State s : es) a -> Eff es a
- execState :: HasCallStack => s -> Eff (State s : es) a -> Eff es s
- get :: (HasCallStack, State s :> es) => Eff es s
- gets :: (HasCallStack, State s :> es) => (s -> a) -> Eff es a
- put :: (HasCallStack, State s :> es) => s -> Eff es ()
- state :: (HasCallStack, State s :> es) => (s -> (a, s)) -> Eff es a
- modify :: (HasCallStack, State s :> es) => (s -> s) -> Eff es ()
- stateM :: (HasCallStack, State s :> es) => (s -> Eff es (a, s)) -> Eff es a
- modifyM :: (HasCallStack, State s :> es) => (s -> Eff es s) -> Eff es ()
Effect
data State (s :: Type) :: Effect Source #
Provide access to a strict (WHNF), thread local, mutable value of type s
.
Instances
type DispatchOf (State s) Source # | |
Defined in Effectful.State.Static.Local | |
newtype StaticRep (State s) Source # | |
Defined in Effectful.State.Static.Local |
Handlers
:: HasCallStack | |
=> s | The initial state. |
-> Eff (State s : es) a | |
-> Eff es (a, s) |
Run the State
effect with the given initial state and return the final
value along with the final state.
:: HasCallStack | |
=> s | The initial state. |
-> Eff (State s : es) a | |
-> Eff es a |
Run the State
effect with the given initial state and return the final
value, discarding the final state.
:: HasCallStack | |
=> s | The initial state. |
-> Eff (State s : es) a | |
-> Eff es s |
Run the State
effect with the given initial state and return the final
state, discarding the final value.
Operations
:: (HasCallStack, State s :> es) | |
=> (s -> a) | The function to apply to the state. |
-> Eff es a |
put :: (HasCallStack, State s :> es) => s -> Eff es () Source #
Set the current state to the given value.
:: (HasCallStack, State s :> es) | |
=> (s -> (a, s)) | The function to modify the state. |
-> Eff es a |
Apply the function to the current state and return a value.
:: (HasCallStack, State s :> es) | |
=> (s -> s) | The function to modify the state. |
-> Eff es () |
:: (HasCallStack, State s :> es) | |
=> (s -> Eff es (a, s)) | The function to modify the state. |
-> Eff es a |
Apply the monadic function to the current state and return a value.