monads-tf-0.1.0.3: Monad classes, using type families

Copyright(c) Andy Gill 2001, (c) Oregon Graduate Institute of Science and Technology, 2001
LicenseBSD-style (see the file LICENSE)
Maintainerross@soi.city.ac.uk
Stabilityexperimental
Portabilitynon-portable (type families)
Safe HaskellSafe
LanguageHaskell98

Control.Monad.State.Class

Description

MonadState class.

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

Documentation

class Monad m => MonadState m where Source #

get returns the state from the internals of the monad.

put replaces the state inside the monad.

Minimal complete definition

get, put

Associated Types

type StateType m Source #

Methods

get :: m (StateType m) Source #

put :: StateType m -> m () Source #

Instances

MonadState m => MonadState (MaybeT m) Source # 

Associated Types

type StateType (MaybeT m :: * -> *) :: * Source #

Methods

get :: MaybeT m (StateType (MaybeT m)) Source #

put :: StateType (MaybeT m) -> MaybeT m () Source #

MonadState m => MonadState (ListT m) Source # 

Associated Types

type StateType (ListT m :: * -> *) :: * Source #

Methods

get :: ListT m (StateType (ListT m)) Source #

put :: StateType (ListT m) -> ListT m () Source #

(Monoid w, MonadState m) => MonadState (WriterT w m) Source # 

Associated Types

type StateType (WriterT w m :: * -> *) :: * Source #

Methods

get :: WriterT w m (StateType (WriterT w m)) Source #

put :: StateType (WriterT w m) -> WriterT w m () Source #

(Monoid w, MonadState m) => MonadState (WriterT w m) Source # 

Associated Types

type StateType (WriterT w m :: * -> *) :: * Source #

Methods

get :: WriterT w m (StateType (WriterT w m)) Source #

put :: StateType (WriterT w m) -> WriterT w m () Source #

Monad m => MonadState (StateT s m) Source # 

Associated Types

type StateType (StateT s m :: * -> *) :: * Source #

Methods

get :: StateT s m (StateType (StateT s m)) Source #

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

Monad m => MonadState (StateT s m) Source # 

Associated Types

type StateType (StateT s m :: * -> *) :: * Source #

Methods

get :: StateT s m (StateType (StateT s m)) Source #

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

MonadState m => MonadState (IdentityT * m) Source # 

Associated Types

type StateType (IdentityT * m :: * -> *) :: * Source #

(Error e, MonadState m) => MonadState (ErrorT e m) Source # 

Associated Types

type StateType (ErrorT e m :: * -> *) :: * Source #

Methods

get :: ErrorT e m (StateType (ErrorT e m)) Source #

put :: StateType (ErrorT e m) -> ErrorT e m () Source #

MonadState m => MonadState (ReaderT * r m) Source # 

Associated Types

type StateType (ReaderT * r m :: * -> *) :: * Source #

Methods

get :: ReaderT * r m (StateType (ReaderT * r m)) Source #

put :: StateType (ReaderT * r m) -> ReaderT * r m () Source #

MonadState m => MonadState (ContT * r m) Source # 

Associated Types

type StateType (ContT * r m :: * -> *) :: * Source #

Methods

get :: ContT * r m (StateType (ContT * r m)) Source #

put :: StateType (ContT * r m) -> ContT * r m () Source #

(Monad m, Monoid w) => MonadState (RWST r w s m) Source # 

Associated Types

type StateType (RWST r w s m :: * -> *) :: * Source #

Methods

get :: RWST r w s m (StateType (RWST r w s m)) Source #

put :: StateType (RWST r w s m) -> RWST r w s m () Source #

(Monad m, Monoid w) => MonadState (RWST r w s m) Source # 

Associated Types

type StateType (RWST r w s m :: * -> *) :: * Source #

Methods

get :: RWST r w s m (StateType (RWST r w s m)) Source #

put :: StateType (RWST r w s m) -> 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.