-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monad classes for transformers, using functional dependencies -- -- MTL is a collection of monad classes, extending the -- transformers package, using functional dependencies for generic -- lifting of monadic actions. @package mtl @version 2.3.1 -- | -- --

A note on commutativity

-- -- Some effects are commutative: it doesn't matter which you -- resolve first, as all possible orderings of commutative effects are -- isomorphic. Consider, for example, the reader and state effects, as -- exemplified by ReaderT and StateT respectively. If we -- have ReaderT r (State s) a, this is effectively -- r -> State s a ~ r -> s -> (a, s); if we -- instead have StateT s (Reader r) a, this is -- effectively s -> Reader r (a, s) ~ s -> r -> (a, -- s). Since we can always reorder function arguments (for example, -- using flip, as in this case) without changing the result, these -- are isomorphic, showing that reader and state are commutative, -- or, more precisely, commute with each other. -- -- However, this isn't generally the case. Consider instead the error and -- state effects, as exemplified by MaybeT and StateT -- respectively. If we have MaybeT (State s) a, -- this is effectively State s (Maybe a) ~ s -> -- (Maybe a, s): put simply, the error can occur only in the -- result, but not the state, which always 'survives'. On the -- other hand, if we have StateT s Maybe a, this -- is instead s -> Maybe (a, s): here, if we error, we -- lose both the state and the result! Thus, error and state -- effects do not commute with each other. -- -- As the MTL is capability-based, we support any ordering of -- non-commutative effects on an equal footing. Indeed, if you wish to -- use MonadState, for example, whether your final monadic stack -- ends up being MaybeT (State s) a, -- StateT s Maybe a, or anything else, you will be -- able to write your desired code without having to consider such -- differences. However, the way we implement these capabilities -- for any given transformer (or rather, any given transformed stack) -- is affected by this ordering unless the effects in question are -- commutative. -- -- We note in this module which effects the accumulation effect does and -- doesn't commute with; we also note on implementations with -- non-commutative transformers what the outcome will be. Note that, -- depending on how the 'inner monad' is structured, this may be more -- complex than we note: we describe only what impact the 'outer effect' -- has, not what else might be in the stack. -- --

Commutativity of accumulation

-- -- The accumulation effect commutes with the identity effect -- (IdentityT), reader, writer or state effects (ReaderT, -- WriterT, StateT and any combination, including -- RWST for example) and with itself. It does not commute -- with anything else. module Control.Monad.Accum -- | The capability to accumulate. This can be seen in one of two ways: -- -- -- --

Laws

-- -- accum should obey the following: -- --
    --
  1. accum (const (x, mempty)) = -- pure x
  2. --
  3. accum f *> accum g = -- accum $ acc -> let (_, v) = f acc (res, w) = g -- (acc <> v) in (res, v <> w)
  4. --
-- -- If you choose to define look and add instead, their -- definitions must obey the following: -- --
    --
  1. look *> look = -- look
  2. --
  3. add mempty = pure -- ()
  4. --
  5. add x *> add y = -- add (x <> y)
  6. --
  7. add x *> look = -- look >>= w -> add x $> w -- <> x
  8. --
-- -- If you want to define both, the relationship between them is as -- follows. These are also the default definitions. -- --
    --
  1. look = accum $ acc -- -> (acc, mempty)
  2. --
  3. add x = accum $ acc -- -> ((), x)
  4. --
  5. accum f = look >>= acc -- -> let (res, v) = f acc in add v $> res
  6. --
class (Monoid w, Monad m) => MonadAccum w m | m -> w -- | Retrieve the accumulated result so far. look :: MonadAccum w m => m w -- | Append a value to the result. add :: MonadAccum w m => w -> m () -- | Embed a simple accumulation action into the monad. accum :: MonadAccum w m => (w -> (a, w)) -> m a -- | A helper type to decrease boilerplate when defining new transformer -- instances of MonadAccum. -- -- Most of the instances in this module are derived using this method; -- for example, our instance of ExceptT is derived as follows: -- --
--   deriving via (LiftingAccum (ExceptT e) m) instance (MonadAccum w m) =>
--    MonadAccum w (ExceptT e m)
--   
newtype LiftingAccum (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) LiftingAccum :: t m a -> LiftingAccum (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) -- | Retrieve a function of the accumulated value. looks :: forall (a :: Type) (m :: Type -> Type) (w :: Type). MonadAccum w m => (w -> a) -> m a instance GHC.Base.Monad (t m) => GHC.Base.Monad (Control.Monad.Accum.LiftingAccum t m) instance GHC.Base.Applicative (t m) => GHC.Base.Applicative (Control.Monad.Accum.LiftingAccum t m) instance GHC.Base.Functor (t m) => GHC.Base.Functor (Control.Monad.Accum.LiftingAccum t m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Cont.ContT r m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Accum.MonadAccum w' m => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (Control.Monad.Accum.MonadAccum w' m, GHC.Base.Monoid w) => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (Control.Monad.Accum.MonadAccum w' m, GHC.Base.Monoid w) => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Reader.ReaderT r m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Select.SelectT r m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Accum.MonadAccum w m => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.State.Strict.StateT s m) instance Control.Monad.Accum.MonadAccum w' m => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (Control.Monad.Accum.MonadAccum w' m, GHC.Base.Monoid w) => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (Control.Monad.Accum.MonadAccum w' m, GHC.Base.Monoid w) => Control.Monad.Accum.MonadAccum w' (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (Control.Monad.Trans.Class.MonadTrans t, GHC.Base.Monad (t m), Control.Monad.Accum.MonadAccum w m) => Control.Monad.Accum.MonadAccum w (Control.Monad.Accum.LiftingAccum t m) instance GHC.Base.Monoid w => Control.Monad.Accum.MonadAccum w (Control.Monad.Trans.Accum.AccumT w Data.Functor.Identity.Identity) -- | -- -- 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 :: Type -> Type) -- | callCC (call-with-current-continuation) calls a function with -- the current continuation as its argument. Provides an escape -- continuation mechanism for use with Continuation monads. Escape -- continuations allow to abort the current computation and return a -- value immediately. They achieve a similar effect to throwError -- and catchError within an Except monad. Advantage of this -- function over calling return is that it makes the -- continuation explicit, allowing more flexibility and better control -- (see examples in Control.Monad.Cont). -- -- The standard idiom used with callCC is to provide a -- lambda-expression to name the continuation. Then calling the named -- continuation anywhere within its scope will escape from the -- computation, even if it is many layers deep within nested -- computations. callCC :: MonadCont m => ((a -> m b) -> m a) -> m a -- | Introduces a recursive binding to the continuation. Due to the use of -- callCC, calling the continuation will interrupt execution of -- the current block creating an effect similar to goto/setjmp in C. label :: MonadCont m => a -> m (a -> m b, a) -- | Simplified version of label without arguments. label_ :: MonadCont m => m (m a) -- | Lift a callCC-style function through any MonadTrans. -- --

Note

-- -- For any function f, 'liftCallCC f' satisfies the -- uniformity condition provided that f is -- quasi-algebraic. More specifically, for any g, we must have: -- --
--   'join' '$' f (\exit -> 'pure' '$' g (exit '.' 'pure') = f g
--   
-- -- callCC is quasi-algebraic; furthermore, for any quasi-algebraic -- f, liftCallCC f is also quasi-algebraic. -- --

See also

-- -- liftCallCC :: forall (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) (b :: Type). (MonadTrans t, Monad m, forall (m' :: Type -> Type). Monad m' => Monad (t m')) => CallCC m (t m a) b -> CallCC (t m) a b instance forall k (r :: k) (m :: k -> *). Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Cont.ContT r m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Reader.ReaderT r m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Cont.Class.MonadCont m => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.State.Strict.StateT s m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Cont.Class.MonadCont m) => Control.Monad.Cont.Class.MonadCont (Control.Monad.Trans.Accum.AccumT w m) -- | -- -- 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 :: Type -> Type) -- | callCC (call-with-current-continuation) calls a function with -- the current continuation as its argument. Provides an escape -- continuation mechanism for use with Continuation monads. Escape -- continuations allow to abort the current computation and return a -- value immediately. They achieve a similar effect to throwError -- and catchError within an Except monad. Advantage of this -- function over calling return is that it makes the -- continuation explicit, allowing more flexibility and better control -- (see examples in Control.Monad.Cont). -- -- The standard idiom used with callCC is to provide a -- lambda-expression to name the continuation. Then calling the named -- continuation anywhere within its scope will escape from the -- computation, even if it is many layers deep within nested -- computations. callCC :: MonadCont m => ((a -> m b) -> m a) -> m a -- | Introduces a recursive binding to the continuation. Due to the use of -- callCC, calling the continuation will interrupt execution of -- the current block creating an effect similar to goto/setjmp in C. label :: MonadCont m => a -> m (a -> m b, a) -- | Simplified version of label without arguments. label_ :: MonadCont m => m (m a) -- | Continuation monad. Cont r a is a CPS ("continuation-passing -- style") 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 -- | The result of running a CPS computation with a given final -- continuation. (The inverse of cont) runCont :: Cont r a -> (a -> r) -> r -- | The result of running a CPS computation with the identity as the final -- continuation. -- -- evalCont :: Cont r 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 any type constructor: the Monad instance and most -- of the operations do not require m to be a monad. -- -- ContT is not a functor on the category of monads, and many -- operations cannot be lifted through it. newtype ContT (r :: k) (m :: k -> Type) a ContT :: ((a -> m r) -> m r) -> ContT (r :: k) (m :: k -> Type) a runContT :: ContT r m a -> (a -> m r) -> m r -- | The result of running a CPS computation with return as the -- final continuation. -- -- evalContT :: Monad m => ContT r m r -> m r -- | Apply a function to transform the result of a continuation-passing -- computation. This has a more restricted type than the map -- operations for other monad transformers, because ContT does not -- define a functor in the category of monads. -- -- mapContT :: forall {k} m (r :: k) a. (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 :: forall {k} b m (r :: k) a. ((b -> m r) -> a -> m r) -> ContT r m a -> ContT r m b -- | -- -- The Error monad (also called the Exception monad). module Control.Monad.Error.Class -- | 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 -- MonadError class. (If you are using the deprecated -- Control.Monad.Error or Control.Monad.Trans.Error, you -- may also have to define an Error instance.) class (Monad m) => MonadError e m | m -> e -- | Is used within a monadic computation to begin exception processing. throwError :: MonadError e m => e -> m a -- | A handler function to handle previous errors and return to normal -- execution. A common idiom is: -- --
--   do { action1; action2; action3 } `catchError` handler
--   
-- -- where the action functions can call throwError. Note -- that handler and the do-block must have the same return type. catchError :: MonadError e m => m a -> (e -> m a) -> m a -- | Lifts an Either e into any MonadError -- e. -- --
--   do { val <- liftEither =<< action1; action2 }
--   
-- -- where action1 returns an Either to represent errors. liftEither :: MonadError e m => Either e a -> m a -- | MonadError analogue to the try function. tryError :: MonadError e m => m a -> m (Either e a) -- | MonadError analogue to the withExceptT function. -- Modify the value (but not the type) of an error. The type is fixed -- because of the functional dependency m -> e. If you need -- to change the type of e use mapError or -- modifyError. withError :: MonadError e m => (e -> e) -> m a -> m a -- | As handle is flipped catch, handleError is -- flipped catchError. handleError :: MonadError e m => (e -> m a) -> m a -> m a -- | MonadError analogue of the mapExceptT function. The -- computation is unwrapped, a function is applied to the -- Either, and the result is lifted into the second -- MonadError instance. mapError :: (MonadError e m, MonadError e' n) => (m (Either e a) -> n (Either e' b)) -> m a -> n b -- | A different MonadError analogue to the withExceptT -- function. Modify the value (and possibly the type) of an error in an -- ExceptT-transformed monad, while stripping the -- ExceptT layer. -- -- This is useful for adapting the MonadError constraint of a -- computation. -- -- For example: -- --
--   data DatabaseError = ...
--   
--   performDatabaseQuery :: (MonadError DatabaseError m, ...) => m PersistedValue
--   
--   data AppError
--     = MkDatabaseError DatabaseError
--     | ...
--   
--   app :: (MonadError AppError m, ...) => m ()
--   
-- -- Given these types, performDatabaseQuery cannot be used -- directly inside app, because the error types don't match. -- Using modifyError, an equivalent function with a different -- error type can be constructed: -- --
--   performDatabaseQuery' :: (MonadError AppError m, ...) => m PersistedValue
--   performDatabaseQuery' = modifyError MkDatabaseError performDatabaseQuery
--   
-- -- Since the error types do match, performDatabaseQuery' _can_ -- be used in app, assuming all other constraints carry over. -- -- This works by instantiating the m in the type of -- performDatabaseQuery to ExceptT DatabaseError m', -- which satisfies the MonadError DatabaseError constraint. -- Immediately, the ExceptT DatabaseError layer is unwrapped, -- producing Either a DatabaseError or a -- PersistedValue. If it's the former, the error is wrapped in -- MkDatabaseError and re-thrown in the inner monad, otherwise -- the result value is returned. modifyError :: MonadError e' m => (e -> e') -> ExceptT e m a -> m a instance Control.Monad.Error.Class.MonadError GHC.IO.Exception.IOException GHC.Types.IO instance Control.Monad.Error.Class.MonadError () GHC.Maybe.Maybe instance Control.Monad.Error.Class.MonadError e (Data.Either.Either e) instance GHC.Base.Monad m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Error.Class.MonadError e m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Error.Class.MonadError e m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Error.Class.MonadError e m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Reader.ReaderT r m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Error.Class.MonadError e m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Error.Class.MonadError e m => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.State.Strict.StateT s m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Error.Class.MonadError e m) => Control.Monad.Error.Class.MonadError e (Control.Monad.Trans.Accum.AccumT w m) -- | -- -- The Error monad (also called the Exception monad). module Control.Monad.Except -- | 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 -- MonadError class. (If you are using the deprecated -- Control.Monad.Error or Control.Monad.Trans.Error, you -- may also have to define an Error instance.) class (Monad m) => MonadError e m | m -> e -- | Is used within a monadic computation to begin exception processing. throwError :: MonadError e m => e -> m a -- | A handler function to handle previous errors and return to normal -- execution. A common idiom is: -- --
--   do { action1; action2; action3 } `catchError` handler
--   
-- -- where the action functions can call throwError. Note -- that handler and the do-block must have the same return type. catchError :: MonadError e m => m a -> (e -> m a) -> m a -- | Lifts an Either e into any MonadError -- e. -- --
--   do { val <- liftEither =<< action1; action2 }
--   
-- -- where action1 returns an Either to represent errors. liftEither :: MonadError e m => Either e a -> m a -- | MonadError analogue to the try function. tryError :: MonadError e m => m a -> m (Either e a) -- | MonadError analogue to the withExceptT function. -- Modify the value (but not the type) of an error. The type is fixed -- because of the functional dependency m -> e. If you need -- to change the type of e use mapError or -- modifyError. withError :: MonadError e m => (e -> e) -> m a -> m a -- | As handle is flipped catch, handleError is -- flipped catchError. handleError :: MonadError e m => (e -> m a) -> m a -> m a -- | MonadError analogue of the mapExceptT function. The -- computation is unwrapped, a function is applied to the -- Either, and the result is lifted into the second -- MonadError instance. mapError :: (MonadError e m, MonadError e' n) => (m (Either e a) -> n (Either e' b)) -> m a -> n b -- | A different MonadError analogue to the withExceptT -- function. Modify the value (and possibly the type) of an error in an -- ExceptT-transformed monad, while stripping the -- ExceptT layer. -- -- This is useful for adapting the MonadError constraint of a -- computation. -- -- For example: -- --
--   data DatabaseError = ...
--   
--   performDatabaseQuery :: (MonadError DatabaseError m, ...) => m PersistedValue
--   
--   data AppError
--     = MkDatabaseError DatabaseError
--     | ...
--   
--   app :: (MonadError AppError m, ...) => m ()
--   
-- -- Given these types, performDatabaseQuery cannot be used -- directly inside app, because the error types don't match. -- Using modifyError, an equivalent function with a different -- error type can be constructed: -- --
--   performDatabaseQuery' :: (MonadError AppError m, ...) => m PersistedValue
--   performDatabaseQuery' = modifyError MkDatabaseError performDatabaseQuery
--   
-- -- Since the error types do match, performDatabaseQuery' _can_ -- be used in app, assuming all other constraints carry over. -- -- This works by instantiating the m in the type of -- performDatabaseQuery to ExceptT DatabaseError m', -- which satisfies the MonadError DatabaseError constraint. -- Immediately, the ExceptT DatabaseError layer is unwrapped, -- producing Either a DatabaseError or a -- PersistedValue. If it's the former, the error is wrapped in -- MkDatabaseError and re-thrown in the inner monad, otherwise -- the result value is returned. modifyError :: MonadError e' m => (e -> e') -> ExceptT e m a -> m a -- | A monad transformer that adds exceptions to other monads. -- -- ExceptT constructs a monad parameterized over two things: -- -- -- -- The return function yields a computation that produces the -- given value, while >>= sequences two subcomputations, -- exiting on the first exception. newtype ExceptT e (m :: Type -> Type) a ExceptT :: m (Either e a) -> ExceptT e (m :: Type -> Type) a -- | The parameterizable exception monad. -- -- Computations are either exceptions or normal values. -- -- The return function returns a normal value, while -- >>= exits on the first exception. For a variant that -- continues after an error and collects all the errors, see -- Errors. type Except e = ExceptT e Identity -- | The inverse of ExceptT. runExceptT :: ExceptT e m a -> m (Either e a) -- | Map the unwrapped computation using the given function. -- -- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b -- | Transform any exceptions thrown by the computation using the given -- function. withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a -- | Extractor for computations in the exception monad. (The inverse of -- except). runExcept :: Except e a -> Either e a -- | Map the unwrapped computation using the given function. -- -- mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b -- | Transform any exceptions thrown by the computation using the given -- function (a specialization of withExceptT). withExcept :: (e -> e') -> Except e a -> Except e' a -- | -- -- 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 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 -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Executes a computation in a modified environment. local :: MonadReader r m => (r -> r) -> m a -> m a -- | Retrieves a function of the current environment. reader :: MonadReader r m => (r -> a) -> m a -- | Retrieves a function of the current environment. asks :: MonadReader r m => (r -> a) -> m a instance Control.Monad.Reader.Class.MonadReader r ((->) r) instance GHC.Base.Monad m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Reader.ReaderT r m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Reader.Class.MonadReader r' m => Control.Monad.Reader.Class.MonadReader r' (Control.Monad.Trans.Cont.ContT r m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Reader.Class.MonadReader r m => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.State.Strict.StateT s m) instance (GHC.Base.Monoid w, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.Reader.Class.MonadReader r m) => Control.Monad.Reader.Class.MonadReader r (Control.Monad.Trans.Accum.AccumT w m) instance Control.Monad.Reader.Class.MonadReader r' m => Control.Monad.Reader.Class.MonadReader r' (Control.Monad.Trans.Select.SelectT r m) -- | -- --

A note on commutativity

-- -- Some effects are commutative: it doesn't matter which you -- resolve first, as all possible orderings of commutative effects are -- isomorphic. Consider, for example, the reader and state effects, as -- exemplified by ReaderT and StateT respectively. If we -- have ReaderT r (State s) a, this is effectively -- r -> State s a ~ r -> s -> (a, s); if we -- instead have StateT s (Reader r) a, this is -- effectively s -> Reader r (a, s) ~ s -> r -> (a, -- s). Since we can always reorder function arguments (for example, -- using flip, as in this case) without changing the result, these -- are isomorphic, showing that reader and state are commutative, -- or, more precisely, commute with each other. -- -- However, this isn't generally the case. Consider instead the error and -- state effects, as exemplified by MaybeT and StateT -- respectively. If we have MaybeT (State s) a, -- this is effectively State s (Maybe a) ~ s -> -- (Maybe a, s): put simply, the error can occur only in the -- result, but not the state, which always 'survives'. On the -- other hand, if we have StateT s Maybe a, this -- is instead s -> Maybe (a, s): here, if we error, we -- lose both the state and the result! Thus, error and state -- effects do not commute with each other. -- -- As the MTL is capability-based, we support any ordering of -- non-commutative effects on an equal footing. Indeed, if you wish to -- use MonadState, for example, whether your final monadic stack -- ends up being MaybeT (State s) a, -- StateT s Maybe a, or anything else, you will be -- able to write your desired code without having to consider such -- differences. However, the way we implement these capabilities -- for any given transformer (or rather, any given transformed stack) -- is affected by this ordering unless the effects in question are -- commutative. -- -- We note in this module which effects the accumulation effect does and -- doesn't commute with; we also note on implementations with -- non-commutative transformers what the outcome will be. Note that, -- depending on how the 'inner monad' is structured, this may be more -- complex than we note: we describe only what impact the 'outer effect' -- has, not what else might be in the stack. -- --

Commutativity of selection

-- -- The selection effect commutes with the identity effect -- (IdentityT), but nothing else. module Control.Monad.Select -- | The capability to search with backtracking. Essentially describes a -- 'policy function': given the state of the search (and a 'ranking' or -- 'evaluation' of each possible result so far), pick the result that's -- currently best. -- --

Laws

-- -- Any instance of MonadSelect must follow these laws: -- -- class (Monad m) => MonadSelect r m | m -> r select :: MonadSelect r m => ((a -> r) -> a) -> m a -- | A helper type to decrease boilerplate when defining new transformer -- instances of MonadSelect. -- -- Most of the instances in this module are derived using this method; -- for example, our instance of ExceptT is derived as follows: -- --
--   deriving via (LiftingSelect (ExceptT e) m) instance (MonadSelect r m) =>
--    MonadSelect r (ExceptT e m)
--   
newtype LiftingSelect (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) LiftingSelect :: t m a -> LiftingSelect (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) (a :: Type) instance GHC.Base.Monad (t m) => GHC.Base.Monad (Control.Monad.Select.LiftingSelect t m) instance GHC.Base.Applicative (t m) => GHC.Base.Applicative (Control.Monad.Select.LiftingSelect t m) instance GHC.Base.Functor (t m) => GHC.Base.Functor (Control.Monad.Select.LiftingSelect t m) instance Control.Monad.Select.MonadSelect r m => Control.Monad.Select.MonadSelect r (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Select.MonadSelect r' m => Control.Monad.Select.MonadSelect r' (Control.Monad.Trans.Cont.ContT r m) instance Control.Monad.Select.MonadSelect r m => Control.Monad.Select.MonadSelect r (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Select.MonadSelect r m => Control.Monad.Select.MonadSelect r (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Select.MonadSelect r' m => Control.Monad.Select.MonadSelect r' (Control.Monad.Trans.Reader.ReaderT r m) instance Control.Monad.Select.MonadSelect w m => Control.Monad.Select.MonadSelect w (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Select.MonadSelect w m => Control.Monad.Select.MonadSelect w (Control.Monad.Trans.State.Strict.StateT s m) instance Control.Monad.Select.MonadSelect w' m => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (Control.Monad.Select.MonadSelect w' m, GHC.Base.Monoid w) => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (Control.Monad.Select.MonadSelect w' m, GHC.Base.Monoid w) => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.Writer.Strict.WriterT w m) instance Control.Monad.Select.MonadSelect w' m => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (Control.Monad.Select.MonadSelect w' m, GHC.Base.Monoid w) => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (Control.Monad.Select.MonadSelect w' m, GHC.Base.Monoid w) => Control.Monad.Select.MonadSelect w' (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance (Control.Monad.Select.MonadSelect r m, GHC.Base.Monoid w) => Control.Monad.Select.MonadSelect r (Control.Monad.Trans.Accum.AccumT w m) instance (Control.Monad.Trans.Class.MonadTrans t, Control.Monad.Select.MonadSelect r m, GHC.Base.Monad (t m)) => Control.Monad.Select.MonadSelect r (Control.Monad.Select.LiftingSelect t m) instance Control.Monad.Select.MonadSelect r (Control.Monad.Trans.Select.SelectT r Data.Functor.Identity.Identity) -- | 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 -- | Return the state from the internals of the monad. get :: MonadState s m => m s -- | Replace the state inside the monad. put :: MonadState s m => s -> m () -- | Embed a simple state action into the monad. 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 () -- | A variant of modify in which the computation is strict in the -- new 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 GHC.Base.Monad m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.State.Lazy.StateT s m) instance GHC.Base.Monad m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.State.Strict.StateT s m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monad m, GHC.Base.Monoid w) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Cont.ContT r m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Reader.ReaderT r m) instance (GHC.Base.Monoid w, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (GHC.Base.Monoid w, Control.Monad.State.Class.MonadState s m) => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Accum.AccumT w m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Trans.Select.SelectT 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 -- | 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 -- | Return the state from the internals of the monad. get :: MonadState s m => m s -- | Replace the state inside the monad. put :: MonadState s m => s -> m () -- | Embed a simple state action into the monad. 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 () -- | A variant of modify in which the computation is strict in the -- new 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 :: Type -> Type) a StateT :: (s -> m (a, s)) -> StateT s (m :: Type -> Type) a runStateT :: StateT s m 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 :: forall s (m :: Type -> Type) a. (s -> s) -> StateT s m a -> StateT 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 -- | Return the state from the internals of the monad. get :: MonadState s m => m s -- | Replace the state inside the monad. put :: MonadState s m => s -> m () -- | Embed a simple state action into the monad. 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 () -- | A variant of modify in which the computation is strict in the -- new 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 :: Type -> Type) a StateT :: (s -> m (a, s)) -> StateT s (m :: Type -> Type) a runStateT :: StateT s m 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 :: forall s (m :: Type -> Type) a. (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 -- | -- -- 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 -- | Retrieves the monad environment. ask :: MonadReader r m => m r -- | Executes a computation in a modified environment. local :: MonadReader r m => (r -> r) -> m a -> m a -- | Retrieves a function of the current environment. 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 :: Type -> Type) a ReaderT :: (r -> m a) -> ReaderT r (m :: Type -> Type) a runReaderT :: ReaderT r m 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 :: forall r' r (m :: Type -> Type) a. (r' -> r) -> ReaderT r m a -> ReaderT r' m a -- | 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 -- | writer (a,w) embeds a simple writer action. writer :: MonadWriter w m => (a, w) -> m a -- | tell w is an action that produces the output -- w. tell :: MonadWriter w m => w -> m () -- | listen m is an action that executes the action -- m and adds its output to the value of the computation. listen :: MonadWriter w m => m a -> m (a, w) -- | pass m is an action that executes the action -- m, which returns a value and a function, and returns the -- value, applying the function to the output. 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 GHC.Base.Monoid w => Control.Monad.Writer.Class.MonadWriter w ((,) w) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Writer.CPS.WriterT w m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Maybe.MaybeT m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Reader.ReaderT r m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.State.Strict.StateT s m) instance (GHC.Base.Monoid w', Control.Monad.Writer.Class.MonadWriter w m) => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Trans.Accum.AccumT w' m) -- | Strict writer monads that use continuation-passing-style to achieve -- constant space usage. -- -- 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. -- -- Since: mtl-2.3, transformers-0.5.6 module Control.Monad.Writer.CPS class (Monoid w, Monad m) => MonadWriter w m | m -> w -- | writer (a,w) embeds a simple writer action. writer :: MonadWriter w m => (a, w) -> m a -- | tell w is an action that produces the output -- w. tell :: MonadWriter w m => w -> m () -- | listen m is an action that executes the action -- m and adds its output to the value of the computation. listen :: MonadWriter w m => m a -> m (a, w) -- | pass m is an action that executes the action -- m, which returns a value and a function, and returns the -- value, applying the function to the output. 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 :: Monoid w => Writer w a -> (a, w) -- | Extract the output from a writer computation. -- -- execWriter :: Monoid w => Writer w a -> w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriter :: (Monoid w, Monoid w') => ((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. data WriterT w (m :: Type -> Type) a -- | Extract the output from a writer computation. -- -- execWriterT :: (Monad m, Monoid w) => WriterT w m a -> m w -- | Map both the return value and output of a computation using the given -- function. -- -- mapWriterT :: (Monad n, Monoid w, Monoid w') => (m (a, w) -> n (b, w')) -> WriterT w m a -> WriterT w' n b -- | 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 (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.RWS.CPS.RWST r w s m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (GHC.Base.Monoid w, GHC.Base.Monad m) => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.RWS.Class.MonadRWS r w s m => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.RWS.Class.MonadRWS r w s m => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.RWS.Class.MonadRWS r w s m => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Trans.Maybe.MaybeT m) -- | 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 :: Type -> Type) a RWST :: (r -> s -> m (a, s, w)) -> RWST r w s (m :: Type -> Type) a runRWST :: RWST r w s m 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 :: forall r' s r w (m :: Type -> Type) a. (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a -- | 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 :: Type -> Type) a RWST :: (r -> s -> m (a, s, w)) -> RWST r w s (m :: Type -> Type) a runRWST :: RWST r w s m 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 :: forall r' s r w (m :: Type -> Type) a. (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 -- | Strict RWS monad that uses continuation-passing-style to achieve -- constant space usage. -- -- 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. -- -- Since: mtl-2.3, transformers-0.5.6 module Control.Monad.RWS.CPS -- | 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 :: Monoid w => (r -> s -> (a, s, w)) -> RWS r w s a -- | Unwrap an RWS computation as a function. (The inverse of rws.) runRWS :: Monoid w => 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 :: Monoid w => 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 :: Monoid w => 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 :: (Monoid w, Monoid w') => ((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. data RWST r w s (m :: Type -> Type) a -- | Unwrap an RWST computation as a function. (The inverse of -- rwsT.) runRWST :: Monoid w => RWST r w s m 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, Monoid w) => 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, Monoid w) => RWST r w s m a -> r -> s -> m (s, w) -- | Map the inner computation using the given function. -- -- mapRWST :: (Monad n, Monoid w, Monoid w') => (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 :: forall r' s r w (m :: Type -> Type) a. (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w 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 -- | writer (a,w) embeds a simple writer action. writer :: MonadWriter w m => (a, w) -> m a -- | tell w is an action that produces the output -- w. tell :: MonadWriter w m => w -> m () -- | listen m is an action that executes the action -- m and adds its output to the value of the computation. listen :: MonadWriter w m => m a -> m (a, w) -- | pass m is an action that executes the action -- m, which returns a value and a function, and returns the -- value, applying the function to the output. 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 :: Type -> Type) a WriterT :: m (a, w) -> WriterT w (m :: Type -> Type) a runWriterT :: WriterT w m 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 -- | writer (a,w) embeds a simple writer action. writer :: MonadWriter w m => (a, w) -> m a -- | tell w is an action that produces the output -- w. tell :: MonadWriter w m => w -> m () -- | listen m is an action that executes the action -- m and adds its output to the value of the computation. listen :: MonadWriter w m => m a -> m (a, w) -- | pass m is an action that executes the action -- m, which returns a value and a function, and returns the -- value, applying the function to the output. 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 :: Type -> Type) a WriterT :: m (a, w) -> WriterT w (m :: Type -> Type) a [runWriterT] :: WriterT w (m :: Type -> Type) 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