phantom-state-0.2.1.1: Phantom State Transformer. Like State Monad, but without values.

Safe HaskellSafe
LanguageHaskell2010

Control.Applicative.PhantomState

Description

Phantom State Transformer type and functions.

Synopsis

Documentation

data PhantomStateT s m a Source #

The Phantom State Transformer is like the State Monad Transformer, but it does not hold any value. Therefore, it automatically discards the result of any computation. Only changes in the state and effects will remain. This transformer produces a new Applicative functor from any Monad. The primitive operations in this functor are:

Although useState and changeState are defined in terms of useAndChangeState:

   useState f = useAndChangeState (\s -> f s *> pure s)
changeState f = useAndChangeState (pure . f)

So useAndChangeState is the only actual primitive.

Use runPhantomStateT (or runPhantomState) to get the result of a phantom state computation.

Instances

Functor (PhantomStateT s m) Source # 

Methods

fmap :: (a -> b) -> PhantomStateT s m a -> PhantomStateT s m b #

(<$) :: a -> PhantomStateT s m b -> PhantomStateT s m a #

Monad m => Applicative (PhantomStateT s m) Source # 

Methods

pure :: a -> PhantomStateT s m a #

(<*>) :: PhantomStateT s m (a -> b) -> PhantomStateT s m a -> PhantomStateT s m b #

(*>) :: PhantomStateT s m a -> PhantomStateT s m b -> PhantomStateT s m b #

(<*) :: PhantomStateT s m a -> PhantomStateT s m b -> PhantomStateT s m a #

(Monad m, Alternative m) => Alternative (PhantomStateT s m) Source # 

Methods

empty :: PhantomStateT s m a #

(<|>) :: PhantomStateT s m a -> PhantomStateT s m a -> PhantomStateT s m a #

some :: PhantomStateT s m a -> PhantomStateT s m [a] #

many :: PhantomStateT s m a -> PhantomStateT s m [a] #

type PhantomState s = PhantomStateT s Identity Source #

Type synonym of PhantomStateT where the underlying Monad is the Identity monad.

useState :: Applicative m => (s -> m a) -> PhantomStateT s m () Source #

Perform an applicative action using the current state, leaving the state unchanged. The result will be discarded, so only the effect will remain.

changeState :: Applicative m => (s -> s) -> PhantomStateT s m () Source #

Modify the state using a pure function. No effect will be produced, only the state will be modified.

useAndChangeState :: (s -> m s) -> PhantomStateT s m () Source #

Combination of useState and changeState. It allows you to change the state while performing any effects. The new state will be the result of applying the argument function to the old state. The following equations hold:

   useState f *> changeState g }
                               } = useAndChangeState (\s -> f s *> g s)
changeState g *>    useState f }

runPhantomStateT Source #

Arguments

:: PhantomStateT s m a

Phantom state computation

-> s

Initial state

-> m s

Final result

Perform a phantom state computation by setting an initial state and running all the actions from there.

runPhantomState Source #

Arguments

:: PhantomState s a

Phantom state computation

-> s

Initial state

-> s

Final result

Specialized version of runPhantomStateT where the underlying Monad is the Identity monad.