fused-effects-exceptions-0.1.1.0: Handle exceptions thrown in IO with fused-effects.

Safe HaskellNone
LanguageHaskell2010

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

Documentation

data Catch m k Source #

Constructors

Exception e => CatchIO (m output) (e -> m output) (output -> k) 
Instances
Effect Catch Source # 
Instance details

Defined in Control.Effect.Catch

Methods

handle :: Functor f => f () -> (forall x. f (m x) -> n (f x)) -> Catch m (m a) -> Catch n (n (f a))

HFunctor Catch Source # 
Instance details

Defined in Control.Effect.Catch

Methods

fmap' :: (a -> b) -> Catch m a -> Catch m b

hmap :: (forall x. m x -> n x) -> Catch m a -> Catch n a

Functor (Catch m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

fmap :: (a -> b) -> Catch m a -> Catch m b #

(<$) :: a -> Catch m b -> Catch m a #

(Carrier sig m, MonadIO m) => Carrier (Catch :+: sig) (CatchC m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

eff :: (Catch :+: sig) (CatchC m) (CatchC m a) -> CatchC m a

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 :: (forall x. m x -> IO x) -> CatchC m a -> m a Source #

Evaluate a Catch effect.

withCatch :: MonadUnliftIO m => CatchC m a -> m a Source #

Evaluate a Catch effect, using MonadUnliftIO to infer a correct unlifting function.

newtype CatchC m a Source #

Constructors

CatchC 

Fields

Instances
Monad m => Monad (CatchC m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

(>>=) :: CatchC m a -> (a -> CatchC m b) -> CatchC m b #

(>>) :: CatchC m a -> CatchC m b -> CatchC m b #

return :: a -> CatchC m a #

fail :: String -> CatchC m a #

Functor m => Functor (CatchC m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

fmap :: (a -> b) -> CatchC m a -> CatchC m b #

(<$) :: a -> CatchC m b -> CatchC m a #

Applicative m => Applicative (CatchC m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

pure :: a -> CatchC m a #

(<*>) :: CatchC m (a -> b) -> CatchC m a -> CatchC m b #

liftA2 :: (a -> b -> c) -> CatchC m a -> CatchC m b -> CatchC m c #

(*>) :: CatchC m a -> CatchC m b -> CatchC m b #

(<*) :: CatchC m a -> CatchC m b -> CatchC m a #

MonadIO m => MonadIO (CatchC m) Source # 
Instance details

Defined in Control.Effect.Catch

Methods

liftIO :: IO a -> CatchC m a #

MonadUnliftIO m => MonadUnliftIO (CatchC m) Source # 
Instance details

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 # 
Instance details

Defined in Control.Effect.Catch

Methods

eff :: (Catch :+: sig) (CatchC m) (CatchC m a) -> CatchC m a