effet-0.1.0.0: An Effect System based on Type Classes
Copyright(c) Michael Szvetits 2020
LicenseBSD3 (see the file LICENSE)
Maintainertypedbyte@qualified.name
Stabilitystable
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Control.Effect.State

Description

The state effect, similar to the MonadState type class from the mtl library.

Lazy and strict interpretations of the effect are available here: Control.Effect.State.Lazy and Control.Effect.State.Strict.

Synopsis

Tagged State Effect

class Monad m => State' tag s m | tag m -> s where Source #

An effect that adds a mutable state to a given computation.

Minimal complete definition

get', put' | state'

Methods

get' :: m s Source #

Gets the current state.

put' :: s -> m () Source #

Replaces the state with a new value.

state' :: (s -> (s, a)) -> m a Source #

Updates the state and produces a value based on the current state.

Instances

Instances details
Monad m => State' (tag :: k) s (StateT s m) Source # 
Instance details

Defined in Control.Effect.State

Methods

get' :: StateT s m s Source #

put' :: s -> StateT s m () Source #

state' :: (s -> (s, a)) -> StateT s m a Source #

Monad m => State' (tag :: k) s (StateT s m) Source # 
Instance details

Defined in Control.Effect.State

Methods

get' :: StateT s m s Source #

put' :: s -> StateT s m () Source #

state' :: (s -> (s, a)) -> StateT s m a Source #

Lift (State' tag s) t m => State' (tag :: k) s (Via eff t m) Source # 
Instance details

Defined in Control.Effect.State

Methods

get' :: Via eff t m s Source #

put' :: s -> Via eff t m () Source #

state' :: (s -> (s, a)) -> Via eff t m a Source #

Handle (State' tag s) t m => State' (tag :: k) s (Via (State' tag s) t m) Source # 
Instance details

Defined in Control.Effect.State

Methods

get' :: Via (State' tag s) t m s Source #

put' :: s -> Via (State' tag s) t m () Source #

state' :: (s -> (s, a)) -> Via (State' tag s) t m a Source #

State' new s m => State' (tag :: k2) s (Tagger tag new m) Source # 
Instance details

Defined in Control.Effect.State

Methods

get' :: Tagger tag new m s Source #

put' :: s -> Tagger tag new m () Source #

state' :: (s -> (s, a)) -> Tagger tag new m a Source #

Untagged State Effect

If you don't require disambiguation of multiple state effects (i.e., you only have one state effect in your monadic context), it is recommended to always use the untagged state effect.

type State s = State' G s Source #

get :: State s m => m s Source #

put :: State s m => s -> m () Source #

state :: State s m => (s -> (s, a)) -> m a Source #

Convenience Functions

If you don't require disambiguation of multiple state effects (i.e., you only have one state effect in your monadic context), it is recommended to always use the untagged functions.

gets' :: forall tag s m a. State' tag s m => (s -> a) -> m a Source #

Gets a specific component of the state, using the provided projection function.

gets :: State s m => (s -> a) -> m a Source #

The untagged version of gets'.

modify' :: forall tag s m. State' tag s m => (s -> s) -> m () Source #

Modifies the state, using the provided function.

modify :: State s m => (s -> s) -> m () Source #

The untagged version of modify'.

modifyStrict' :: forall tag s m. State' tag s m => (s -> s) -> m () Source #

Modifies the state, using the provided function. The computation is strict in the new state.

modifyStrict :: State s m => (s -> s) -> m () Source #

The untagged version of modifyStrict'.

Tagging and Untagging

Conversion functions between the tagged and untagged state effect, usually used in combination with type applications, like:

    tagState' @"newTag" program
    retagState' @"oldTag" @"newTag" program
    untagState' @"erasedTag" program

tagState' :: forall new s m a. Via (State' G s) (Tagger G new) m a -> m a Source #

retagState' :: forall tag new s m a. Via (State' tag s) (Tagger tag new) m a -> m a Source #

untagState' :: forall tag s m a. Via (State' tag s) (Tagger tag G) m a -> m a Source #