simple-effects-0.13.0.0: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.State

Description

The MonadState you know and love with some differences. First, there's no functional dependency limiting your stack to a single state type. This means less type inference so it might not be enough to just write getState. Write getState @MyStateType instead using TypeApplications.

Second, the functions have less generic names and are called getState and setState.

Third, since it's a part of this effect framework, you get an implement function with which you can provide a different state implementation at runtime.

Synopsis

Documentation

data State s m Source #

Constructors

StateMethods 

Fields

Instances
Effect (State s) Source # 
Instance details

Defined in Control.Effects.State

Associated Types

type CanLift (State s) t :: Constraint Source #

type ExtraConstraint (State s) m :: Constraint Source #

Methods

liftThrough :: (CanLift (State s) t, Monad m, Monad (t m)) => State s m -> State s (t m) Source #

mergeContext :: Monad m => m (State s m) -> State s m Source #

Monad m => MonadEffect (State s) (StateT s m) Source # 
Instance details

Defined in Control.Effects.State

Methods

effect :: State s (StateT s m) Source #

Generic (State s m) Source # 
Instance details

Defined in Control.Effects.State

Associated Types

type Rep (State s m) :: Type -> Type #

Methods

from :: State s m -> Rep (State s m) x #

to :: Rep (State s m) x -> State s m #

UniqueEffect State (StateT s m) (s :: Type) Source # 
Instance details

Defined in Control.Effects.State

UniqueEffect State (RuntimeImplemented (State s) m) (s :: Type) Source # 
Instance details

Defined in Control.Effects.State

type CanLift (State s) t Source # 
Instance details

Defined in Control.Effects.State

type CanLift (State s) t = MonadTrans t
type ExtraConstraint (State s) m Source # 
Instance details

Defined in Control.Effects.State

type Rep (State s m) Source # 
Instance details

Defined in Control.Effects.State

type Rep (State s m) = D1 (MetaData "State" "Control.Effects.State" "simple-effects-0.13.0.0-CkkfVtQm23r7lDFbMuonrn" False) (C1 (MetaCons "StateMethods" PrefixI True) (S1 (MetaSel (Just "_getState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (m s)) :*: S1 (MetaSel (Just "_setState") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (s -> m ()))))

getState :: forall s m. MonadEffect (State s) m => m s Source #

Get current value of the state with the type s. You can use type applications to tell the type checker which type of state you want. getState @Int

setState :: forall s m. MonadEffect (State s) m => s -> m () Source #

Set a new value for the state of type s You can use type applications to tell the type checker which type of state you're setting. setState @Int 5

modifyState :: forall s m. MonadEffect (State s) m => (s -> s) -> m () Source #

Transform the state of type s using the given function. You can use type applications to tell the type checker which type of state you're modifying. modifyState @Int (+ 1)

implementStateViaStateT :: forall s m a. Monad m => s -> StateT s m a -> m a Source #

Implement the state effect via the StateT transformer. If you have a function with a type like f :: MonadEffect (State Int) m => m () you can use implementStateViaStateT to satisfy the MonadEffect constraint.

implementStateViaStateT @Int 0 f :: Monad m => m ()

implementStateViaIORef :: forall s m a. MonadIO m => s -> RuntimeImplemented (State s) m a -> m a Source #

Handle the state requirement using an IORef. If you have a function with a type like f :: MonadEffect (State Int) m => m () you can use implementStateViaIORef to replace the MonadEffect constraint with MonadIO. This is convenient if you already have a MonadIO constraint and you don't want to use the StateT transformer for some reason.

implementStateViaIORef @Int 0 f :: MonadIO m => m ()