-- Hoogle documentation, generated by Haddock
-- See Hoogle, http://www.haskell.org/hoogle/
-- | Concrete functor and monad transformers
--
-- A portable library of functor and monad transformers, inspired by the
-- paper
--
--
--
-- This package contains:
--
--
-- - the monad transformer class (in
-- Control.Monad.Trans.Class)
-- - concrete functor and monad transformers, each with associated
-- operations and functions to lift operations associated with other
-- transformers.
--
--
-- The package can be used on its own in portable Haskell code, in which
-- case operations need to be manually lifted through transformer stacks
-- (see Control.Monad.Trans.Class for some examples).
-- Alternatively, it can be used with the non-portable monad classes in
-- the mtl or monads-tf packages, which automatically
-- lift operations introduced by monad transformers through other
-- transformers.
@package transformers
@version 0.5.6.2
-- | Making functors with an Applicative instance that performs
-- actions in the reverse order.
module Control.Applicative.Backwards
-- | The same functor, but with an Applicative instance that
-- performs actions in the reverse order.
newtype Backwards f a
Backwards :: f a -> Backwards f a
[forwards] :: Backwards f a -> f a
instance Data.Functor.Classes.Eq1 f => Data.Functor.Classes.Eq1 (Control.Applicative.Backwards.Backwards f)
instance Data.Functor.Classes.Ord1 f => Data.Functor.Classes.Ord1 (Control.Applicative.Backwards.Backwards f)
instance Data.Functor.Classes.Read1 f => Data.Functor.Classes.Read1 (Control.Applicative.Backwards.Backwards f)
instance Data.Functor.Classes.Show1 f => Data.Functor.Classes.Show1 (Control.Applicative.Backwards.Backwards f)
instance (Data.Functor.Classes.Eq1 f, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Applicative.Backwards.Backwards f a)
instance (Data.Functor.Classes.Ord1 f, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Applicative.Backwards.Backwards f a)
instance (Data.Functor.Classes.Read1 f, GHC.Read.Read a) => GHC.Read.Read (Control.Applicative.Backwards.Backwards f a)
instance (Data.Functor.Classes.Show1 f, GHC.Show.Show a) => GHC.Show.Show (Control.Applicative.Backwards.Backwards f a)
instance GHC.Base.Functor f => GHC.Base.Functor (Control.Applicative.Backwards.Backwards f)
instance GHC.Base.Applicative f => GHC.Base.Applicative (Control.Applicative.Backwards.Backwards f)
instance GHC.Base.Alternative f => GHC.Base.Alternative (Control.Applicative.Backwards.Backwards f)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Applicative.Backwards.Backwards f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Applicative.Backwards.Backwards f)
instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (Control.Applicative.Backwards.Backwards f)
-- | Signatures for monad operations that require specialized lifting. Each
-- signature has a uniformity property that the lifting should satisfy.
module Control.Monad.Signatures
-- | Signature of the callCC operation, introduced in
-- Control.Monad.Trans.Cont. Any lifting function
-- liftCallCC should satisfy
--
--
type CallCC m a b = ((a -> m b) -> m a) -> m a
-- | Signature of the catchE operation, introduced in
-- Control.Monad.Trans.Except. Any lifting function
-- liftCatch should satisfy
--
--
type Catch e m a = m a -> (e -> m a) -> m a
-- | Signature of the listen operation, introduced in
-- Control.Monad.Trans.Writer. Any lifting function
-- liftListen should satisfy
--
--
type Listen w m a = m a -> m (a, w)
-- | Signature of the pass operation, introduced in
-- Control.Monad.Trans.Writer. Any lifting function
-- liftPass should satisfy
--
--
type Pass w m a = m (a, w -> w) -> m a
-- | The class of monad transformers.
--
-- A monad transformer makes a 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.
module Control.Monad.Trans.Class
-- | The class of monad transformers. Instances should satisfy the
-- following laws, which state that lift is a monad
-- transformation:
--
--
class MonadTrans t
-- | Lift a computation from the argument monad to the constructed monad.
lift :: (MonadTrans t, Monad m) => m a -> t m a
-- | Continuation monads.
--
-- Delimited continuation operators are taken from Kenichi Asai and Oleg
-- Kiselyov's tutorial at CW 2011, "Introduction to programming with
-- shift and reset"
-- (http://okmij.org/ftp/continuations/#tutorial).
module Control.Monad.Trans.Cont
-- | 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
-- | reset m delimits the continuation of any shift
-- inside m.
--
--
reset :: Cont r r -> Cont r' r
-- | shift f captures the continuation up to the nearest
-- enclosing reset and passes it to f:
--
--
shift :: ((a -> r) -> Cont r r) -> Cont r a
-- | 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 m a
ContT :: ((a -> m r) -> m r) -> ContT r m 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 :: (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
-- | callCC (call-with-current-continuation) calls its argument
-- function, passing it the current continuation. It provides an escape
-- continuation mechanism for use with continuation monads. Escape
-- continuations one allow to abort the current computation and return a
-- value immediately. They achieve a similar effect to throwE and
-- catchE within an ExceptT monad. The advantage of this
-- function over calling return is that it makes the continuation
-- explicit, allowing more flexibility and better control.
--
-- 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 :: ((a -> ContT r m b) -> ContT r m a) -> ContT r m a
-- | resetT m delimits the continuation of any
-- shiftT inside m.
--
--
resetT :: Monad m => ContT r m r -> ContT r' m r
-- | shiftT f captures the continuation up to the nearest
-- enclosing resetT and passes it to f:
--
--
shiftT :: Monad m => ((a -> m r) -> ContT r m r) -> ContT r m a
-- | liftLocal ask local yields a local function
-- for ContT r m.
liftLocal :: Monad m => m r' -> ((r' -> r') -> m r -> m r) -> (r' -> r') -> ContT r m a -> ContT r m a
instance forall k (r :: k) (m :: k -> *). GHC.Base.Functor (Control.Monad.Trans.Cont.ContT r m)
instance forall k (r :: k) (m :: k -> *). GHC.Base.Applicative (Control.Monad.Trans.Cont.ContT r m)
instance forall k (r :: k) (m :: k -> *). GHC.Base.Monad (Control.Monad.Trans.Cont.ContT r m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Cont.ContT r m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Cont.ContT r)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Cont.ContT r m)
-- | This monad transformer adds the ability to fail or throw exceptions to
-- a monad.
--
-- A sequence of actions succeeds, producing a value, only if all the
-- actions in the sequence are successful. If one fails with an error,
-- the rest of the sequence is skipped and the composite action fails
-- with that error.
--
-- If the value of the error is not required, the variant in
-- Control.Monad.Trans.Maybe may be used instead.
--
-- Note: This module will be removed in a future release. Instead,
-- use Control.Monad.Trans.Except, which does not restrict the
-- exception type, and also includes a base exception monad.
-- | Deprecated: Use Control.Monad.Trans.Except instead
module Control.Monad.Trans.Error
-- | An exception to be thrown.
--
-- Minimal complete definition: noMsg or strMsg.
class Error a
-- | Creates an exception without a message. The default implementation is
-- strMsg "".
noMsg :: Error a => a
-- | Creates an exception with a message. The default implementation of
-- strMsg s is noMsg.
strMsg :: Error a => String -> a
-- | Workaround so that we can have a Haskell 98 instance Error
-- String.
class ErrorList a
listMsg :: ErrorList 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:
--
--
-- - e - The error type.
-- - m - The inner monad.
--
--
-- 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 m a
[runErrorT] :: ErrorT e m 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
-- | Signal an error value e.
--
--
throwError :: Monad m => e -> ErrorT e m a
-- | Handle an error.
--
--
catchError :: Monad m => ErrorT e m a -> (e -> ErrorT e m a) -> ErrorT e m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ErrorT e m) a b
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ErrorT e m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ErrorT e m) a
instance (GHC.Classes.Eq e, Data.Functor.Classes.Eq1 m) => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Classes.Ord e, Data.Functor.Classes.Ord1 m) => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Read.Read e, Data.Functor.Classes.Read1 m) => Data.Functor.Classes.Read1 (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Show.Show e, Data.Functor.Classes.Show1 m) => Data.Functor.Classes.Show1 (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Classes.Eq e, Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Error.ErrorT e m a)
instance (GHC.Classes.Ord e, Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Error.ErrorT e m a)
instance (GHC.Read.Read e, Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Error.ErrorT e m a)
instance (GHC.Show.Show e, Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Error.ErrorT e m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Error.ErrorT e m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Error.ErrorT e f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Error.ErrorT e f)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Base.Functor m, GHC.Base.Monad m, Control.Monad.Trans.Error.Error e) => GHC.Base.Alternative (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Base.Monad m, Control.Monad.Trans.Error.Error e) => GHC.Base.Monad (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Base.Monad m, Control.Monad.Trans.Error.Error e) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Error.ErrorT e m)
instance (GHC.Base.Monad m, Control.Monad.Trans.Error.Error e) => GHC.Base.MonadPlus (Control.Monad.Trans.Error.ErrorT e m)
instance (Control.Monad.Fix.MonadFix m, Control.Monad.Trans.Error.Error e) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Error.ErrorT e m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Error.ErrorT e)
instance (Control.Monad.Trans.Error.Error e, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Error.ErrorT e m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Error.ErrorT e m)
instance Control.Monad.Trans.Error.ErrorList a => Control.Monad.Trans.Error.Error [a]
instance Control.Monad.Trans.Error.ErrorList GHC.Types.Char
instance Control.Monad.Trans.Error.Error e => GHC.Base.Alternative (Data.Either.Either e)
instance Control.Monad.Trans.Error.Error e => GHC.Base.MonadPlus (Data.Either.Either e)
instance Control.Monad.Trans.Error.Error GHC.IO.Exception.IOException
-- | This monad transformer extends a monad with the ability to throw
-- exceptions.
--
-- A sequence of actions terminates normally, producing a value, only if
-- none of the actions in the sequence throws an exception. If one throws
-- an exception, the rest of the sequence is skipped and the composite
-- action exits with that exception.
--
-- If the value of the exception is not required, the variant in
-- Control.Monad.Trans.Maybe may be used instead.
module Control.Monad.Trans.Except
-- | 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
-- | Constructor for computations in the exception monad. (The inverse of
-- runExcept).
except :: Monad m => Either e 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
-- | A monad transformer that adds exceptions to other monads.
--
-- ExceptT constructs a monad parameterized over two things:
--
--
-- - e - The exception type.
-- - m - The inner monad.
--
--
-- The return function yields a computation that produces the
-- given value, while >>= sequences two subcomputations,
-- exiting on the first exception.
newtype ExceptT e m a
ExceptT :: m (Either e a) -> ExceptT e m a
-- | 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 :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
-- | Signal an exception value e.
--
--
throwE :: Monad m => e -> ExceptT e m a
-- | Handle an exception.
--
--
catchE :: Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a
instance (GHC.Classes.Eq e, Data.Functor.Classes.Eq1 m) => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Classes.Ord e, Data.Functor.Classes.Ord1 m) => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Read.Read e, Data.Functor.Classes.Read1 m) => Data.Functor.Classes.Read1 (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Show.Show e, Data.Functor.Classes.Show1 m) => Data.Functor.Classes.Show1 (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Classes.Eq e, Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Except.ExceptT e m a)
instance (GHC.Classes.Ord e, Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Except.ExceptT e m a)
instance (GHC.Read.Read e, Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Except.ExceptT e m a)
instance (GHC.Show.Show e, Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Except.ExceptT e m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Except.ExceptT e m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Except.ExceptT e f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Except.ExceptT e f)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Base.Functor m, GHC.Base.Monad m, GHC.Base.Monoid e) => GHC.Base.Alternative (Control.Monad.Trans.Except.ExceptT e m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Except.ExceptT e m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Except.ExceptT e m)
instance (GHC.Base.Monad m, GHC.Base.Monoid e) => GHC.Base.MonadPlus (Control.Monad.Trans.Except.ExceptT e m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Except.ExceptT e m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Except.ExceptT e)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Except.ExceptT e m)
instance Control.Monad.Zip.MonadZip m => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Except.ExceptT e m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Except.ExceptT e m)
-- | The identity monad transformer.
--
-- This is useful for functions parameterized by a monad transformer.
module Control.Monad.Trans.Identity
-- | The trivial monad transformer, which maps a monad to an equivalent
-- monad.
newtype IdentityT f a
IdentityT :: f a -> IdentityT f a
[runIdentityT] :: IdentityT f a -> f a
-- | Lift a unary operation to the new monad.
mapIdentityT :: (m a -> n b) -> IdentityT m a -> IdentityT n b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m a -> Catch e (IdentityT m) a
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m a b -> CallCC (IdentityT m) a b
instance Data.Functor.Classes.Eq1 f => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Identity.IdentityT f)
instance Data.Functor.Classes.Ord1 f => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Identity.IdentityT f)
instance Data.Functor.Classes.Read1 f => Data.Functor.Classes.Read1 (Control.Monad.Trans.Identity.IdentityT f)
instance Data.Functor.Classes.Show1 f => Data.Functor.Classes.Show1 (Control.Monad.Trans.Identity.IdentityT f)
instance (Data.Functor.Classes.Eq1 f, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Identity.IdentityT f a)
instance (Data.Functor.Classes.Ord1 f, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Identity.IdentityT f a)
instance (Data.Functor.Classes.Read1 f, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Identity.IdentityT f a)
instance (Data.Functor.Classes.Show1 f, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Identity.IdentityT f a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Identity.IdentityT m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Identity.IdentityT f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Identity.IdentityT f)
instance GHC.Base.Applicative m => GHC.Base.Applicative (Control.Monad.Trans.Identity.IdentityT m)
instance GHC.Base.Alternative m => GHC.Base.Alternative (Control.Monad.Trans.Identity.IdentityT m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Identity.IdentityT m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Identity.IdentityT m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Monad.Trans.Identity.IdentityT m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Identity.IdentityT m)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Identity.IdentityT m)
instance Control.Monad.Zip.MonadZip m => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Identity.IdentityT m)
instance Control.Monad.Trans.Class.MonadTrans Control.Monad.Trans.Identity.IdentityT
instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Identity.IdentityT f)
-- | The ListT monad transformer, adding backtracking to a given monad,
-- which must be commutative.
-- | Deprecated: This transformer is invalid on most monads
module Control.Monad.Trans.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 m a
[runListT] :: ListT m a -> m [a]
-- | Map between ListT computations.
--
--
mapListT :: (m [a] -> n [b]) -> ListT m a -> ListT n b
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m [a] [b] -> CallCC (ListT m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m [a] -> Catch e (ListT m) a
instance Data.Functor.Classes.Eq1 m => Data.Functor.Classes.Eq1 (Control.Monad.Trans.List.ListT m)
instance Data.Functor.Classes.Ord1 m => Data.Functor.Classes.Ord1 (Control.Monad.Trans.List.ListT m)
instance Data.Functor.Classes.Read1 m => Data.Functor.Classes.Read1 (Control.Monad.Trans.List.ListT m)
instance Data.Functor.Classes.Show1 m => Data.Functor.Classes.Show1 (Control.Monad.Trans.List.ListT m)
instance (Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.List.ListT m a)
instance (Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.List.ListT m a)
instance (Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.List.ListT m a)
instance (Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.List.ListT m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.List.ListT m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.List.ListT f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.List.ListT f)
instance GHC.Base.Applicative m => GHC.Base.Applicative (Control.Monad.Trans.List.ListT m)
instance GHC.Base.Applicative m => GHC.Base.Alternative (Control.Monad.Trans.List.ListT m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.List.ListT m)
instance GHC.Base.Monad m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.List.ListT m)
instance GHC.Base.Monad m => GHC.Base.MonadPlus (Control.Monad.Trans.List.ListT m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.List.ListT m)
instance Control.Monad.Trans.Class.MonadTrans Control.Monad.Trans.List.ListT
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.List.ListT m)
instance Control.Monad.Zip.MonadZip m => Control.Monad.Zip.MonadZip (Control.Monad.Trans.List.ListT m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.List.ListT m)
-- | The MaybeT monad transformer extends a monad with the ability
-- to exit the computation without returning a value.
--
-- A sequence of actions produces a value only if all the actions in the
-- sequence do. If one exits, the rest of the sequence is skipped and the
-- composite action exits.
--
-- For a variant allowing a range of exception values, see
-- Control.Monad.Trans.Except.
module Control.Monad.Trans.Maybe
-- | The parameterizable maybe monad, obtained by composing an arbitrary
-- monad with the Maybe monad.
--
-- Computations are actions that may produce a value or exit.
--
-- The return function yields a computation that produces that
-- value, while >>= sequences two subcomputations, exiting
-- if either computation does.
newtype MaybeT m a
MaybeT :: m (Maybe a) -> MaybeT m a
[runMaybeT] :: MaybeT m a -> m (Maybe a)
-- | Transform the computation inside a MaybeT.
--
--
mapMaybeT :: (m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
-- | Convert a MaybeT computation to ExceptT, with a default
-- exception value.
maybeToExceptT :: Functor m => e -> MaybeT m a -> ExceptT e m a
-- | Convert a ExceptT computation to MaybeT, discarding the
-- value of any exception.
exceptToMaybeT :: Functor m => ExceptT e m a -> MaybeT m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m (Maybe a) (Maybe b) -> CallCC (MaybeT m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (Maybe a) -> Catch e (MaybeT m) a
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (Maybe a) -> Listen w (MaybeT m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (Maybe a) -> Pass w (MaybeT m) a
instance Data.Functor.Classes.Eq1 m => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Maybe.MaybeT m)
instance Data.Functor.Classes.Ord1 m => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Maybe.MaybeT m)
instance Data.Functor.Classes.Read1 m => Data.Functor.Classes.Read1 (Control.Monad.Trans.Maybe.MaybeT m)
instance Data.Functor.Classes.Show1 m => Data.Functor.Classes.Show1 (Control.Monad.Trans.Maybe.MaybeT m)
instance (Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Maybe.MaybeT m a)
instance (Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Maybe.MaybeT m a)
instance (Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Maybe.MaybeT m a)
instance (Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Maybe.MaybeT m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Maybe.MaybeT m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Maybe.MaybeT f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Maybe.MaybeT f)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Maybe.MaybeT m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Alternative (Control.Monad.Trans.Maybe.MaybeT m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Maybe.MaybeT m)
instance GHC.Base.Monad m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Maybe.MaybeT m)
instance GHC.Base.Monad m => GHC.Base.MonadPlus (Control.Monad.Trans.Maybe.MaybeT m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Maybe.MaybeT m)
instance Control.Monad.Trans.Class.MonadTrans Control.Monad.Trans.Maybe.MaybeT
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Maybe.MaybeT m)
instance Control.Monad.Zip.MonadZip m => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Maybe.MaybeT m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Maybe.MaybeT m)
-- | A monad transformer that combines ReaderT, WriterT
-- and StateT. This version uses continuation-passing-style for
-- the writer part to achieve constant space usage. For a lazy version
-- with the same interface, see Control.Monad.Trans.RWS.Lazy.
module Control.Monad.Trans.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 a
-- | Construct an RWST computation from a function. (The inverse of
-- runRWST.)
rwsT :: (Functor m, Monoid w) => (r -> s -> m (a, s, w)) -> RWST r w s m 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.
--
--
-- - runRWST (mapRWST f m) r s = f (runRWST m
-- r s) mapRWST :: (m (a, s, w) -> n (b, s, w')) -> RWST r w s
-- m a -> RWST r w' s n b
--
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 :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a
-- | Constructor for computations in the reader monad (equivalent to
-- asks).
reader :: Monad m => (r -> a) -> RWST r w s m a
-- | Fetch the value of the environment.
ask :: Monad m => RWST r w s m r
-- | Execute a computation in a modified environment
--
--
local :: (r -> r) -> RWST r w s m a -> RWST r w s m a
-- | Retrieve a function of the current environment.
--
--
asks :: Monad m => (r -> a) -> RWST r w s m a
-- | Construct a writer computation from a (result, output) pair.
writer :: (Monoid w, Monad m) => (a, w) -> RWST r w s m a
-- | tell w is an action that produces the output
-- w.
tell :: (Monoid w, Monad m) => w -> RWST r w s m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: (Monoid w, Monad m) => RWST r w s m a -> RWST r w s m (a, w)
-- | 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 :: (Monoid w, Monad m) => (w -> b) -> RWST r w s m a -> RWST r w s m (a, b)
-- | 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 :: (Monoid w, Monoid w', Monad m) => RWST r w s m (a, w -> w') -> RWST r w' s m a
-- | 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 :: (Monoid w, Monad m) => (w -> w) -> RWST r w s m a -> RWST r w s m a
-- | Construct a state monad computation from a state transformer function.
state :: Monad m => (s -> (a, s)) -> RWST r w s m a
-- | Fetch the current value of the state within the monad.
get :: Monad m => RWST r w s m s
-- | put s sets the state within the monad to s.
put :: Monad m => s -> RWST r w s m ()
-- | modify f is an action that updates the state to the
-- result of applying f to the current state.
--
--
modify :: Monad m => (s -> s) -> RWST r w s m ()
-- | Get a specific component of the state, using a projection function
-- supplied.
--
--
gets :: Monad m => (s -> a) -> RWST r w s m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current state on entering the continuation.
liftCallCC' :: CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, s, w) -> Catch e (RWST r w s m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.RWS.CPS.RWST r w s m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.RWS.CPS.RWST r w s)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.RWS.CPS.RWST r w s m)
-- | A monad transformer that combines ReaderT, WriterT
-- and StateT. This version is lazy; for a constant-space
-- version with almost the same interface, see
-- Control.Monad.Trans.RWS.CPS.
module Control.Monad.Trans.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 m 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 :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a
-- | Constructor for computations in the reader monad (equivalent to
-- asks).
reader :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a
-- | Fetch the value of the environment.
ask :: (Monoid w, Monad m) => RWST r w s m r
-- | Execute a computation in a modified environment
--
--
local :: (r -> r) -> RWST r w s m a -> RWST r w s m a
-- | Retrieve a function of the current environment.
--
--
asks :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a
-- | Construct a writer computation from a (result, output) pair.
writer :: Monad m => (a, w) -> RWST r w s m a
-- | tell w is an action that produces the output
-- w.
tell :: Monad m => w -> RWST r w s m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: Monad m => RWST r w s m a -> RWST r w s m (a, w)
-- | 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 :: Monad m => (w -> b) -> RWST r w s m a -> RWST r w s m (a, b)
-- | 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 :: Monad m => RWST r w s m (a, w -> w) -> RWST r w s m a
-- | 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 :: Monad m => (w -> w) -> RWST r w s m a -> RWST r w s m a
-- | Construct a state monad computation from a state transformer function.
state :: (Monoid w, Monad m) => (s -> (a, s)) -> RWST r w s m a
-- | Fetch the current value of the state within the monad.
get :: (Monoid w, Monad m) => RWST r w s m s
-- | put s sets the state within the monad to s.
put :: (Monoid w, Monad m) => s -> RWST r w s m ()
-- | modify f is an action that updates the state to the
-- result of applying f to the current state.
--
--
modify :: (Monoid w, Monad m) => (s -> s) -> RWST r w s m ()
-- | Get a specific component of the state, using a projection function
-- supplied.
--
--
gets :: (Monoid w, Monad m) => (s -> a) -> RWST r w s m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: Monoid w => CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current state on entering the continuation.
liftCallCC' :: Monoid w => CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, s, w) -> Catch e (RWST r w s m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Monad m) => GHC.Base.Monad (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, Control.Monad.Fail.MonadFail m) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance (GHC.Base.Monoid w, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance GHC.Base.Monoid w => Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.RWS.Lazy.RWST r w s)
instance (GHC.Base.Monoid w, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.RWS.Lazy.RWST r w s m)
-- | A monad transformer that combines ReaderT, WriterT
-- and StateT. This version is lazy; for a constant-space
-- version with almost the same interface, see
-- Control.Monad.Trans.RWS.CPS.
module Control.Monad.Trans.RWS
-- | A monad transformer that combines ReaderT, WriterT
-- and StateT. This version is strict; for a lazy version with
-- the same interface, see Control.Monad.Trans.RWS.Lazy. Although
-- the output is built strictly, it is not possible to achieve constant
-- space behaviour with this transformer: for that, use
-- Control.Monad.Trans.RWS.CPS instead.
module Control.Monad.Trans.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 m 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 :: (r' -> s -> (r, s)) -> RWST r w s m a -> RWST r' w s m a
-- | Constructor for computations in the reader monad (equivalent to
-- asks).
reader :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a
-- | Fetch the value of the environment.
ask :: (Monoid w, Monad m) => RWST r w s m r
-- | Execute a computation in a modified environment
--
--
local :: (r -> r) -> RWST r w s m a -> RWST r w s m a
-- | Retrieve a function of the current environment.
--
--
asks :: (Monoid w, Monad m) => (r -> a) -> RWST r w s m a
-- | Construct a writer computation from a (result, output) pair.
writer :: Monad m => (a, w) -> RWST r w s m a
-- | tell w is an action that produces the output
-- w.
tell :: Monad m => w -> RWST r w s m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: Monad m => RWST r w s m a -> RWST r w s m (a, w)
-- | 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 :: Monad m => (w -> b) -> RWST r w s m a -> RWST r w s m (a, b)
-- | 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 :: Monad m => RWST r w s m (a, w -> w) -> RWST r w s m a
-- | 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 :: Monad m => (w -> w) -> RWST r w s m a -> RWST r w s m a
-- | Construct a state monad computation from a state transformer function.
state :: (Monoid w, Monad m) => (s -> (a, s)) -> RWST r w s m a
-- | Fetch the current value of the state within the monad.
get :: (Monoid w, Monad m) => RWST r w s m s
-- | put s sets the state within the monad to s.
put :: (Monoid w, Monad m) => s -> RWST r w s m ()
-- | modify f is an action that updates the state to the
-- result of applying f to the current state.
--
--
modify :: (Monoid w, Monad m) => (s -> s) -> RWST r w s m ()
-- | Get a specific component of the state, using a projection function
-- supplied.
--
--
gets :: (Monoid w, Monad m) => (s -> a) -> RWST r w s m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: Monoid w => CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current state on entering the continuation.
liftCallCC' :: Monoid w => CallCC m (a, s, w) (b, s, w) -> CallCC (RWST r w s m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, s, w) -> Catch e (RWST r w s m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.Monad m) => GHC.Base.Monad (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, Control.Monad.Fail.MonadFail m) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance (GHC.Base.Monoid w, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance GHC.Base.Monoid w => Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.RWS.Strict.RWST r w s)
instance (GHC.Base.Monoid w, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.RWS.Strict.RWST r w s m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.RWS.Strict.RWST r w s m)
-- | Declaration of the ReaderT monad transformer, which adds a
-- static environment to a given monad.
--
-- If the computation is to modify the stored information, use
-- Control.Monad.Trans.State instead.
module Control.Monad.Trans.Reader
-- | 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
-- | Constructor for computations in the reader monad (equivalent to
-- asks).
reader :: Monad m => (r -> a) -> ReaderT r m a
-- | 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 m 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 :: (r' -> r) -> ReaderT r m a -> ReaderT r' m a
-- | Fetch the value of the environment.
ask :: Monad m => ReaderT r m r
-- | Execute a computation in a modified environment (a specialization of
-- withReaderT).
--
--
local :: (r -> r) -> ReaderT r m a -> ReaderT r m a
-- | Retrieve a function of the current environment.
--
--
asks :: Monad m => (r -> a) -> ReaderT r m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: CallCC m a b -> CallCC (ReaderT r m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m a -> Catch e (ReaderT r m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Reader.ReaderT r m)
instance GHC.Base.Applicative m => GHC.Base.Applicative (Control.Monad.Trans.Reader.ReaderT r m)
instance GHC.Base.Alternative m => GHC.Base.Alternative (Control.Monad.Trans.Reader.ReaderT r m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Reader.ReaderT r m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Reader.ReaderT r m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Monad.Trans.Reader.ReaderT r m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Reader.ReaderT r m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Reader.ReaderT r)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Reader.ReaderT r m)
instance Control.Monad.Zip.MonadZip m => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Reader.ReaderT r m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Reader.ReaderT r m)
-- | Selection monad transformer, modelling search algorithms.
--
--
module Control.Monad.Trans.Select
-- | Selection monad.
type Select r = SelectT r Identity
-- | Constructor for computations in the selection monad.
select :: ((a -> r) -> a) -> Select r a
-- | Runs a Select computation with a function for evaluating
-- answers to select a particular answer. (The inverse of select.)
runSelect :: Select r a -> (a -> r) -> a
-- | Apply a function to transform the result of a selection computation.
--
--
mapSelect :: (a -> a) -> Select r a -> Select r a
-- | Selection monad transformer.
--
-- SelectT is not a functor on the category of monads, and many
-- operations cannot be lifted through it.
newtype SelectT r m a
SelectT :: ((a -> m r) -> m a) -> SelectT r m a
-- | Runs a SelectT computation with a function for evaluating
-- answers to select a particular answer. (The inverse of select.)
runSelectT :: SelectT r m a -> (a -> m r) -> m a
-- | Apply a function to transform the result of a selection computation.
-- This has a more restricted type than the map operations for
-- other monad transformers, because SelectT does not define a
-- functor in the category of monads.
--
--
mapSelectT :: (m a -> m a) -> SelectT r m a -> SelectT r m a
-- | Convert a selection computation to a continuation-passing computation.
selectToContT :: Monad m => SelectT r m a -> ContT r m a
-- | Deprecated name for selectToContT.
-- | Deprecated: Use selectToContT instead
selectToCont :: Monad m => SelectT r m a -> ContT r m a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Select.SelectT r m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Select.SelectT r m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.Select.SelectT r m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Select.SelectT r m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Select.SelectT r m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Monad.Trans.Select.SelectT r m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Select.SelectT r)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Select.SelectT r m)
-- | Lazy state monads, passing an updatable state through a computation.
-- See below for examples.
--
-- Some computations may not require the full power of state
-- transformers:
--
--
--
-- In this version, sequencing of computations is lazy, so that for
-- example the following produces a usable result:
--
--
-- evalState (sequence $ repeat $ do { n <- get; put (n*2); return n }) 1
--
--
-- For a strict version with the same interface, see
-- Control.Monad.Trans.State.Strict.
module Control.Monad.Trans.State.Lazy
-- | 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
-- | Construct a state monad computation from a function. (The inverse of
-- runState.)
state :: Monad m => (s -> (a, s)) -> StateT s m a
-- | 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:
--
--
-- - s - The state.
-- - m - The inner monad.
--
--
-- The return function leaves the state unchanged, while
-- >>= uses the final state of the first computation as
-- the initial state of the second.
newtype StateT s m a
StateT :: (s -> m (a, s)) -> StateT s m 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 :: (s -> s) -> StateT s m a -> StateT s m a
-- | Fetch the current value of the state within the monad.
get :: Monad m => StateT s m s
-- | put s sets the state within the monad to s.
put :: Monad m => s -> StateT s m ()
-- | modify f is an action that updates the state to the
-- result of applying f to the current state.
--
--
modify :: Monad m => (s -> s) -> StateT s m ()
-- | A variant of modify in which the computation is strict in the
-- new state.
--
--
modify' :: Monad m => (s -> s) -> StateT s m ()
-- | Get a specific component of the state, using a projection function
-- supplied.
--
--
gets :: Monad m => (s -> a) -> StateT s m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: CallCC m (a, s) (b, s) -> CallCC (StateT s m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current state on entering the continuation. It does
-- not satisfy the uniformity property (see
-- Control.Monad.Signatures).
liftCallCC' :: CallCC m (a, s) (b, s) -> CallCC (StateT s m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, s) -> Catch e (StateT s m) a
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (a, s) -> Listen w (StateT s m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (a, s) -> Pass w (StateT s m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.State.Lazy.StateT s m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.State.Lazy.StateT s m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.State.Lazy.StateT s m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.State.Lazy.StateT s m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.State.Lazy.StateT s m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Monad.Trans.State.Lazy.StateT s m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.State.Lazy.StateT s m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.State.Lazy.StateT s)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.State.Lazy.StateT s m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.State.Lazy.StateT s m)
-- | State monads, passing an updatable state through a computation.
--
-- Some computations may not require the full power of state
-- transformers:
--
--
--
-- This version is lazy; for a strict version, see
-- Control.Monad.Trans.State.Strict, which has the same interface.
module Control.Monad.Trans.State
-- | Strict state monads, passing an updatable state through a computation.
-- See below for examples.
--
-- Some computations may not require the full power of state
-- transformers:
--
--
--
-- In this version, sequencing of computations is strict (but
-- computations are not strict in the state unless you force it with
-- seq or the like). For a lazy version with the same interface,
-- see Control.Monad.Trans.State.Lazy.
module Control.Monad.Trans.State.Strict
-- | 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
-- | Construct a state monad computation from a function. (The inverse of
-- runState.)
state :: Monad m => (s -> (a, s)) -> StateT s m a
-- | 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:
--
--
-- - s - The state.
-- - m - The inner monad.
--
--
-- The return function leaves the state unchanged, while
-- >>= uses the final state of the first computation as
-- the initial state of the second.
newtype StateT s m a
StateT :: (s -> m (a, s)) -> StateT s m 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 :: (s -> s) -> StateT s m a -> StateT s m a
-- | Fetch the current value of the state within the monad.
get :: Monad m => StateT s m s
-- | put s sets the state within the monad to s.
put :: Monad m => s -> StateT s m ()
-- | modify f is an action that updates the state to the
-- result of applying f to the current state.
--
--
modify :: Monad m => (s -> s) -> StateT s m ()
-- | A variant of modify in which the computation is strict in the
-- new state.
--
--
modify' :: Monad m => (s -> s) -> StateT s m ()
-- | Get a specific component of the state, using a projection function
-- supplied.
--
--
gets :: Monad m => (s -> a) -> StateT s m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: CallCC m (a, s) (b, s) -> CallCC (StateT s m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current state on entering the continuation. It does
-- not satisfy the uniformity property (see
-- Control.Monad.Signatures).
liftCallCC' :: CallCC m (a, s) (b, s) -> CallCC (StateT s m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, s) -> Catch e (StateT s m) a
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (a, s) -> Listen w (StateT s m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (a, s) -> Pass w (StateT s m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.State.Strict.StateT s m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.State.Strict.StateT s m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.State.Strict.StateT s m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.State.Strict.StateT s m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.State.Strict.StateT s m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Control.Monad.Trans.State.Strict.StateT s m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.State.Strict.StateT s m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.State.Strict.StateT s)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.State.Strict.StateT s m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.State.Strict.StateT s m)
-- | The strict WriterT monad transformer, which adds collection of
-- outputs (such as a count or string output) to a given monad.
--
-- This monad transformer provides only limited access to the output
-- during the computation. For more general access, use
-- Control.Monad.Trans.State instead.
--
-- This version builds its output strictly and uses
-- continuation-passing-style to achieve constant space usage. This
-- transformer can be used as a drop-in replacement for
-- Control.Monad.Trans.Writer.Strict.
module Control.Monad.Trans.Writer.CPS
-- | 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
-- | Construct a writer computation from a (result, output) pair. (The
-- inverse of runWriter.)
writer :: (Monoid w, Monad m) => (a, w) -> WriterT w m a
-- | 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:
--
--
-- - w - the output to accumulate.
-- - m - The inner monad.
--
--
-- The return function produces the output mempty, while
-- >>= combines the outputs of the subcomputations using
-- mappend.
data WriterT w m a
-- | Construct a writer computation from a (result, output) computation.
-- (The inverse of runWriterT.)
writerT :: (Functor m, Monoid w) => m (a, w) -> WriterT w m a
-- | Unwrap a writer computation. (The inverse of writerT.)
runWriterT :: Monoid w => WriterT w m a -> m (a, w)
-- | 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
-- | tell w is an action that produces the output
-- w.
tell :: (Monoid w, Monad m) => w -> WriterT w m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: (Monoid w, Monad m) => WriterT w m a -> WriterT w m (a, w)
-- | 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 :: (Monoid w, Monad m) => (w -> b) -> WriterT w m a -> WriterT w m (a, b)
-- | 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 :: (Monoid w, Monoid w', Monad m) => WriterT w m (a, w -> w') -> WriterT w' m a
-- | 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 :: (Monoid w, Monad m) => (w -> w) -> WriterT w m a -> WriterT w m a
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original state on entering the continuation.
liftCallCC :: CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, w) -> Catch e (WriterT w m) a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance (GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance (GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Writer.CPS.WriterT w m)
instance Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Writer.CPS.WriterT w)
instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Writer.CPS.WriterT w m)
-- | The lazy WriterT monad transformer, which adds collection of
-- outputs (such as a count or string output) to a given monad.
--
-- This monad transformer provides only limited access to the output
-- during the computation. For more general access, use
-- Control.Monad.Trans.State instead.
--
-- This version builds its output lazily; for a constant-space version
-- with almost the same interface, see
-- Control.Monad.Trans.Writer.CPS.
module Control.Monad.Trans.Writer.Lazy
-- | 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
-- | Construct a writer computation from a (result, output) pair. (The
-- inverse of runWriter.)
writer :: Monad m => (a, w) -> WriterT w m a
-- | 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:
--
--
-- - w - the output to accumulate.
-- - m - The inner monad.
--
--
-- 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 m 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
-- | tell w is an action that produces the output
-- w.
tell :: Monad m => w -> WriterT w m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: Monad m => WriterT w m a -> WriterT w m (a, w)
-- | 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 :: Monad m => (w -> b) -> WriterT w m a -> WriterT w m (a, b)
-- | 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 :: Monad m => WriterT w m (a, w -> w) -> WriterT w m a
-- | 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 :: Monad m => (w -> w) -> WriterT w m a -> WriterT w m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: Monoid w => CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, w) -> Catch e (WriterT w m) a
instance (GHC.Classes.Eq w, Data.Functor.Classes.Eq1 m) => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Classes.Ord w, Data.Functor.Classes.Ord1 m) => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Read.Read w, Data.Functor.Classes.Read1 m) => Data.Functor.Classes.Read1 (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Show.Show w, Data.Functor.Classes.Show1 m) => Data.Functor.Classes.Show1 (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Classes.Eq w, Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Writer.Lazy.WriterT w m a)
instance (GHC.Classes.Ord w, Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Writer.Lazy.WriterT w m a)
instance (GHC.Read.Read w, Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Writer.Lazy.WriterT w m a)
instance (GHC.Show.Show w, Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Writer.Lazy.WriterT w m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Writer.Lazy.WriterT w f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Writer.Lazy.WriterT w f)
instance (GHC.Base.Monoid w, GHC.Base.Applicative m) => GHC.Base.Applicative (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.Alternative m) => GHC.Base.Alternative (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.Monad m) => GHC.Base.Monad (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Fail.MonadFail m) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance GHC.Base.Monoid w => Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Writer.Lazy.WriterT w)
instance (GHC.Base.Monoid w, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Zip.MonadZip m) => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Writer.Lazy.WriterT w m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Writer.Lazy.WriterT w m)
-- | The WriterT monad transformer. This version builds its output lazily;
-- for a constant-space version with almost the same interface, see
-- Control.Monad.Trans.Writer.CPS.
module Control.Monad.Trans.Writer
-- | The lazy AccumT monad transformer, which adds accumulation
-- capabilities (such as declarations or document patches) to a given
-- monad.
--
-- This monad transformer provides append-only accumulation during the
-- computation. For more general access, use
-- Control.Monad.Trans.State instead.
module Control.Monad.Trans.Accum
-- | An accumulation 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 Accum w = AccumT w Identity
-- | Construct an accumulation computation from a (result, output) pair.
-- (The inverse of runAccum.)
accum :: Monad m => (w -> (a, w)) -> AccumT w m a
-- | Unwrap an accumulation computation as a (result, output) pair. (The
-- inverse of accum.)
runAccum :: Accum w a -> w -> (a, w)
-- | Extract the output from an accumulation computation.
--
--
execAccum :: Accum w a -> w -> w
-- | Evaluate an accumulation computation with the given initial output
-- history and return the final value, discarding the final output.
--
--
evalAccum :: Monoid w => Accum w a -> w -> a
-- | Map both the return value and output of a computation using the given
-- function.
--
--
mapAccum :: ((a, w) -> (b, w)) -> Accum w a -> Accum w b
-- | An accumulation monad parameterized by:
--
--
-- - w - the output to accumulate.
-- - m - The inner monad.
--
--
-- The return function produces the output mempty, while
-- >>= combines the outputs of the subcomputations using
-- mappend.
--
-- This monad transformer is similar to both state and writer monad
-- transformers. Thus it can be seen as
--
--
-- - a restricted append-only version of a state monad transformer
-- or
-- - a writer monad transformer with the extra ability to read all
-- previous output.
--
newtype AccumT w m a
AccumT :: (w -> m (a, w)) -> AccumT w m a
-- | Unwrap an accumulation computation.
runAccumT :: AccumT w m a -> w -> m (a, w)
-- | Extract the output from an accumulation computation.
--
--
execAccumT :: Monad m => AccumT w m a -> w -> m w
-- | Evaluate an accumulation computation with the given initial output
-- history and return the final value, discarding the final output.
--
--
evalAccumT :: (Monad m, Monoid w) => AccumT w m a -> w -> m a
-- | Map both the return value and output of a computation using the given
-- function.
--
--
mapAccumT :: (m (a, w) -> n (b, w)) -> AccumT w m a -> AccumT w n b
-- | look is an action that fetches all the previously
-- accumulated output.
look :: (Monoid w, Monad m) => AccumT w m w
-- | look is an action that retrieves a function of the
-- previously accumulated output.
looks :: (Monoid w, Monad m) => (w -> a) -> AccumT w m a
-- | add w is an action that produces the output
-- w.
add :: Monad m => w -> AccumT w m ()
-- | Uniform lifting of a callCC operation to the new monad. This
-- version rolls back to the original output history on entering the
-- continuation.
liftCallCC :: CallCC m (a, w) (b, w) -> CallCC (AccumT w m) a b
-- | In-situ lifting of a callCC operation to the new monad. This
-- version uses the current output history on entering the continuation.
-- It does not satisfy the uniformity property (see
-- Control.Monad.Signatures).
liftCallCC' :: CallCC m (a, w) (b, w) -> CallCC (AccumT w m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, w) -> Catch e (AccumT w m) a
-- | Lift a listen operation to the new monad.
liftListen :: Monad m => Listen w m (a, s) -> Listen w (AccumT s m) a
-- | Lift a pass operation to the new monad.
liftPass :: Monad m => Pass w m (a, s) -> Pass w (AccumT s m) a
-- | Convert a read-only computation into an accumulation computation.
readerToAccumT :: (Functor m, Monoid w) => ReaderT w m a -> AccumT w m a
-- | Convert a writer computation into an accumulation computation.
writerToAccumT :: WriterT w m a -> AccumT w m a
-- | Convert an accumulation (append-only) computation into a fully
-- stateful computation.
accumToStateT :: (Functor m, Monoid s) => AccumT s m a -> StateT s m a
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Applicative (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.Alternative (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.Monad m) => GHC.Base.Monad (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, Control.Monad.Fail.MonadFail m) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.Accum.AccumT w m)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Accum.AccumT w m)
instance GHC.Base.Monoid w => Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Accum.AccumT w)
instance (GHC.Base.Monoid w, GHC.Base.Functor m, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Accum.AccumT w m)
-- | The strict WriterT monad transformer, which adds collection of
-- outputs (such as a count or string output) to a given monad.
--
-- This monad transformer provides only limited access to the output
-- during the computation. For more general access, use
-- Control.Monad.Trans.State instead.
--
-- This version builds its output strictly; for a lazy version with the
-- same interface, see Control.Monad.Trans.Writer.Lazy. Although
-- the output is built strictly, it is not possible to achieve constant
-- space behaviour with this transformer: for that, use
-- Control.Monad.Trans.Writer.CPS instead.
module Control.Monad.Trans.Writer.Strict
-- | 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
-- | Construct a writer computation from a (result, output) pair. (The
-- inverse of runWriter.)
writer :: Monad m => (a, w) -> WriterT w m a
-- | 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:
--
--
-- - w - the output to accumulate.
-- - m - The inner monad.
--
--
-- 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 m 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
-- | tell w is an action that produces the output
-- w.
tell :: Monad m => w -> WriterT w m ()
-- | listen m is an action that executes the action
-- m and adds its output to the value of the computation.
--
--
listen :: Monad m => WriterT w m a -> WriterT w m (a, w)
-- | 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 :: Monad m => (w -> b) -> WriterT w m a -> WriterT w m (a, b)
-- | 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 :: Monad m => WriterT w m (a, w -> w) -> WriterT w m a
-- | 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 :: Monad m => (w -> w) -> WriterT w m a -> WriterT w m a
-- | Lift a callCC operation to the new monad.
liftCallCC :: Monoid w => CallCC m (a, w) (b, w) -> CallCC (WriterT w m) a b
-- | Lift a catchE operation to the new monad.
liftCatch :: Catch e m (a, w) -> Catch e (WriterT w m) a
instance (GHC.Classes.Eq w, Data.Functor.Classes.Eq1 m) => Data.Functor.Classes.Eq1 (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Classes.Ord w, Data.Functor.Classes.Ord1 m) => Data.Functor.Classes.Ord1 (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Read.Read w, Data.Functor.Classes.Read1 m) => Data.Functor.Classes.Read1 (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Show.Show w, Data.Functor.Classes.Show1 m) => Data.Functor.Classes.Show1 (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Classes.Eq w, Data.Functor.Classes.Eq1 m, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Monad.Trans.Writer.Strict.WriterT w m a)
instance (GHC.Classes.Ord w, Data.Functor.Classes.Ord1 m, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Monad.Trans.Writer.Strict.WriterT w m a)
instance (GHC.Read.Read w, Data.Functor.Classes.Read1 m, GHC.Read.Read a) => GHC.Read.Read (Control.Monad.Trans.Writer.Strict.WriterT w m a)
instance (GHC.Show.Show w, Data.Functor.Classes.Show1 m, GHC.Show.Show a) => GHC.Show.Show (Control.Monad.Trans.Writer.Strict.WriterT w m a)
instance GHC.Base.Functor m => GHC.Base.Functor (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Monad.Trans.Writer.Strict.WriterT w f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Monad.Trans.Writer.Strict.WriterT w f)
instance (GHC.Base.Monoid w, GHC.Base.Applicative m) => GHC.Base.Applicative (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.Alternative m) => GHC.Base.Alternative (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.Monad m) => GHC.Base.Monad (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Fail.MonadFail m) => Control.Monad.Fail.MonadFail (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, GHC.Base.MonadPlus m) => GHC.Base.MonadPlus (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Fix.MonadFix m) => Control.Monad.Fix.MonadFix (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance GHC.Base.Monoid w => Control.Monad.Trans.Class.MonadTrans (Control.Monad.Trans.Writer.Strict.WriterT w)
instance (GHC.Base.Monoid w, Control.Monad.IO.Class.MonadIO m) => Control.Monad.IO.Class.MonadIO (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance (GHC.Base.Monoid w, Control.Monad.Zip.MonadZip m) => Control.Monad.Zip.MonadZip (Control.Monad.Trans.Writer.Strict.WriterT w m)
instance Data.Functor.Contravariant.Contravariant m => Data.Functor.Contravariant.Contravariant (Control.Monad.Trans.Writer.Strict.WriterT w m)
-- | The constant functor.
module Data.Functor.Constant
-- | Constant functor.
newtype Constant a b
Constant :: a -> Constant a b
[getConstant] :: Constant a b -> a
instance forall a k (b :: k). GHC.Classes.Ord a => GHC.Classes.Ord (Data.Functor.Constant.Constant a b)
instance forall a k (b :: k). GHC.Classes.Eq a => GHC.Classes.Eq (Data.Functor.Constant.Constant a b)
instance forall k a (b :: k). GHC.Read.Read a => GHC.Read.Read (Data.Functor.Constant.Constant a b)
instance forall k a (b :: k). GHC.Show.Show a => GHC.Show.Show (Data.Functor.Constant.Constant a b)
instance Data.Functor.Classes.Eq2 Data.Functor.Constant.Constant
instance Data.Functor.Classes.Ord2 Data.Functor.Constant.Constant
instance Data.Functor.Classes.Read2 Data.Functor.Constant.Constant
instance Data.Functor.Classes.Show2 Data.Functor.Constant.Constant
instance GHC.Classes.Eq a => Data.Functor.Classes.Eq1 (Data.Functor.Constant.Constant a)
instance GHC.Classes.Ord a => Data.Functor.Classes.Ord1 (Data.Functor.Constant.Constant a)
instance GHC.Read.Read a => Data.Functor.Classes.Read1 (Data.Functor.Constant.Constant a)
instance GHC.Show.Show a => Data.Functor.Classes.Show1 (Data.Functor.Constant.Constant a)
instance GHC.Base.Functor (Data.Functor.Constant.Constant a)
instance Data.Foldable.Foldable (Data.Functor.Constant.Constant a)
instance Data.Traversable.Traversable (Data.Functor.Constant.Constant a)
instance forall k a (b :: k). GHC.Base.Semigroup a => GHC.Base.Semigroup (Data.Functor.Constant.Constant a b)
instance GHC.Base.Monoid a => GHC.Base.Applicative (Data.Functor.Constant.Constant a)
instance forall k a (b :: k). GHC.Base.Monoid a => GHC.Base.Monoid (Data.Functor.Constant.Constant a b)
instance Data.Bifunctor.Bifunctor Data.Functor.Constant.Constant
instance Data.Bifoldable.Bifoldable Data.Functor.Constant.Constant
instance Data.Bitraversable.Bitraversable Data.Functor.Constant.Constant
instance Data.Functor.Contravariant.Contravariant (Data.Functor.Constant.Constant a)
-- | Adding a new kind of pure computation to an applicative functor.
module Control.Applicative.Lift
-- | Applicative functor formed by adding pure computations to a given
-- applicative functor.
data Lift f a
Pure :: a -> Lift f a
Other :: f a -> Lift f a
-- | Projection to the other functor.
unLift :: Applicative f => Lift f a -> f a
-- | Apply a transformation to the other computation.
mapLift :: (f a -> g a) -> Lift f a -> Lift g a
-- | Eliminator for Lift.
--
--
elimLift :: (a -> r) -> (f a -> r) -> Lift f a -> r
-- | An applicative functor that collects a monoid (e.g. lists) of errors.
-- A sequence of computations fails if any of its components do, but
-- unlike monads made with ExceptT from
-- Control.Monad.Trans.Except, these computations continue after
-- an error, collecting all the errors.
--
--
type Errors e = Lift (Constant e)
-- | Extractor for computations with accumulating errors.
--
--
runErrors :: Errors e a -> Either e a
-- | Report an error.
failure :: e -> Errors e a
-- | Convert from Either to Errors (inverse of
-- runErrors).
eitherToErrors :: Either e a -> Errors e a
instance Data.Functor.Classes.Eq1 f => Data.Functor.Classes.Eq1 (Control.Applicative.Lift.Lift f)
instance Data.Functor.Classes.Ord1 f => Data.Functor.Classes.Ord1 (Control.Applicative.Lift.Lift f)
instance Data.Functor.Classes.Read1 f => Data.Functor.Classes.Read1 (Control.Applicative.Lift.Lift f)
instance Data.Functor.Classes.Show1 f => Data.Functor.Classes.Show1 (Control.Applicative.Lift.Lift f)
instance (Data.Functor.Classes.Eq1 f, GHC.Classes.Eq a) => GHC.Classes.Eq (Control.Applicative.Lift.Lift f a)
instance (Data.Functor.Classes.Ord1 f, GHC.Classes.Ord a) => GHC.Classes.Ord (Control.Applicative.Lift.Lift f a)
instance (Data.Functor.Classes.Read1 f, GHC.Read.Read a) => GHC.Read.Read (Control.Applicative.Lift.Lift f a)
instance (Data.Functor.Classes.Show1 f, GHC.Show.Show a) => GHC.Show.Show (Control.Applicative.Lift.Lift f a)
instance GHC.Base.Functor f => GHC.Base.Functor (Control.Applicative.Lift.Lift f)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Control.Applicative.Lift.Lift f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Control.Applicative.Lift.Lift f)
instance GHC.Base.Applicative f => GHC.Base.Applicative (Control.Applicative.Lift.Lift f)
instance GHC.Base.Alternative f => GHC.Base.Alternative (Control.Applicative.Lift.Lift f)
-- | Making functors whose elements are notionally in the reverse order
-- from the original functor.
module Data.Functor.Reverse
-- | The same functor, but with Foldable and Traversable
-- instances that process the elements in the reverse order.
newtype Reverse f a
Reverse :: f a -> Reverse f a
[getReverse] :: Reverse f a -> f a
instance Data.Functor.Classes.Eq1 f => Data.Functor.Classes.Eq1 (Data.Functor.Reverse.Reverse f)
instance Data.Functor.Classes.Ord1 f => Data.Functor.Classes.Ord1 (Data.Functor.Reverse.Reverse f)
instance Data.Functor.Classes.Read1 f => Data.Functor.Classes.Read1 (Data.Functor.Reverse.Reverse f)
instance Data.Functor.Classes.Show1 f => Data.Functor.Classes.Show1 (Data.Functor.Reverse.Reverse f)
instance (Data.Functor.Classes.Eq1 f, GHC.Classes.Eq a) => GHC.Classes.Eq (Data.Functor.Reverse.Reverse f a)
instance (Data.Functor.Classes.Ord1 f, GHC.Classes.Ord a) => GHC.Classes.Ord (Data.Functor.Reverse.Reverse f a)
instance (Data.Functor.Classes.Read1 f, GHC.Read.Read a) => GHC.Read.Read (Data.Functor.Reverse.Reverse f a)
instance (Data.Functor.Classes.Show1 f, GHC.Show.Show a) => GHC.Show.Show (Data.Functor.Reverse.Reverse f a)
instance GHC.Base.Functor f => GHC.Base.Functor (Data.Functor.Reverse.Reverse f)
instance GHC.Base.Applicative f => GHC.Base.Applicative (Data.Functor.Reverse.Reverse f)
instance GHC.Base.Alternative f => GHC.Base.Alternative (Data.Functor.Reverse.Reverse f)
instance GHC.Base.Monad m => GHC.Base.Monad (Data.Functor.Reverse.Reverse m)
instance Control.Monad.Fail.MonadFail m => Control.Monad.Fail.MonadFail (Data.Functor.Reverse.Reverse m)
instance GHC.Base.MonadPlus m => GHC.Base.MonadPlus (Data.Functor.Reverse.Reverse m)
instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Data.Functor.Reverse.Reverse f)
instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Data.Functor.Reverse.Reverse f)
instance Data.Functor.Contravariant.Contravariant f => Data.Functor.Contravariant.Contravariant (Data.Functor.Reverse.Reverse f)