Copyright | (c) Andy Gill 2001 (c) Oregon Graduate Institute of Science and Technology 2001 |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | ross@soi.city.ac.uk |
Stability | experimental |
Portability | non-portable (type families) |
Safe Haskell | None |
Language | GHC2021 |
Control.Monad.State.Strict
Description
Strict state monads.
This module is inspired by the paper /Functional Programming with Overloading and Higher-Order Polymorphism/, Mark P Jones (http://web.cecs.pdx.edu/~mpj/) Advanced School of Functional Programming, 1995.
Synopsis
- class Monad m => MonadState (m :: Type -> Type) where
- modify :: MonadState m => (StateType m -> StateType m) -> m ()
- gets :: MonadState m => (StateType m -> a) -> m a
- type State s = StateT s Identity
- runState :: State s a -> s -> (a, s)
- evalState :: State s a -> s -> a
- execState :: State s a -> s -> s
- mapState :: ((a, s) -> (b, s)) -> State s a -> State s b
- withState :: (s -> s) -> State s a -> State s a
- newtype StateT s (m :: Type -> Type) a = StateT {
- runStateT :: s -> m (a, s)
- evalStateT :: Monad m => StateT s m a -> s -> m a
- execStateT :: Monad m => StateT s m a -> s -> m s
- mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b
- withStateT :: forall s (m :: Type -> Type) a. (s -> s) -> StateT s m a -> StateT s m a
- class Applicative m => Monad (m :: Type -> Type) where
- class Monad m => MonadFail (m :: Type -> Type) where
- fail :: String -> m a
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- class Functor (f :: Type -> Type) where
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- join :: Monad m => m (m a) -> m a
- class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where
- ap :: Monad m => m (a -> b) -> m a -> m b
- liftM :: Monad m => (a1 -> r) -> m a1 -> m r
- liftM2 :: Monad m => (a1 -> a2 -> r) -> m a1 -> m a2 -> m r
- liftM3 :: Monad m => (a1 -> a2 -> a3 -> r) -> m a1 -> m a2 -> m a3 -> m r
- liftM4 :: Monad m => (a1 -> a2 -> a3 -> a4 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m r
- liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r
- when :: Applicative f => Bool -> f () -> f ()
- forM_ :: (Foldable t, Monad m) => t a -> (a -> m b) -> m ()
- msum :: (Foldable t, MonadPlus m) => t (m a) -> m a
- void :: Functor f => f a -> f ()
- forM :: (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b)
- (<$!>) :: Monad m => (a -> b) -> m a -> m b
- (<=<) :: Monad m => (b -> m c) -> (a -> m b) -> a -> m c
- (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c
- foldM :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m b
- foldM_ :: (Foldable t, Monad m) => (b -> a -> m b) -> b -> t a -> m ()
- replicateM :: Applicative m => Int -> m a -> m [a]
- replicateM_ :: Applicative m => Int -> m a -> m ()
- unless :: Applicative f => Bool -> f () -> f ()
- filterM :: Applicative m => (a -> m Bool) -> [a] -> m [a]
- forever :: Applicative f => f a -> f b
- mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c])
- mfilter :: MonadPlus m => (a -> Bool) -> m a -> m a
- zipWithM :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m [c]
- zipWithM_ :: Applicative m => (a -> b -> m c) -> [a] -> [b] -> m ()
- guard :: Alternative f => Bool -> f ()
- class Monad m => MonadFix (m :: Type -> Type) where
- mfix :: (a -> m a) -> m a
- fix :: (a -> a) -> a
- module Control.Monad.Trans
MonadState class
class Monad m => MonadState (m :: Type -> Type) where Source #
get returns the state from the internals of the monad.
put replaces the state inside the monad.
Instances
MonadState m => MonadState (MaybeT m) Source # | |
MonadState m => MonadState (ExceptT e m) Source # | |
MonadState m => MonadState (IdentityT m) Source # | |
MonadState m => MonadState (ReaderT r m) Source # | |
Monad m => MonadState (StateT s m) Source # | |
Monad m => MonadState (StateT s m) Source # | |
(Monoid w, MonadState m) => MonadState (WriterT w m) Source # | |
(Monoid w, MonadState m) => MonadState (WriterT w m) Source # | |
MonadState m => MonadState (ContT r m) Source # | |
(Monad m, Monoid w) => MonadState (RWST r w s m) Source # | |
(Monad m, Monoid w) => MonadState (RWST r w s m) Source # | |
modify :: MonadState m => (StateType m -> StateType m) -> m () Source #
Monadic state transformer.
Maps an old state to a new state inside a state monad. The old state is thrown away.
Main> :t modify ((+1) :: Int -> Int) modify (...) :: (MonadState Int a) => a ()
This says that modify (+1)
acts over any
Monad that is a member of the MonadState
class,
with an Int
state.
gets :: MonadState m => (StateType m -> a) -> m a Source #
Gets specific component of the state, using a projection function supplied.
The State monad
The StateT monad transformer
newtype StateT s (m :: Type -> Type) a #
Instances
MonadTrans (StateT s) | |||||
Defined in Control.Monad.Trans.State.Strict | |||||
MonadFail m => MonadFail (StateT s m) | |||||
Defined in Control.Monad.Trans.State.Strict | |||||
MonadFix m => MonadFix (StateT s m) | |||||
Defined in Control.Monad.Trans.State.Strict | |||||
MonadIO m => MonadIO (StateT s m) | |||||
Defined in Control.Monad.Trans.State.Strict | |||||
Contravariant m => Contravariant (StateT s m) | |||||
(Functor m, MonadPlus m) => Alternative (StateT s m) | |||||
(Functor m, Monad m) => Applicative (StateT s m) | |||||
Defined in Control.Monad.Trans.State.Strict | |||||
Functor m => Functor (StateT s m) | |||||
Monad m => Monad (StateT s m) | |||||
MonadPlus m => MonadPlus (StateT s m) | |||||
MonadCont m => MonadCont (StateT s m) Source # | |||||
MonadError m => MonadError (StateT s m) Source # | |||||
Defined in Control.Monad.Except.Class Associated Types
| |||||
MonadReader m => MonadReader (StateT s m) Source # | |||||
Defined in Control.Monad.Reader.Class Associated Types
| |||||
Monad m => MonadState (StateT s m) Source # | |||||
MonadWriter m => MonadWriter (StateT s m) Source # | |||||
Defined in Control.Monad.Writer.Class Associated Types
| |||||
Generic (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict Associated Types
| |||||
type ErrorType (StateT s m) Source # | |||||
Defined in Control.Monad.Except.Class | |||||
type EnvType (StateT s m) Source # | |||||
Defined in Control.Monad.Reader.Class | |||||
type StateType (StateT s m) Source # | |||||
Defined in Control.Monad.State.Class | |||||
type WriterType (StateT s m) Source # | |||||
Defined in Control.Monad.Writer.Class | |||||
type Rep (StateT s m a) | |||||
Defined in Control.Monad.Trans.State.Strict type Rep (StateT s m a) = D1 ('MetaData "StateT" "Control.Monad.Trans.State.Strict" "transformers-0.6.1.0-a97a" 'True) (C1 ('MetaCons "StateT" 'PrefixI 'True) (S1 ('MetaSel ('Just "runStateT") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (s -> m (a, s))))) |
evalStateT :: Monad m => StateT s m a -> s -> m a #
execStateT :: Monad m => StateT s m a -> s -> m s #
withStateT :: forall s (m :: Type -> Type) a. (s -> s) -> StateT s m a -> StateT s m a #
class Applicative m => Monad (m :: Type -> Type) where #
Minimal complete definition
Instances
Monad Complex | |
Monad Identity | |
Monad First | |
Monad Last | |
Monad Down | |
Monad First | |
Monad Last | |
Monad Max | |
Monad Min | |
Monad Dual | |
Monad Product | |
Monad Sum | |
Monad NonEmpty | |
Monad STM | |
Monad NoIO | |
Monad Par1 | |
Monad P | |
Monad ReadP | |
Monad ReadPrec | |
Monad IO | |
Monad Maybe | |
Monad Solo | |
Monad [] | |
Monad m => Monad (WrappedMonad m) | |
ArrowApply a => Monad (ArrowMonad a) | |
Monad (Either e) | |
Monad (Proxy :: Type -> Type) | |
Monad (U1 :: Type -> Type) | |
Monad (ST s) | |
Monad m => Monad (MaybeT m) | |
Monoid a => Monad ((,) a) | |
Monad m => Monad (Kleisli m a) | |
Monad f => Monad (Ap f) | |
Monad f => Monad (Alt f) | |
Monad f => Monad (Rec1 f) | |
(Monoid w, Functor m, Monad m) => Monad (AccumT w m) | |
Monad m => Monad (ExceptT e m) | |
Monad m => Monad (IdentityT m) | |
Monad m => Monad (ReaderT r m) | |
Monad m => Monad (SelectT r m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
Monad m => Monad (Reverse m) | |
(Monoid a, Monoid b) => Monad ((,,) a b) | |
(Monad f, Monad g) => Monad (Product f g) | |
(Monad f, Monad g) => Monad (f :*: g) | |
Monad (ContT r m) | |
(Monoid a, Monoid b, Monoid c) => Monad ((,,,) a b c) | |
Monad ((->) r) | |
Monad f => Monad (M1 i c f) | |
Monad m => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
class Monad m => MonadFail (m :: Type -> Type) where #
Instances
class Functor (f :: Type -> Type) where #
Minimal complete definition
Instances
Functor ZipList | |
Defined in Control.Applicative | |
Functor Handler | |
Defined in Control.Exception | |
Functor Complex | |
Defined in Data.Complex | |
Functor Identity | |
Functor First | |
Functor Last | |
Functor Down | |
Functor First | |
Defined in Data.Semigroup | |
Functor Last | |
Defined in Data.Semigroup | |
Functor Max | |
Defined in Data.Semigroup | |
Functor Min | |
Defined in Data.Semigroup | |
Functor Dual | |
Functor Product | |
Functor Sum | |
Functor NonEmpty | |
Functor STM | |
Defined in GHC.Conc.Sync | |
Functor NoIO | |
Functor Par1 | |
Defined in GHC.Generics | |
Functor ArgDescr | |
Defined in System.Console.GetOpt | |
Functor ArgOrder | |
Defined in System.Console.GetOpt | |
Functor OptDescr | |
Defined in System.Console.GetOpt | |
Functor P | |
Defined in Text.ParserCombinators.ReadP | |
Functor ReadP | |
Defined in Text.ParserCombinators.ReadP | |
Functor ReadPrec | |
Defined in Text.ParserCombinators.ReadPrec | |
Functor IO | |
Functor Maybe | |
Functor Solo | |
Functor [] | |
Monad m => Functor (WrappedMonad m) | |
Defined in Control.Applicative | |
Arrow a => Functor (ArrowMonad a) | |
Defined in Control.Arrow | |
Functor (Either a) | |
Defined in Data.Either | |
Functor (Proxy :: Type -> Type) | |
Defined in Data.Proxy | |
Functor (Arg a) | |
Defined in Data.Semigroup | |
Functor (Array i) | |
Functor (U1 :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (V1 :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (ST s) | |
Functor f => Functor (Lift f) | |
Defined in Control.Applicative.Lift | |
Functor m => Functor (MaybeT m) | |
Defined in Control.Monad.Trans.Maybe | |
Functor ((,) a) | |
Arrow a => Functor (WrappedArrow a b) | |
Defined in Control.Applicative | |
Functor m => Functor (Kleisli m a) | |
Defined in Control.Arrow | |
Functor (Const m :: Type -> Type) | |
Defined in Data.Functor.Const | |
Functor f => Functor (Ap f) | |
Functor f => Functor (Alt f) | |
(Generic1 f, Functor (Rep1 f)) => Functor (Generically1 f) | |
Defined in GHC.Generics | |
Functor f => Functor (Rec1 f) | |
Defined in GHC.Generics | |
Functor (URec (Ptr ()) :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (URec Char :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (URec Double :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (URec Float :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (URec Int :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (URec Word :: Type -> Type) | |
Defined in GHC.Generics | |
Functor f => Functor (Backwards f) | |
Defined in Control.Applicative.Backwards | |
Functor m => Functor (AccumT w m) | |
Defined in Control.Monad.Trans.Accum | |
Functor m => Functor (ExceptT e m) | |
Functor m => Functor (IdentityT m) | |
Defined in Control.Monad.Trans.Identity | |
Functor m => Functor (ReaderT r m) | |
Functor m => Functor (SelectT r m) | |
Defined in Control.Monad.Trans.Select | |
Functor m => Functor (StateT s m) | |
Functor m => Functor (StateT s m) | |
Functor m => Functor (WriterT w m) | |
Defined in Control.Monad.Trans.Writer.CPS | |
Functor m => Functor (WriterT w m) | |
Functor m => Functor (WriterT w m) | |
Functor (Constant a :: Type -> Type) | |
Defined in Data.Functor.Constant | |
Functor f => Functor (Reverse f) | |
Defined in Data.Functor.Reverse | |
Functor ((,,) a b) | |
(Functor f, Functor g) => Functor (Product f g) | |
Defined in Data.Functor.Product | |
(Functor f, Functor g) => Functor (Sum f g) | |
Defined in Data.Functor.Sum | |
(Functor f, Functor g) => Functor (f :*: g) | |
Defined in GHC.Generics | |
(Functor f, Functor g) => Functor (f :+: g) | |
Defined in GHC.Generics | |
Functor (K1 i c :: Type -> Type) | |
Defined in GHC.Generics | |
Functor (ContT r m) | |
Functor ((,,,) a b c) | |
Functor ((->) r) | |
(Functor f, Functor g) => Functor (Compose f g) | |
Defined in Data.Functor.Compose | |
(Functor f, Functor g) => Functor (f :.: g) | |
Defined in GHC.Generics | |
Functor f => Functor (M1 i c f) | |
Defined in GHC.Generics | |
Functor m => Functor (RWST r w s m) | |
Defined in Control.Monad.Trans.RWS.CPS | |
Functor m => Functor (RWST r w s m) | |
Functor m => Functor (RWST r w s m) | |
Functor ((,,,,) a b c d) | |
Functor ((,,,,,) a b c d e) | |
Functor ((,,,,,,) a b c d e f) | |
class (Alternative m, Monad m) => MonadPlus (m :: Type -> Type) where #
Minimal complete definition
Nothing
Instances
liftM5 :: Monad m => (a1 -> a2 -> a3 -> a4 -> a5 -> r) -> m a1 -> m a2 -> m a3 -> m a4 -> m a5 -> m r #
replicateM :: Applicative m => Int -> m a -> m [a] #
replicateM_ :: Applicative m => Int -> m a -> m () #
mapAndUnzipM :: Applicative m => (a -> m (b, c)) -> [a] -> m ([b], [c]) #
class Monad m => MonadFix (m :: Type -> Type) where #
Instances
module Control.Monad.Trans
Examples
A function to increment a counter. Taken from the paper Generalising Monads to Arrows, John Hughes (http://www.math.chalmers.se/~rjmh/), November 1998:
tick :: State Int Int tick = do n <- get put (n+1) return n
Add one to the given number using the state monad:
plusOne :: Int -> Int plusOne n = execState tick n
A contrived addition example. Works only with positive numbers:
plus :: Int -> Int -> Int plus n x = execState (sequence $ replicate n tick) x
An example from The Craft of Functional Programming, Simon Thompson (http://www.cs.kent.ac.uk/people/staff/sjt/), Addison-Wesley 1999: "Given an arbitrary tree, transform it to a tree of integers in which the original elements are replaced by natural numbers, starting from 0. The same element has to be replaced by the same number at every occurrence, and when we meet an as-yet-unvisited element we have to find a 'new' number to match it with:"
data Tree a = Nil | Node a (Tree a) (Tree a) deriving (Show, Eq) type Table a = [a]
numberTree :: Eq a => Tree a -> State (Table a) (Tree Int) numberTree Nil = return Nil numberTree (Node x t1 t2) = do num <- numberNode x nt1 <- numberTree t1 nt2 <- numberTree t2 return (Node num nt1 nt2) where numberNode :: Eq a => a -> State (Table a) Int numberNode x = do table <- get (newTable, newPos) <- return (nNode x table) put newTable return newPos nNode:: (Eq a) => a -> Table a -> (Table a, Int) nNode x table = case (findIndexInList (== x) table) of Nothing -> (table ++ [x], length table) Just i -> (table, i) findIndexInList :: (a -> Bool) -> [a] -> Maybe Int findIndexInList = findIndexInListHelp 0 findIndexInListHelp _ _ [] = Nothing findIndexInListHelp count f (h:t) = if (f h) then Just count else findIndexInListHelp (count+1) f t
numTree applies numberTree with an initial state:
numTree :: (Eq a) => Tree a -> Tree Int numTree t = evalState (numberTree t) []
testTree = Node "Zero" (Node "One" (Node "Two" Nil Nil) (Node "One" (Node "Zero" Nil Nil) Nil)) Nil numTree testTree => Node 0 (Node 1 (Node 2 Nil Nil) (Node 1 (Node 0 Nil Nil) Nil)) Nil
sumTree is a little helper function that does not use the State monad:
sumTree :: (Num a) => Tree a -> a sumTree Nil = 0 sumTree (Node e t1 t2) = e + (sumTree t1) + (sumTree t2)