-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monad classes, using functional dependencies -- -- Monad classes using functional dependencies, with instances for -- various monad transformers, inspired by the paper Functional -- Programming with Overloading and Higher-Order Polymorphism, by -- Mark P Jones, in Advanced School of Functional Programming, -- 1995 (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html). @package mtl @version 2.1.2 -- | The MonadWriter class. -- -- Inspired by the paper Functional Programming with Overloading and -- Higher-Order Polymorphism, Mark P Jones -- (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced -- School of Functional Programming, 1995. module Control.Monad.Writer.Class class (Monoid w, Monad m) => MonadWriter w m | m -> w where writer ~(a, w) = do { tell w; return a } tell w = writer ((), w) writer :: MonadWriter w m => (a, w) -> m a tell :: MonadWriter w m => w -> m () listen :: MonadWriter w m => m a -> m (a, w) pass :: MonadWriter w m => m (a, w -> w) -> m a -- | listens f m is an action that executes the action -- m and adds the result of applying f to the output to -- the value of the computation. -- -- listens :: MonadWriter w m => (w -> b) -> m a -> m (a, b) -- | censor f m is an action that executes the action -- m and applies the function f to its output, leaving -- the return value unchanged. -- -- censor :: MonadWriter w m => (w -> w) -> m a -> m a instance MonadWriter w m => MonadWriter w (StateT s m) instance MonadWriter w m => MonadWriter w (StateT s m) instance MonadWriter w m => MonadWriter w (ReaderT r m) instance MonadWriter w m => MonadWriter w (MaybeT m) instance MonadWriter w m => MonadWriter w (IdentityT m) instance (Error e, MonadWriter w m) => MonadWriter w (ErrorT e m) instance (Monoid w, Monad m) => MonadWriter w (RWST r w s m) instance (Monoid w, Monad m) => MonadWriter w (RWST r w s m) instance (Monoid w, Monad m) => MonadWriter w (WriterT w m) instance (Monoid w, Monad m) => MonadWriter w (WriterT w m) -- | 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. module Control.Monad.State.Class -- | Minimal definition is either both of get and put or -- just state class Monad m => MonadState s m | m -> s where get = state (\ s -> (s, s)) put s = state (\ _ -> ((), s)) state f = do { s <- get; let ~(a, s') = f s; put s'; return a } get :: MonadState s m => m s put :: MonadState s m => s -> m () state :: MonadState s m => (s -> (a, s)) -> m a -- | 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. modify :: MonadState s m => (s -> s) -> m () -- | Gets specific component of the state, using a projection function -- supplied. gets :: MonadState s m => (s -> a) -> m a instance (Monoid w, MonadState s m) => MonadState s (WriterT w m) instance (Monoid w, MonadState s m) => MonadState s (WriterT w m) instance MonadState s m => MonadState s (ReaderT r m) instance MonadState s m => MonadState s (MaybeT m) instance MonadState s m => MonadState s (ListT m) instance MonadState s m => MonadState s (IdentityT m) instance (Error e, MonadState s m) => MonadState s (ErrorT e m) instance MonadState s m => MonadState s (ContT r m) instance (Monad m, Monoid w) => MonadState s (RWST r w s m) instance (Monad m, Monoid w) => MonadState s (RWST r w s m) instance Monad m => MonadState s (StateT s m) instance Monad m => MonadState s (StateT s m) -- | -- -- The Reader monad (also called the Environment monad). -- Represents a computation, which can read values from a shared -- environment, pass values from function to function, and execute -- sub-computations in a modified environment. Using Reader -- monad for such computations is often clearer and easier than using the -- State monad. -- -- 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. module Control.Monad.Reader.Class -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r m | m -> r where reader f = do { r <- ask; return (f r) } ask :: MonadReader r m => m r local :: MonadReader r m => (r -> r) -> m a -> m a reader :: MonadReader r m => (r -> a) -> m a -- | Retrieves a function of the current environment. asks :: MonadReader r m => (r -> a) -> m a instance (Monoid w, MonadReader r m) => MonadReader r (WriterT w m) instance (Monoid w, MonadReader r m) => MonadReader r (WriterT w m) instance MonadReader r m => MonadReader r (StateT s m) instance MonadReader r m => MonadReader r (StateT s m) instance MonadReader r m => MonadReader r (MaybeT m) instance MonadReader r m => MonadReader r (ListT m) instance MonadReader r m => MonadReader r (IdentityT m) instance (Error e, MonadReader r m) => MonadReader r (ErrorT e m) instance MonadReader r' m => MonadReader r' (ContT r m) instance (Monad m, Monoid w) => MonadReader r (RWST r w s m) instance (Monad m, Monoid w) => MonadReader r (RWST r w s m) instance Monad m => MonadReader r (ReaderT r m) instance MonadReader r ((->) r) -- | Declaration of the MonadRWS class. -- -- 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. module Control.Monad.RWS.Class class (Monoid w, MonadReader r m, MonadWriter w m, MonadState s m) => MonadRWS r w s m | m -> r, m -> w, m -> s instance MonadRWS r w s m => MonadRWS r w s (MaybeT m) instance MonadRWS r w s m => MonadRWS r w s (IdentityT m) instance (Error e, MonadRWS r w s m) => MonadRWS r w s (ErrorT e m) instance (Monoid w, Monad m) => MonadRWS r w s (RWST r w s m) instance (Monoid w, Monad m) => MonadRWS r w s (RWST r w s m) -- | -- -- The Identity monad is a monad that does not embody any -- computational strategy. It simply applies the bound function to its -- input without any modification. Computationally, there is no reason to -- use the Identity monad instead of the much simpler act of -- simply applying functions to their arguments. The purpose of the -- Identity monad is its fundamental role in the theory of monad -- transformers. Any monad transformer applied to the Identity -- monad yields a non-transformer version of that monad. module Control.Monad.Identity -- | -- -- The Error monad (also called the Exception monad). module Control.Monad.Error.Class -- | An exception to be thrown. -- -- Minimal complete definition: noMsg or strMsg. class Error a noMsg :: Error a => a strMsg :: Error a => String -> a -- | The strategy of combining computations that can throw exceptions by -- bypassing bound functions from the point an exception is thrown to the -- point that it is handled. -- -- Is parameterized over the type of error information and the monad type -- constructor. It is common to use Either String as the -- monad type constructor for an error monad in which error descriptions -- take the form of strings. In that case and many other common cases the -- resulting monad is already defined as an instance of the -- MonadError class. You can also define your own error type -- and/or use a monad type constructor other than Either -- String or Either IOError. In -- these cases you will have to explicitly define instances of the -- Error and/or MonadError classes. class Monad m => MonadError e m | m -> e throwError :: MonadError e m => e -> m a catchError :: MonadError e m => m a -> (e -> m a) -> m a instance (Monoid w, MonadError e m) => MonadError e (WriterT w m) instance (Monoid w, MonadError e m) => MonadError e (WriterT w m) instance MonadError e m => MonadError e (StateT s m) instance MonadError e m => MonadError e (StateT s m) instance (Monoid w, MonadError e m) => MonadError e (RWST r w s m) instance (Monoid w, MonadError e m) => MonadError e (RWST r w s m) instance MonadError e m => MonadError e (ReaderT r m) instance MonadError e m => MonadError e (MaybeT m) instance MonadError e m => MonadError e (ListT m) instance MonadError e m => MonadError e (IdentityT m) instance (Monad m, Error e) => MonadError e (ErrorT e m) instance Error e => MonadError e (Either e) instance MonadError IOException IO -- | -- -- The Continuation monad represents computations in continuation-passing -- style (CPS). In continuation-passing style function result is not -- returned, but instead is passed to another function, received as a -- parameter (continuation). Computations are built up from sequences of -- nested continuations, terminated by a final continuation (often -- id) which produces the final result. Since continuations are -- functions which represent the future of a computation, manipulation of -- the continuation functions can achieve complex manipulations of the -- future of the computation, such as interrupting a computation in the -- middle, aborting a portion of a computation, restarting a computation, -- and interleaving execution of computations. The Continuation monad -- adapts CPS to the structure of a monad. -- -- Before using the Continuation monad, be sure that you have a firm -- understanding of continuation-passing style and that continuations -- represent the best solution to your particular design problem. Many -- algorithms which require continuations in other languages do not -- require them in Haskell, due to Haskell's lazy semantics. Abuse of the -- Continuation monad can produce code that is impossible to understand -- and maintain. module Control.Monad.Cont.Class class Monad m => MonadCont m callCC :: MonadCont m => ((a -> m b) -> m a) -> m a instance (Monoid w, MonadCont m) => MonadCont (WriterT w m) instance (Monoid w, MonadCont m) => MonadCont (WriterT w m) instance MonadCont m => MonadCont (StateT s m) instance MonadCont m => MonadCont (StateT s m) instance (Monoid w, MonadCont m) => MonadCont (RWST r w s m) instance (Monoid w, MonadCont m) => MonadCont (RWST r w s m) instance MonadCont m => MonadCont (ReaderT r m) instance MonadCont m => MonadCont (MaybeT m) instance MonadCont m => MonadCont (ListT m) instance MonadCont m => MonadCont (IdentityT m) instance (Error e, MonadCont m) => MonadCont (ErrorT e m) instance MonadCont (ContT r m) -- | Classes for monad transformers. -- -- A monad transformer makes new monad out of an existing monad, such -- that computations of the old monad may be embedded in the new one. To -- construct a monad with a desired set of features, one typically starts -- with a base monad, such as Identity, [] or -- IO, and applies a sequence of monad transformers. -- -- Most monad transformer modules include the special case of applying -- the transformer to Identity. For example, State s is -- an abbreviation for StateT s Identity. -- -- Each monad transformer also comes with an operation -- runXXX to unwrap the transformer, exposing a -- computation of the inner monad. module Control.Monad.Trans -- | -- -- The Error monad (also called the Exception monad). module Control.Monad.Error -- | The strategy of combining computations that can throw exceptions by -- bypassing bound functions from the point an exception is thrown to the -- point that it is handled. -- -- Is parameterized over the type of error information and the monad type -- constructor. It is common to use Either String as the -- monad type constructor for an error monad in which error descriptions -- take the form of strings. In that case and many other common cases the -- resulting monad is already defined as an instance of the -- MonadError class. You can also define your own error type -- and/or use a monad type constructor other than Either -- String or Either IOError. In -- these cases you will have to explicitly define instances of the -- Error and/or MonadError classes. class Monad m => MonadError e m | m -> e throwError :: MonadError e m => e -> m a catchError :: MonadError e m => m a -> (e -> m a) -> m a -- | An exception to be thrown. -- -- Minimal complete definition: noMsg or strMsg. class Error a noMsg :: Error a => a strMsg :: Error a => String -> a -- | The error monad transformer. It can be used to add error handling to -- other monads. -- -- The ErrorT Monad structure is parameterized over two things: -- -- -- -- The return function yields a successful computation, while -- >>= sequences two subcomputations, failing on the first -- error. newtype ErrorT e (m :: * -> *) a :: * -> (* -> *) -> * -> * ErrorT :: m (Either e a) -> ErrorT e a runErrorT :: ErrorT e a -> m (Either e a) -- | Map the unwrapped computation using the given function. -- -- mapErrorT :: (m (Either e a) -> n (Either e' b)) -> ErrorT e m a -> ErrorT e' n b -- | The List monad. module Control.Monad.List -- | Parameterizable list monad, with an inner monad. -- -- Note: this does not yield a monad unless the argument monad is -- commutative. newtype ListT (m :: * -> *) a :: (* -> *) -> * -> * ListT :: m [a] -> ListT a runListT :: ListT a -> m [a] -- | Map between ListT computations. -- -- mapListT :: (m [a] -> n [b]) -> ListT m a -> ListT n b -- | Lazy RWS monad. -- -- 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. module Control.Monad.RWS.Lazy -- | A monad containing an environment of type r, output of type -- w and an updatable state of type s. type RWS r w s = RWST r w s Identity -- | Construct an RWS computation from a function. (The inverse of -- runRWS.) rws :: (r -> s -> (a, s, w)) -> RWS r w s a -- | Unwrap an RWS computation as a function. (The inverse of rws.) runRWS :: RWS r w s a -> r -> s -> (a, s, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final value and output, discarding the final state. evalRWS :: RWS r w s a -> r -> s -> (a, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final state and output, discarding the final value. execRWS :: RWS r w s a -> r -> s -> (s, w) -- | Map the return value, final state and output of a computation using -- the given function. -- -- mapRWS :: ((a, s, w) -> (b, s, w')) -> RWS r w s a -> RWS r w' s b -- | withRWS f m executes action m with an initial -- environment and state modified by applying f. -- -- withRWS :: (r' -> s -> (r, s)) -> RWS r w s a -> RWS r' w s a -- | A monad transformer adding reading an environment of type r, -- collecting an output of type w and updating a state of type -- s to an inner monad m. newtype RWST r w s (m :: * -> *) a :: * -> * -> * -> (* -> *) -> * -> * RWST :: (r -> s -> m (a, s, w)) -> RWST r w s a runRWST :: RWST r w s a -> r -> s -> m (a, s, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final value and output, discarding the final state. evalRWST :: Monad m => RWST r w s m a -> r -> s -> m (a, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final state and output, discarding the final value. execRWST :: Monad m => RWST r w s m a -> r -> s -> m (s, w) -- | Map the inner computation using the given function. -- -- mapRWST :: (m (a, s, w) -> n (b, s, w')) -> RWST r w s m a -> RWST r w' s n b -- | withRWST f m executes action m with an -- initial environment and state modified by applying f. -- -- withRWST :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a -- | Declaration of the MonadRWS class. -- -- 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. module Control.Monad.RWS -- | -- -- The Reader monad (also called the Environment monad). -- Represents a computation, which can read values from a shared -- environment, pass values from function to function, and execute -- sub-computations in a modified environment. Using Reader monad -- for such computations is often clearer and easier than using the -- State monad. -- -- 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. module Control.Monad.Reader -- | See examples in Control.Monad.Reader. Note, the partially -- applied function type (->) r is a simple reader monad. See -- the instance declaration below. class Monad m => MonadReader r m | m -> r where reader f = do { r <- ask; return (f r) } ask :: MonadReader r m => m r local :: MonadReader r m => (r -> r) -> m a -> m a reader :: MonadReader r m => (r -> a) -> m a -- | Retrieves a function of the current environment. asks :: MonadReader r m => (r -> a) -> m a -- | The parameterizable reader monad. -- -- Computations are functions of a shared environment. -- -- The return function ignores the environment, while -- >>= passes the inherited environment to both -- subcomputations. type Reader r = ReaderT r Identity -- | Runs a Reader and extracts the final value from it. (The -- inverse of reader.) runReader :: Reader r a -> r -> a -- | Transform the value returned by a Reader. -- -- mapReader :: (a -> b) -> Reader r a -> Reader r b -- | Execute a computation in a modified environment (a specialization of -- withReaderT). -- -- withReader :: (r' -> r) -> Reader r a -> Reader r' a -- | The reader monad transformer, which adds a read-only environment to -- the given monad. -- -- The return function ignores the environment, while -- >>= passes the inherited environment to both -- subcomputations. newtype ReaderT r (m :: * -> *) a :: * -> (* -> *) -> * -> * ReaderT :: (r -> m a) -> ReaderT r a -- | The underlying computation, as a function of the environment. runReaderT :: ReaderT r a -> r -> m a -- | Transform the computation inside a ReaderT. -- -- mapReaderT :: (m a -> n b) -> ReaderT r m a -> ReaderT r n b -- | Execute a computation in a modified environment (a more general -- version of local). -- -- withReaderT :: (r' -> r) -> ReaderT r m a -> ReaderT r' m a -- | Strict RWS monad. -- -- 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. module Control.Monad.RWS.Strict -- | A monad containing an environment of type r, output of type -- w and an updatable state of type s. type RWS r w s = RWST r w s Identity -- | Construct an RWS computation from a function. (The inverse of -- runRWS.) rws :: (r -> s -> (a, s, w)) -> RWS r w s a -- | Unwrap an RWS computation as a function. (The inverse of rws.) runRWS :: RWS r w s a -> r -> s -> (a, s, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final value and output, discarding the final state. evalRWS :: RWS r w s a -> r -> s -> (a, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final state and output, discarding the final value. execRWS :: RWS r w s a -> r -> s -> (s, w) -- | Map the return value, final state and output of a computation using -- the given function. -- -- mapRWS :: ((a, s, w) -> (b, s, w')) -> RWS r w s a -> RWS r w' s b -- | withRWS f m executes action m with an initial -- environment and state modified by applying f. -- -- withRWS :: (r' -> s -> (r, s)) -> RWS r w s a -> RWS r' w s a -- | A monad transformer adding reading an environment of type r, -- collecting an output of type w and updating a state of type -- s to an inner monad m. newtype RWST r w s (m :: * -> *) a :: * -> * -> * -> (* -> *) -> * -> * RWST :: (r -> s -> m (a, s, w)) -> RWST r w s a runRWST :: RWST r w s a -> r -> s -> m (a, s, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final value and output, discarding the final state. evalRWST :: Monad m => RWST r w s m a -> r -> s -> m (a, w) -- | Evaluate a computation with the given initial state and environment, -- returning the final state and output, discarding the final value. execRWST :: Monad m => RWST r w s m a -> r -> s -> m (s, w) -- | Map the inner computation using the given function. -- -- mapRWST :: (m (a, s, w) -> n (b, s, w')) -> RWST r w s m a -> RWST r w' s n b -- | withRWST f m executes action m with an -- initial environment and state modified by applying f. -- -- withRWST :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a -- | Lazy 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. module Control.Monad.State.Lazy -- | Minimal definition is either both of get and put or -- just state class Monad m => MonadState s m | m -> s where get = state (\ s -> (s, s)) put s = state (\ _ -> ((), s)) state f = do { s <- get; let ~(a, s') = f s; put s'; return a } get :: MonadState s m => m s put :: MonadState s m => s -> m () state :: MonadState s m => (s -> (a, s)) -> m a -- | 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. modify :: MonadState s m => (s -> s) -> m () -- | Gets specific component of the state, using a projection function -- supplied. gets :: MonadState s m => (s -> a) -> m a -- | 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. type State s = StateT s Identity -- | Unwrap a state monad computation as a function. (The inverse of -- state.) runState :: State s a -> s -> (a, s) -- | Evaluate a state computation with the given initial state and return -- the final value, discarding the final state. -- -- evalState :: State s a -> s -> a -- | Evaluate a state computation with the given initial state and return -- the final state, discarding the final value. -- -- execState :: State s a -> s -> s -- | Map both the return value and final state of a computation using the -- given function. -- -- mapState :: ((a, s) -> (b, s)) -> State s a -> State s b -- | withState f m executes action m on a state -- modified by applying f. -- -- withState :: (s -> s) -> State s a -> State s a -- | A state transformer monad parameterized by: -- -- -- -- The return function leaves the state unchanged, while -- >>= uses the final state of the first computation as -- the initial state of the second. newtype StateT s (m :: * -> *) a :: * -> (* -> *) -> * -> * StateT :: (s -> m (a, s)) -> StateT s a runStateT :: StateT s a -> s -> m (a, s) -- | Evaluate a state computation with the given initial state and return -- the final value, discarding the final state. -- -- evalStateT :: Monad m => StateT s m a -> s -> m a -- | Evaluate a state computation with the given initial state and return -- the final state, discarding the final value. -- -- execStateT :: Monad m => StateT s m a -> s -> m s -- | Map both the return value and final state of a computation using the -- given function. -- -- mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b -- | withStateT f m executes action m on a state -- modified by applying f. -- -- withStateT :: (s -> s) -> StateT s m a -> StateT s m a -- | 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. module Control.Monad.State -- | 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. module Control.Monad.State.Strict -- | Minimal definition is either both of get and put or -- just state class Monad m => MonadState s m | m -> s where get = state (\ s -> (s, s)) put s = state (\ _ -> ((), s)) state f = do { s <- get; let ~(a, s') = f s; put s'; return a } get :: MonadState s m => m s put :: MonadState s m => s -> m () state :: MonadState s m => (s -> (a, s)) -> m a -- | 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. modify :: MonadState s m => (s -> s) -> m () -- | Gets specific component of the state, using a projection function -- supplied. gets :: MonadState s m => (s -> a) -> m a -- | 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. type State s = StateT s Identity -- | Unwrap a state monad computation as a function. (The inverse of -- state.) runState :: State s a -> s -> (a, s) -- | Evaluate a state computation with the given initial state and return -- the final value, discarding the final state. -- -- evalState :: State s a -> s -> a -- | Evaluate a state computation with the given initial state and return -- the final state, discarding the final value. -- -- execState :: State s a -> s -> s -- | Map both the return value and final state of a computation using the -- given function. -- -- mapState :: ((a, s) -> (b, s)) -> State s a -> State s b -- | withState f m executes action m on a state -- modified by applying f. -- -- withState :: (s -> s) -> State s a -> State s a -- | A state transformer monad parameterized by: -- -- -- -- The return function leaves the state unchanged, while -- >>= uses the final state of the first computation as -- the initial state of the second. newtype StateT s (m :: * -> *) a :: * -> (* -> *) -> * -> * StateT :: (s -> m (a, s)) -> StateT s a runStateT :: StateT s a -> s -> m (a, s) -- | Evaluate a state computation with the given initial state and return -- the final value, discarding the final state. -- -- evalStateT :: Monad m => StateT s m a -> s -> m a -- | Evaluate a state computation with the given initial state and return -- the final state, discarding the final value. -- -- execStateT :: Monad m => StateT s m a -> s -> m s -- | Map both the return value and final state of a computation using the -- given function. -- -- mapStateT :: (m (a, s) -> n (b, s)) -> StateT s m a -> StateT s n b -- | withStateT f m executes action m on a state -- modified by applying f. -- -- withStateT :: (s -> s) -> StateT s m a -> StateT s m a -- | Lazy writer monads. -- -- Inspired by the paper Functional Programming with Overloading and -- Higher-Order Polymorphism, Mark P Jones -- (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced -- School of Functional Programming, 1995. module Control.Monad.Writer.Lazy class (Monoid w, Monad m) => MonadWriter w m | m -> w where writer ~(a, w) = do { tell w; return a } tell w = writer ((), w) writer :: MonadWriter w m => (a, w) -> m a tell :: MonadWriter w m => w -> m () listen :: MonadWriter w m => m a -> m (a, w) pass :: MonadWriter w m => m (a, w -> w) -> m a -- | listens f m is an action that executes the action -- m and adds the result of applying f to the output to -- the value of the computation. -- -- listens :: MonadWriter w m => (w -> b) -> m a -> m (a, b) -- | censor f m is an action that executes the action -- m and applies the function f to its output, leaving -- the return value unchanged. -- -- censor :: MonadWriter w m => (w -> w) -> m a -> m a -- | A writer monad parameterized by the type w of output to -- accumulate. -- -- The return function produces the output mempty, while -- >>= combines the outputs of the subcomputations using -- mappend. type Writer w = WriterT w Identity -- | Unwrap a writer computation as a (result, output) pair. (The inverse -- of writer.) runWriter :: Writer w a -> (a, w) -- | Extract the output from a writer computation. -- -- execWriter :: Writer w a -> w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriter :: ((a, w) -> (b, w')) -> Writer w a -> Writer w' b -- | A writer monad parameterized by: -- -- -- -- The return function produces the output mempty, while -- >>= combines the outputs of the subcomputations using -- mappend. newtype WriterT w (m :: * -> *) a :: * -> (* -> *) -> * -> * WriterT :: m (a, w) -> WriterT w a runWriterT :: WriterT w a -> m (a, w) -- | Extract the output from a writer computation. -- -- execWriterT :: Monad m => WriterT w m a -> m w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriterT :: (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b -- | The MonadWriter class. -- -- Inspired by the paper Functional Programming with Overloading and -- Higher-Order Polymorphism, Mark P Jones -- (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced -- School of Functional Programming, 1995. module Control.Monad.Writer -- | Strict writer monads. -- -- Inspired by the paper Functional Programming with Overloading and -- Higher-Order Polymorphism, Mark P Jones -- (http://web.cecs.pdx.edu/~mpj/pubs/springschool.html) Advanced -- School of Functional Programming, 1995. module Control.Monad.Writer.Strict class (Monoid w, Monad m) => MonadWriter w m | m -> w where writer ~(a, w) = do { tell w; return a } tell w = writer ((), w) writer :: MonadWriter w m => (a, w) -> m a tell :: MonadWriter w m => w -> m () listen :: MonadWriter w m => m a -> m (a, w) pass :: MonadWriter w m => m (a, w -> w) -> m a -- | listens f m is an action that executes the action -- m and adds the result of applying f to the output to -- the value of the computation. -- -- listens :: MonadWriter w m => (w -> b) -> m a -> m (a, b) -- | censor f m is an action that executes the action -- m and applies the function f to its output, leaving -- the return value unchanged. -- -- censor :: MonadWriter w m => (w -> w) -> m a -> m a -- | A writer monad parameterized by the type w of output to -- accumulate. -- -- The return function produces the output mempty, while -- >>= combines the outputs of the subcomputations using -- mappend. type Writer w = WriterT w Identity -- | Unwrap a writer computation as a (result, output) pair. (The inverse -- of writer.) runWriter :: Writer w a -> (a, w) -- | Extract the output from a writer computation. -- -- execWriter :: Writer w a -> w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriter :: ((a, w) -> (b, w')) -> Writer w a -> Writer w' b -- | A writer monad parameterized by: -- -- -- -- The return function produces the output mempty, while -- >>= combines the outputs of the subcomputations using -- mappend. newtype WriterT w (m :: * -> *) a :: * -> (* -> *) -> * -> * WriterT :: m (a, w) -> WriterT w a runWriterT :: WriterT w a -> m (a, w) -- | Extract the output from a writer computation. -- -- execWriterT :: Monad m => WriterT w m a -> m w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriterT :: (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b -- | -- -- The Continuation monad represents computations in continuation-passing -- style (CPS). In continuation-passing style function result is not -- returned, but instead is passed to another function, received as a -- parameter (continuation). Computations are built up from sequences of -- nested continuations, terminated by a final continuation (often -- id) which produces the final result. Since continuations are -- functions which represent the future of a computation, manipulation of -- the continuation functions can achieve complex manipulations of the -- future of the computation, such as interrupting a computation in the -- middle, aborting a portion of a computation, restarting a computation, -- and interleaving execution of computations. The Continuation monad -- adapts CPS to the structure of a monad. -- -- Before using the Continuation monad, be sure that you have a firm -- understanding of continuation-passing style and that continuations -- represent the best solution to your particular design problem. Many -- algorithms which require continuations in other languages do not -- require them in Haskell, due to Haskell's lazy semantics. Abuse of the -- Continuation monad can produce code that is impossible to understand -- and maintain. module Control.Monad.Cont class Monad m => MonadCont m callCC :: MonadCont m => ((a -> m b) -> m a) -> m a -- | Continuation monad. Cont r a is a CPS computation that -- produces an intermediate result of type a within a CPS -- computation whose final result type is r. -- -- The return function simply creates a continuation which -- passes the value on. -- -- The >>= operator adds the bound function into the -- continuation chain. type Cont r = ContT r Identity -- | Construct a continuation-passing computation from a function. (The -- inverse of runCont.) cont :: ((a -> r) -> r) -> Cont r a -- | Runs a CPS computation, returns its result after applying the final -- continuation to it. (The inverse of cont.) runCont :: Cont r a -> (a -> r) -> r -- | Apply a function to transform the result of a continuation-passing -- computation. -- -- mapCont :: (r -> r) -> Cont r a -> Cont r a -- | Apply a function to transform the continuation passed to a CPS -- computation. -- -- withCont :: ((b -> r) -> a -> r) -> Cont r a -> Cont r b -- | The continuation monad transformer. Can be used to add continuation -- handling to other monads. newtype ContT r (m :: * -> *) a :: * -> (* -> *) -> * -> * ContT :: ((a -> m r) -> m r) -> ContT r a runContT :: ContT r a -> (a -> m r) -> m r -- | Apply a function to transform the result of a continuation-passing -- computation. -- -- mapContT :: (m r -> m r) -> ContT r m a -> ContT r m a -- | Apply a function to transform the continuation passed to a CPS -- computation. -- -- withContT :: ((b -> m r) -> a -> m r) -> ContT r m a -> ContT r m b