io-effects-0.1.0: Taming the IO monad

Safe HaskellNone
LanguageHaskell2010

IO.Effects.Exception

Contents

Synopsis

Running Programs with exceptions

runExceptions :: ProgramWithHandler Exceptions es a -> Program es (Either SomeException a) Source #

Run a program that may use exceptions. The program itself is wrapped in a call to tryAny to prevent any top-level exceptions leaking.

runExceptions allows asynchronous exceptions to pass through and does not catch them.

Throwing

throwIO :: (Member Exceptions es, Exception e) => e -> Program es a Source #

Synchronously throw the given exception.

See also: throwIO (from Control.Exception).

Catching (with recovery)

catch :: (Exception e, Member Exceptions es) => Program es a -> (e -> Program es a) -> Program es a Source #

Catch synchronous exceptions. Asynchronous exceptions (exceptions that match isSyncException will not be caught).

See also catch (from Control.Exception).

catchIO :: Member Exceptions es => Program es a -> (IOException -> Program es a) -> Program es a Source #

catch specialized to only catching IOExceptions.

catchAny :: Member Exceptions es => Program es a -> (SomeException -> Program es a) -> Program es a Source #

catch specialized to catch all synchronous exceptions.

catchJust :: (Member Exceptions es, Exception e) => (e -> Maybe b) -> Program es a -> (b -> Program es a) -> Program es a Source #

catchJust is like catch but it takes an extra argument which is an exception predicate, a function which selects which type of exceptions we're interested in.

handle :: (Member Exceptions es, Exception e) => (e -> Program es a) -> Program es a -> Program es a Source #

Flipped version of catch.

handleIO :: Member Exceptions es => (IOException -> Program es a) -> Program es a -> Program es a Source #

Flipped version of catchIO.

handleAny :: Member Exceptions es => (SomeException -> Program es a) -> Program es a -> Program es a Source #

Flipped version of catchAny.

handleJust :: (Member Exceptions es, Exception e) => (e -> Maybe b) -> (b -> Program es a) -> Program es a -> Program es a Source #

Flipped version of catchJust.

try :: (Member Exceptions es, Exception e) => Program es a -> Program es (Either e a) Source #

Like try (from Control.Exception), but will not catch asynchronous exceptions.

tryIO :: Member Exceptions es => Program es a -> Program es (Either IOException a) Source #

try specialized to IOExceptions.

tryAny :: Member Exceptions es => Program es a -> Program es (Either SomeException a) Source #

try specialized to catch all synchronous exceptions.

tryJust :: (Member Exceptions es, Exception e) => (e -> Maybe b) -> Program es a -> Program es (Either b a) Source #

A variant of try that takes an exception predicate to select which exceptions are caught.

data Handler m a where Source #

Generalized version of Handler (from Control.Exception).

Constructors

Handler :: Exception e => (e -> m a) -> Handler m a 

catches :: Member Exceptions es => Program es a -> [Handler (Program es) a] -> Program es a Source #

Same as upstream catches (from Control.Exception), but will not catch asynchronous exceptions.

Cleanup (no recovery)

onException :: Member Exceptions es => Program es a -> Program es b -> Program es a Source #

Async safe version of onException (from Control.Exception).

bracket :: Member Exceptions es => Program es a -> (a -> Program es b) -> (a -> Program es c) -> Program es c Source #

Async safe version of bracket (from Control.Exception).

bracket_ :: Member Exceptions es => Program es a -> Program es b -> Program es c -> Program es c Source #

Async safe version of bracket_ (from Control.Exception).

finally :: Member Exceptions es => Program es a -> Program es b -> Program es a Source #

Async safe version of finally (from Control.Exception).

withException :: (Member Exceptions es, Exception e) => Program es a -> (e -> Program es b) -> Program es a Source #

Async safe version of withException (from Control.Exception).

bracketOnError :: Member Exceptions es => Program es a -> (a -> Program es b) -> (a -> Program es c) -> Program es c Source #

Async safe version of bracketOnError (from Control.Exception).

bracketOnError_ :: Member Exceptions es => Program es a -> Program es b -> Program es c -> Program es c Source #

Async safe version of bracketOnError_ (from Control.Exception).

Distinguishing exception types

isSyncException :: Exception e => e -> Bool Source #

Check if the given exception is synchronous.

Masking

mask :: Member Exceptions es => ((forall x. Program es x -> Program es x) -> Program es a) -> Program es a Source #

uninterruptibleMask :: Member Exceptions es => ((forall x. Program es x -> Program es x) -> Program es a) -> Program es a Source #

Evaluation

Exceptions syntax

data Exceptions m a where Source #

The underlying syntax used by the exception system.

Constructors

Catch :: Exception e => m a -> (e -> m a) -> Exceptions m a 
Evaluate :: a -> Exceptions m a 
Mask :: ((forall a. m a -> m a) -> m b) -> Exceptions m b 
ThrowIO :: Exception e => e -> Exceptions m a 
UninterruptibleMask :: ((forall a. m a -> m a) -> m b) -> Exceptions m b