numerical-0.0.0.0: core package for Numerical Haskell project

Safe HaskellSafe
LanguageHaskell2010

Control.NumericalMonad.State.Strict

Synopsis

Documentation

newtype Identity a Source #

Identity functor and monad.

Constructors

Identity 

Fields

Instances
Monad Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

(>>=) :: Identity a -> (a -> Identity b) -> Identity b #

(>>) :: Identity a -> Identity b -> Identity b #

return :: a -> Identity a #

fail :: String -> Identity a #

Functor Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

MonadFix Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

mfix :: (a -> Identity a) -> Identity a #

Applicative Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

pure :: a -> Identity a #

(<*>) :: Identity (a -> b) -> Identity a -> Identity b #

liftA2 :: (a -> b -> c) -> Identity a -> Identity b -> Identity c #

(*>) :: Identity a -> Identity b -> Identity b #

(<*) :: Identity a -> Identity b -> Identity a #

Foldable Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

fold :: Monoid m => Identity m -> m #

foldMap :: Monoid m => (a -> m) -> Identity a -> m #

foldr :: (a -> b -> b) -> b -> Identity a -> b #

foldr' :: (a -> b -> b) -> b -> Identity a -> b #

foldl :: (b -> a -> b) -> b -> Identity a -> b #

foldl' :: (b -> a -> b) -> b -> Identity a -> b #

foldr1 :: (a -> a -> a) -> Identity a -> a #

foldl1 :: (a -> a -> a) -> Identity a -> a #

toList :: Identity a -> [a] #

null :: Identity a -> Bool #

length :: Identity a -> Int #

elem :: Eq a => a -> Identity a -> Bool #

maximum :: Ord a => Identity a -> a #

minimum :: Ord a => Identity a -> a #

sum :: Num a => Identity a -> a #

product :: Num a => Identity a -> a #

Traversable Identity Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

traverse :: Applicative f => (a -> f b) -> Identity a -> f (Identity b) #

sequenceA :: Applicative f => Identity (f a) -> f (Identity a) #

mapM :: Monad m => (a -> m b) -> Identity a -> m (Identity b) #

sequence :: Monad m => Identity (m a) -> m (Identity a) #

type State s = StateT s Identity Source #

A state monad parameterized by the type s of the state to carry.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

state Source #

Arguments

:: Monad m 
=> (s -> (a, s))

pure state transformer

-> StateT s m a

equivalent state-passing computation

Construct a state monad computation from a function. (The inverse of runState.)

runState Source #

Arguments

:: State s a

state-passing computation to execute

-> s

initial state

-> (a, s)

return value and final state

Unwrap a state monad computation as a function. (The inverse of state.)

evalState Source #

Arguments

:: State s a

state-passing computation to execute

-> s

initial value

-> a

return value of the state computation

Evaluate a state computation with the given initial state and return the final value, discarding the final state.

execState Source #

Arguments

:: State s a

state-passing computation to execute

-> s

initial value

-> s

final state

Evaluate a state computation with the given initial state and return the final state, discarding the final value.

mapState :: ((a, s) -> (b, s)) -> State s a -> State s b Source #

Map both the return value and final state of a computation using the given function.

withState :: (s -> s) -> State s a -> State s a Source #

withState f m executes action m on a state modified by applying f.

newtype StateT s m a Source #

A state transformer monad parameterized by:

  • s - The state.
  • m - The inner monad.

The return function leaves the state unchanged, while >>= uses the final state of the first computation as the initial state of the second.

Constructors

StateT 

Fields

Instances
MonadTrans (StateT s) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

lift :: Monad m => m a -> StateT s m a #

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

Defined in Control.NumericalMonad.State.Strict

Methods

(>>=) :: StateT s m a -> (a -> StateT s m b) -> StateT s m b #

(>>) :: StateT s m a -> StateT s m b -> StateT s m b #

return :: a -> StateT s m a #

fail :: String -> StateT s m a #

Functor m => Functor (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

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

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

MonadFix m => MonadFix (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

mfix :: (a -> StateT s m a) -> StateT s m a #

(Functor m, Monad m) => Applicative (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

pure :: a -> StateT s m a #

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

liftA2 :: (a -> b -> c) -> StateT s m a -> StateT s m b -> StateT s m c #

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

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

MonadIO m => MonadIO (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

liftIO :: IO a -> StateT s m a #

(Functor m, MonadPlus m) => Alternative (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

empty :: StateT s m a #

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

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

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

MonadPlus m => MonadPlus (StateT s m) Source # 
Instance details

Defined in Control.NumericalMonad.State.Strict

Methods

mzero :: StateT s m a #

mplus :: StateT s m a -> StateT s m a -> StateT s m a #

evalStateT :: Monad m => StateT s m a -> s -> m a Source #

Evaluate a state computation with the given initial state and return the final value, discarding the final state.

execStateT :: Monad m => StateT s m a -> s -> m s Source #

Evaluate a state computation with the given initial state and return the final state, discarding the final value.

mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b Source #

Map both the return value and final state of a computation using the given function.

withStateT :: (s -> s) -> StateT s m a -> StateT s m a Source #

withStateT f m executes action m on a state modified by applying f.

get :: Monad m => StateT s m s Source #

Fetch the current value of the state within the monad.

put :: Monad m => s -> StateT s m () Source #

put s sets the state within the monad to s.

modify :: Monad m => (s -> s) -> StateT s m () Source #

modify f is an action that updates the state to the result of applying f to the current state.

modify' :: Monad m => (s -> s) -> StateT s m () Source #

A variant of modify in which the computation is strict in the new state.

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

Get a specific component of the state, using a projection function supplied.