| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Effect.Catch
Description
An effect that enables catching exceptions thrown from
impure computations such as IO.
Use of the Error effect from Control.Effect.Error may lead to
simpler code, as well as avoiding the dynamically-typed nature of
Exception. This is best used when integrating with third-party
libraries that operate in IO. If you are using catch for resource
management, consider using Resource instead.
Synopsis
- data Catch m k = Exception e => CatchIO (m output) (e -> m output) (output -> m k)
- catch :: (Member Catch sig, Carrier sig m, Exception e) => m a -> (e -> m a) -> m a
- catchSync :: (Member Catch sig, Carrier sig m, Exception e, MonadIO m) => m a -> (e -> m a) -> m a
- runCatch :: MonadUnliftIO m => CatchC m a -> m a
- newtype CatchC m a = CatchC {
- runCatchC :: ReaderC (Handler m) m a
Documentation
catch :: (Member Catch sig, Carrier sig m, Exception e) => m a -> (e -> m a) -> m a Source #
Like catchError, but delegating to
catch under the hood, which allows catching
errors that might occur when lifting IO computations.
Unhandled errors are rethrown. Use SomeException if you want
to catch all errors.
catchSync :: (Member Catch sig, Carrier sig m, Exception e, MonadIO m) => m a -> (e -> m a) -> m a Source #
Like catch, but the handler only engages on synchronous exceptions.
Async exceptions are rethrown.
runCatch :: MonadUnliftIO m => CatchC m a -> m a Source #
Evaluate a Catch effect, using MonadUnliftIO to infer a correct
unlifting function.
Instances
| Monad m => Monad (CatchC m) Source # | |
| Functor m => Functor (CatchC m) Source # | |
| Applicative m => Applicative (CatchC m) Source # | |
| MonadIO m => MonadIO (CatchC m) Source # | |
Defined in Control.Effect.Catch | |
| MonadUnliftIO m => MonadUnliftIO (CatchC m) Source # | |
Defined in Control.Effect.Catch Methods askUnliftIO :: CatchC m (UnliftIO (CatchC m)) withRunInIO :: ((forall a. CatchC m a -> IO a) -> IO b) -> CatchC m b | |
| (Carrier sig m, MonadIO m) => Carrier (Catch :+: sig) (CatchC m) Source # | |
Defined in Control.Effect.Catch | |