-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Extensible optionally-pure exceptions -- -- Extensible optionally-pure exceptions. @package exceptions @version 0.10.4 -- | This module supports monads that can throw extensible exceptions. The -- exceptions are the very same from Control.Exception, and the -- operations offered very similar, but here they are not limited to -- IO. -- -- This code is in the style of both transformers and mtl, and is -- compatible with them, though doesn't mimic the module structure or -- offer the complete range of features in those packages. -- -- This is very similar to ErrorT and MonadError, but -- based on features of Control.Exception. In particular, it -- handles the complex case of asynchronous exceptions by including -- mask in the typeclass. Note that the extensible exceptions -- feature relies on the RankNTypes language extension. module Control.Monad.Catch -- | A class for monads in which exceptions may be thrown. -- -- Instances should obey the following law: -- --
-- throwM e >> x = throwM e ---- -- In other words, throwing an exception short-circuits the rest of the -- monadic computation. class Monad m => MonadThrow m -- | Throw an exception. Note that this throws when this action is run in -- the monad m, not when it is applied. It is a generalization -- of Control.Exception's throwIO. -- -- Should satisfy the law: -- --
-- throwM e >> f = throwM e --throwM :: (MonadThrow m, Exception e) => e -> m a -- | A class for monads which allow exceptions to be caught, in particular -- exceptions which were thrown by throwM. -- -- Instances should obey the following law: -- --
-- catch (throwM e) f = f e ---- -- Note that the ability to catch an exception does not guarantee -- that we can deal with all possible exit points from a computation. -- Some monads, such as continuation-based stacks, allow for more than -- just a success/failure strategy, and therefore catch -- cannot be used by those monads to properly implement a function -- such as finally. For more information, see MonadMask. class MonadThrow m => MonadCatch m -- | Provide a handler for exceptions thrown during execution of the first -- action. Note that type of the type of the argument to the handler will -- constrain which exceptions are caught. See Control.Exception's -- catch. catch :: (MonadCatch m, Exception e) => m a -> (e -> m a) -> m a -- | A class for monads which provide for the ability to account for all -- possible exit points from a computation, and to mask asynchronous -- exceptions. Continuation-based monads are invalid instances of this -- class. -- -- Instances should ensure that, in the following code: -- --
-- fg = f `finally` g ---- -- The action g is called regardless of what occurs within -- f, including async exceptions. Some monads allow f -- to abort the computation via other effects than throwing an exception. -- For simplicity, we will consider aborting and throwing an exception to -- be two forms of "throwing an error". -- -- If f and g both throw an error, the error thrown by -- fg depends on which errors we're talking about. In a monad -- transformer stack, the deeper layers override the effects of the inner -- layers; for example, ExceptT e1 (Except e2) a represents a -- value of type Either e2 (Either e1 a), so throwing both an -- e1 and an e2 will result in Left e2. If -- f and g both throw an error from the same layer, -- instances should ensure that the error from g wins. -- -- Effects other than throwing an error are also overriden by the deeper -- layers. For example, StateT s Maybe a represents a value of -- type s -> Maybe (a, s), so if an error thrown from -- f causes this function to return Nothing, any -- changes to the state which f also performed will be erased. -- As a result, g will see the state as it was before -- f. Once g completes, f's error will be -- rethrown, so g' state changes will be erased as well. This is -- the normal interaction between effects in a monad transformer stack. -- -- By contrast, lifted-base's version of finally always -- discards all of g's non-IO effects, and g never sees -- any of f's non-IO effects, regardless of the layer ordering -- and regardless of whether f throws an error. This is not the -- result of interacting effects, but a consequence of -- MonadBaseControl's approach. class MonadCatch m => MonadMask m -- | Runs an action with asynchronous exceptions disabled. The action is -- provided a method for restoring the async. environment to what it was -- at the mask call. See Control.Exception's mask. mask :: MonadMask m => ((forall a. m a -> m a) -> m b) -> m b -- | Like mask, but the masked computation is not interruptible (see -- Control.Exception's uninterruptibleMask. WARNING: Only -- use if you need to mask exceptions around an interruptible operation -- AND you can guarantee the interruptible operation will only block for -- a short period of time. Otherwise you render the program/thread -- unresponsive and/or unkillable. uninterruptibleMask :: MonadMask m => ((forall a. m a -> m a) -> m b) -> m b -- | A generalized version of bracket which uses ExitCase to -- distinguish the different exit cases, and returns the values of both -- the use and release actions. In practice, this extra -- information is rarely needed, so it is often more convenient to use -- one of the simpler functions which are defined in terms of this one, -- such as bracket, finally, onError, and -- bracketOnError. -- -- This function exists because in order to thread their effects through -- the execution of bracket, monad transformers need values to be -- threaded from use to release and from -- release to the output value. -- -- NOTE This method was added in version 0.9.0 of this library. -- Previously, implementation of functions like bracket and -- finally in this module were based on the mask and -- uninterruptibleMask functions only, disallowing some classes of -- tranformers from having MonadMask instances (notably -- multi-exit-point transformers like ExceptT). If you are a -- library author, you'll now need to provide an implementation for this -- method. The StateT implementation demonstrates most of the -- subtleties: -- --
-- generalBracket acquire release use = StateT $ s0 -> do -- ((b, _s2), (c, s3)) <- generalBracket -- (runStateT acquire s0) -- ((resource, s1) exitCase -> case exitCase of -- ExitCaseSuccess (b, s2) -> runStateT (release resource (ExitCaseSuccess b)) s2 -- -- -- In the two other cases, the base monad overrides use's state -- -- changes and the state reverts to s1. -- ExitCaseException e -> runStateT (release resource (ExitCaseException e)) s1 -- ExitCaseAbort -> runStateT (release resource ExitCaseAbort) s1 -- ) -- ((resource, s1) -> runStateT (use resource) s1) -- return ((b, c), s3) ---- -- The StateT s m implementation of generalBracket -- delegates to the m implementation of generalBracket. -- The acquire, use, and release arguments -- given to StateT's implementation produce actions of type -- StateT s m a, StateT s m b, and StateT s m -- c. In order to run those actions in the base monad, we need to -- call runStateT, from which we obtain actions of type m -- (a, s), m (b, s), and m (c, s). Since each -- action produces the next state, it is important to feed the state -- produced by the previous action to the next action. -- -- In the ExitCaseSuccess case, the state starts at s0, -- flows through acquire to become s1, flows through -- use to become s2, and finally flows through -- release to become s3. In the other two cases, -- release does not receive the value s2, so its action -- cannot see the state changes performed by use. This is fine, -- because in those two cases, an error was thrown in the base monad, so -- as per the usual interaction between effects in a monad transformer -- stack, those state changes get reverted. So we start from s1 -- instead. -- -- Finally, the m implementation of generalBracket -- returns the pairs (b, s) and (c, s). For monad -- transformers other than StateT, this will be some other type -- representing the effects and values performed and returned by the -- use and release actions. The effect part of the -- use result, in this case _s2, usually needs to be -- discarded, since those effects have already been incorporated in the -- release action. -- -- The only effect which is intentionally not incorporated in the -- release action is the effect of throwing an error. In that -- case, the error must be re-thrown. One subtlety which is easy to miss -- is that in the case in which use and release both -- throw an error, the error from release should take priority. -- Here is an implementation for ExceptT which demonstrates how -- to do this. -- --
-- generalBracket acquire release use = ExceptT $ do -- (eb, ec) <- generalBracket -- (runExceptT acquire) -- (eresource exitCase -> case eresource of -- Left e -> return (Left e) -- nothing to release, acquire didn't succeed -- Right resource -> case exitCase of -- ExitCaseSuccess (Right b) -> runExceptT (release resource (ExitCaseSuccess b)) -- ExitCaseException e -> runExceptT (release resource (ExitCaseException e)) -- _ -> runExceptT (release resource ExitCaseAbort)) -- (either (return . Left) (runExceptT . use)) -- return $ do -- -- The order in which we perform those two Either effects determines -- -- which error will win if they are both Lefts. We want the error from -- -- release to win. -- c <- ec -- b <- eb -- return (b, c) --generalBracket :: MonadMask m => m a -> (a -> ExitCase b -> m c) -> (a -> m b) -> m (b, c) -- | A MonadMask computation may either succeed with a value, abort -- with an exception, or abort for some other reason. For example, in -- ExceptT e IO you can use throwM to abort with an -- exception (ExitCaseException) or throwE to abort with a -- value of type e (ExitCaseAbort). data ExitCase a ExitCaseSuccess :: a -> ExitCase a ExitCaseException :: SomeException -> ExitCase a ExitCaseAbort :: ExitCase a -- | Like mask, but does not pass a restore action to the -- argument. mask_ :: MonadMask m => m a -> m a -- | Like uninterruptibleMask, but does not pass a restore -- action to the argument. uninterruptibleMask_ :: MonadMask m => m a -> m a -- | Catches all exceptions, and somewhat defeats the purpose of the -- extensible exception system. Use sparingly. -- -- NOTE This catches all exceptions, but if the monad -- supports other ways of aborting the computation, those other kinds of -- errors will not be caught. catchAll :: MonadCatch m => m a -> (SomeException -> m a) -> m a -- | Catch all IOError (eqv. IOException) exceptions. Still -- somewhat too general, but better than using catchAll. See -- catchIf for an easy way of catching specific IOErrors -- based on the predicates in System.IO.Error. catchIOError :: MonadCatch m => m a -> (IOError -> m a) -> m a -- | A more generalized way of determining which exceptions to catch at run -- time. catchJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> (b -> m a) -> m a -- | Catch exceptions only if they pass some predicate. Often useful with -- the predicates for testing IOError values in -- System.IO.Error. catchIf :: (MonadCatch m, Exception e) => (e -> Bool) -> m a -> (e -> m a) -> m a -- | Generalized version of Handler data Handler m a Handler :: (e -> m a) -> Handler m a -- | Catches different sorts of exceptions. See Control.Exception's -- catches catches :: (Foldable f, MonadCatch m) => m a -> f (Handler m a) -> m a -- | Flipped catch. See Control.Exception's handle. handle :: (MonadCatch m, Exception e) => (e -> m a) -> m a -> m a -- | Flipped catchAll handleAll :: MonadCatch m => (SomeException -> m a) -> m a -> m a -- | Flipped catchIOError handleIOError :: MonadCatch m => (IOError -> m a) -> m a -> m a -- | Flipped catchJust. See Control.Exception's -- handleJust. handleJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> (b -> m a) -> m a -> m a -- | Flipped catchIf handleIf :: (MonadCatch m, Exception e) => (e -> Bool) -> (e -> m a) -> m a -> m a -- | Similar to catch, but returns an Either result. See -- Control.Exception's try. try :: (MonadCatch m, Exception e) => m a -> m (Either e a) -- | A variant of try that takes an exception predicate to select -- which exceptions are caught. See Control.Exception's -- tryJust tryJust :: (MonadCatch m, Exception e) => (e -> Maybe b) -> m a -> m (Either b a) -- | Run an action only if an exception is thrown in the main action. The -- exception is not caught, simply rethrown. -- -- NOTE The action is only run if an exception is thrown. -- If the monad supports other ways of aborting the computation, the -- action won't run if those other kinds of errors are thrown. See -- onError. onException :: MonadCatch m => m a -> m b -> m a -- | Run an action only if an error is thrown in the main action. Unlike -- onException, this works with every kind of error, not just -- exceptions. For example, if f is an ExceptT -- computation which aborts with a Left, the computation -- onError f g will execute g, while onException f -- g will not. -- -- This distinction is only meaningful for monads which have multiple -- exit points, such as Except and MaybeT. For monads -- that only have a single exit point, there is no difference between -- onException and onError, except that onError has -- a more constrained type. onError :: MonadMask m => m a -> m b -> m a -- | Generalized abstracted pattern of safe resource acquisition and -- release in the face of errors. The first action "acquires" some value, -- which is "released" by the second action at the end. The third action -- "uses" the value and its result is the result of the bracket. -- -- If an error is thrown during the use, the release still happens before -- the error is rethrown. -- -- Note that this is essentially a type-specialized version of -- generalBracket. This function has a more common signature -- (matching the signature from Control.Exception), and is often -- more convenient to use. By contrast, generalBracket is more -- expressive, allowing us to implement other functions like -- bracketOnError. bracket :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b -- | Version of bracket without any value being passed to the second -- and third actions. bracket_ :: MonadMask m => m a -> m c -> m b -> m b -- | Perform an action with a finalizer action that is run, even if an -- error occurs. finally :: MonadMask m => m a -> m b -> m a -- | Like bracket, but only performs the final action if an error is -- thrown by the in-between computation. bracketOnError :: MonadMask m => m a -> (a -> m c) -> (a -> m b) -> m b -- | Any type that you wish to throw or catch as an exception must be an -- instance of the Exception class. The simplest case is a new -- exception type directly below the root: -- --
-- data MyException = ThisException | ThatException -- deriving Show -- -- instance Exception MyException ---- -- The default method definitions in the Exception class do what -- we need in this case. You can now throw and catch -- ThisException and ThatException as exceptions: -- --
-- *Main> throw ThisException `catch` \e -> putStrLn ("Caught " ++ show (e :: MyException)) -- Caught ThisException ---- -- In more complicated examples, you may wish to define a whole hierarchy -- of exceptions: -- --
-- --------------------------------------------------------------------- -- -- Make the root exception type for all the exceptions in a compiler -- -- data SomeCompilerException = forall e . Exception e => SomeCompilerException e -- -- instance Show SomeCompilerException where -- show (SomeCompilerException e) = show e -- -- instance Exception SomeCompilerException -- -- compilerExceptionToException :: Exception e => e -> SomeException -- compilerExceptionToException = toException . SomeCompilerException -- -- compilerExceptionFromException :: Exception e => SomeException -> Maybe e -- compilerExceptionFromException x = do -- SomeCompilerException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make a subhierarchy for exceptions in the frontend of the compiler -- -- data SomeFrontendException = forall e . Exception e => SomeFrontendException e -- -- instance Show SomeFrontendException where -- show (SomeFrontendException e) = show e -- -- instance Exception SomeFrontendException where -- toException = compilerExceptionToException -- fromException = compilerExceptionFromException -- -- frontendExceptionToException :: Exception e => e -> SomeException -- frontendExceptionToException = toException . SomeFrontendException -- -- frontendExceptionFromException :: Exception e => SomeException -> Maybe e -- frontendExceptionFromException x = do -- SomeFrontendException a <- fromException x -- cast a -- -- --------------------------------------------------------------------- -- -- Make an exception type for a particular frontend compiler exception -- -- data MismatchedParentheses = MismatchedParentheses -- deriving Show -- -- instance Exception MismatchedParentheses where -- toException = frontendExceptionToException -- fromException = frontendExceptionFromException ---- -- We can now catch a MismatchedParentheses exception as -- MismatchedParentheses, SomeFrontendException or -- SomeCompilerException, but not other types, e.g. -- IOException: -- --
-- *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: MismatchedParentheses)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeFrontendException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: SomeCompilerException)) -- Caught MismatchedParentheses -- *Main> throw MismatchedParentheses `catch` \e -> putStrLn ("Caught " ++ show (e :: IOException)) -- *** Exception: MismatchedParentheses --class (Typeable e, Show e) => Exception e toException :: Exception e => e -> SomeException fromException :: Exception e => SomeException -> Maybe e -- | Render this exception value in a human-friendly manner. -- -- Default implementation: show. displayException :: Exception e => e -> String -- | The SomeException type is the root of the exception type -- hierarchy. When an exception of type e is thrown, behind the -- scenes it is encapsulated in a SomeException. data SomeException SomeException :: e -> SomeException instance GHC.Show.Show a => GHC.Show.Show (Control.Monad.Catch.ExitCase a) instance GHC.Base.Monad m => GHC.Base.Functor (Control.Monad.Catch.Handler m) instance Control.Monad.Catch.MonadMask GHC.Types.IO instance (e GHC.Types.~ GHC.Exception.Type.SomeException) => Control.Monad.Catch.MonadMask (Data.Either.Either e) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.State.Strict.StateT s m) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Reader.ReaderT r m) instance (Control.Monad.Catch.MonadMask m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (Control.Monad.Catch.MonadMask m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (Control.Monad.Catch.MonadMask m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadMask (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (Control.Monad.Catch.MonadMask m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadMask (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Maybe.MaybeT m) instance (Control.Monad.Trans.Error.Error e, Control.Monad.Catch.MonadMask m) => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Error.ErrorT e m) instance Control.Monad.Catch.MonadMask m => Control.Monad.Catch.MonadMask (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Catch.MonadCatch GHC.Types.IO instance Control.Monad.Catch.MonadCatch GHC.Conc.Sync.STM instance (e GHC.Types.~ GHC.Exception.Type.SomeException) => Control.Monad.Catch.MonadCatch (Data.Either.Either e) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.State.Strict.StateT s m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Reader.ReaderT r m) instance (Control.Monad.Catch.MonadCatch m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (Control.Monad.Catch.MonadCatch m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (Control.Monad.Catch.MonadCatch m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (Control.Monad.Catch.MonadCatch m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.List.ListT m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Maybe.MaybeT m) instance (Control.Monad.Trans.Error.Error e, Control.Monad.Catch.MonadCatch m) => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Error.ErrorT e m) instance Control.Monad.Catch.MonadCatch m => Control.Monad.Catch.MonadCatch (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Catch.MonadThrow [] instance Control.Monad.Catch.MonadThrow GHC.Maybe.Maybe instance Control.Monad.Catch.MonadThrow Language.Haskell.TH.Syntax.Q instance Control.Monad.Catch.MonadThrow GHC.Types.IO instance Control.Monad.Catch.MonadThrow (GHC.ST.ST s) instance Control.Monad.Catch.MonadThrow GHC.Conc.Sync.STM instance (e GHC.Types.~ GHC.Exception.Type.SomeException) => Control.Monad.Catch.MonadThrow (Data.Either.Either e) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Identity.IdentityT m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.State.Lazy.StateT s m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.State.Strict.StateT s m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Reader.ReaderT r m) instance (Control.Monad.Catch.MonadThrow m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Writer.Strict.WriterT w m) instance (Control.Monad.Catch.MonadThrow m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Writer.Lazy.WriterT w m) instance (Control.Monad.Catch.MonadThrow m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.RWS.Lazy.RWST r w s m) instance (Control.Monad.Catch.MonadThrow m, GHC.Base.Monoid w) => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.RWS.Strict.RWST r w s m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.List.ListT m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Maybe.MaybeT m) instance (Control.Monad.Trans.Error.Error e, Control.Monad.Catch.MonadThrow m) => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Error.ErrorT e m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Except.ExceptT e m) instance Control.Monad.Catch.MonadThrow m => Control.Monad.Catch.MonadThrow (Control.Monad.Trans.Cont.ContT r m) -- | This module supplies a 'pure' monad transformer that can be used for -- mock-testing code that throws exceptions, so long as those exceptions -- are always thrown with throwM. -- -- Do not mix CatchT with IO. Choose one or the other for -- the bottom of your transformer stack! module Control.Monad.Catch.Pure -- | Add Exception handling abilities to a Monad. -- -- This should never be used in combination with IO. Think -- of CatchT as an alternative base monad for use with mocking -- code that solely throws exceptions via throwM. -- -- Note: that IO monad has these abilities already, so stacking -- CatchT on top of it does not add any value and can possibly be -- confusing: -- --
-- >>> (error "Hello!" :: IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e) -- Hello! ---- --
-- >>> runCatchT $ (error "Hello!" :: CatchT IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e) -- *** Exception: Hello! ---- --
-- >>> runCatchT $ (throwM (ErrorCall "Hello!") :: CatchT IO ()) `catch` (\(e :: ErrorCall) -> liftIO $ print e) -- Hello! --newtype CatchT m a CatchT :: m (Either SomeException a) -> CatchT m a [runCatchT] :: CatchT m a -> m (Either SomeException a) type Catch = CatchT Identity runCatch :: Catch a -> Either SomeException a -- | Map the unwrapped computation using the given function. -- --
-- runCatchT (mapCatchT f m) = f (runCatchT m) --mapCatchT :: (m (Either SomeException a) -> n (Either SomeException b)) -> CatchT m a -> CatchT n b instance GHC.Base.Monad m => GHC.Base.Functor (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => GHC.Base.Applicative (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => GHC.Base.Monad (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => Control.Monad.Fail.MonadFail (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.Fix.MonadFix m => Control.Monad.Fix.MonadFix (Control.Monad.Catch.Pure.CatchT m) instance Data.Foldable.Foldable m => Data.Foldable.Foldable (Control.Monad.Catch.Pure.CatchT m) instance (GHC.Base.Monad m, Data.Traversable.Traversable m) => Data.Traversable.Traversable (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => GHC.Base.Alternative (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => GHC.Base.MonadPlus (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.Trans.Class.MonadTrans Control.Monad.Catch.Pure.CatchT instance Control.Monad.IO.Class.MonadIO m => Control.Monad.IO.Class.MonadIO (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => Control.Monad.Catch.MonadThrow (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => Control.Monad.Catch.MonadCatch (Control.Monad.Catch.Pure.CatchT m) instance GHC.Base.Monad m => Control.Monad.Catch.MonadMask (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.State.Class.MonadState s m => Control.Monad.State.Class.MonadState s (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.Reader.Class.MonadReader e m => Control.Monad.Reader.Class.MonadReader e (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.Writer.Class.MonadWriter w m => Control.Monad.Writer.Class.MonadWriter w (Control.Monad.Catch.Pure.CatchT m) instance Control.Monad.RWS.Class.MonadRWS r w s m => Control.Monad.RWS.Class.MonadRWS r w s (Control.Monad.Catch.Pure.CatchT m)