A universal data type for computations which may fail. Errors are reported using extensible exceptions. These exceptions are not explicitly stated; if you want this kind of functionality, something like control-monad-exception might be a more appropriate fit.
- data Attempt v
- class FromAttempt a where
- fromAttempt :: Attempt v -> a v
- fa :: FromAttempt a => Attempt v -> a v
- joinAttempt :: (FromAttempt m, Monad m) => m (Attempt v) -> m v
- attempt :: (forall e. Exception e => e -> b) -> (a -> b) -> Attempt a -> b
- makeHandler :: [AttemptHandler v] -> v -> forall e. Exception e => e -> v
- data AttemptHandler v = forall e . Exception e => AttemptHandler (e -> v)
- isFailure :: Attempt v -> Bool
- isSuccess :: Attempt v -> Bool
- fromSuccess :: Attempt v -> v
- successes :: [Attempt v] -> [v]
- failures :: [Attempt v] -> [SomeException]
- partitionAttempts :: [Attempt v] -> ([SomeException], [v])
- attemptIO :: (Exception eIn, Exception eOut) => (eIn -> eOut) -> IO v -> IO (Attempt v)
- module Control.Failure
Data type and type class
class FromAttempt a whereSource
Any type which can be converted from an Attempt
. The included instances are your "usual suspects" for dealing with error handling. They include:
IO
: For the IO instance, any exceptions in the Attempt
are thrown as
runtime exceptions.
Maybe
: Returns Nothing
on Failure
, or Just
on Success
.
List: Returns the empty list on Failure
, or a singleton list on Success
.
Either
String
: Returns Left
(show
exception) on Failure
, or Right
on
Success
.
Either
Exception
: Returns Left
exception on Failure
, or Right
on
Success
.
fromAttempt :: Attempt v -> a vSource
fa :: FromAttempt a => Attempt v -> a vSource
A shortcut for fromAttempt
.
joinAttempt :: (FromAttempt m, Monad m) => m (Attempt v) -> m vSource
This is not a simple translation of the Control.Monad.join function.
Instead, for Monad
s which are instances of FromAttempt
, it removes the
inner Attempt
type, reporting errors as defined in the FromAttempt
instance.
For example, join (Just (failureString "foo")) == Nothing.
General handling of Attempt
s
Process either the exception or value in an Attempt
to produce a result.
This function is modeled after maybe
and either
. The first argument must
accept any instances of Exception
. If you want to handle multiple types
of exceptions, see makeHandler
. The second argument converts the success
value.
Note that this function does not expose all the data available in an
Attempt
value. Notably, the monadic stack trace is not passed on to the
error handler. If desired, use the monadicStackTrace
function to extract
it.
makeHandler :: [AttemptHandler v] -> v -> forall e. Exception e => e -> vSource
Convert multiple AttemptHandler
s and a default value into an exception
handler.
This is a convenience function when you want to have special handling for a
few types of Exception
s and provide another value for anything else.
data AttemptHandler v Source
A simple wrapper value necesary due to the Haskell type system. Wraps a
function from a *specific* Exception
type to some value.
forall e . Exception e => AttemptHandler (e -> v) |
Individual Attempt
s
fromSuccess :: Attempt v -> vSource
This is an unsafe, partial function which should only be used if you either know that a function will succeed or don't mind the occassional runtime exception.
Lists of Attempt
s
failures :: [Attempt v] -> [SomeException]Source
Returns only the Failure
values, each wrapped in a SomeException
.
partitionAttempts :: [Attempt v] -> ([SomeException], [v])Source
Runtime exceptions
attemptIO :: (Exception eIn, Exception eOut) => (eIn -> eOut) -> IO v -> IO (Attempt v)Source
Catches runtime (ie, IO) exceptions and inserts them into an Attempt
.
Like handle
, the first argument to this function must explicitly state the
type of its input.
Reexport the Failure
class
module Control.Failure