attempt-0.0.0: Error handling using extensible exceptions outside the IO monad.Source codeContentsIndex
Data.Attempt.Helper
Contents
Non-standard functions
Exception types
Standard functions reimplemented
IO functions with exceptions handled
Description
Replacements for standard functions to represent failure with a MonadAttempt. Lots of inspiration taken from the safe package.
Synopsis
join :: (FromAttempt m, Monad m) => m (Attempt v) -> m v
data KeyNotFound k v = KeyNotFound k [(k, v)]
data EmptyList = EmptyList
newtype CouldNotRead = CouldNotRead String
data NegativeIndex = NegativeIndex
lookup :: (Typeable k, Typeable v, Show k, Eq k, MonadAttempt m) => k -> [(k, v)] -> m v
tail :: MonadAttempt m => [a] -> m [a]
init :: MonadAttempt m => [a] -> m [a]
head :: MonadAttempt m => [a] -> m a
last :: MonadAttempt m => [a] -> m a
read :: (MonadAttempt m, Read a) => String -> m a
at :: MonadAttempt m => [a] -> Int -> m a
assert :: (MonadAttempt m, Exception e) => Bool -> v -> e -> m v
readFile :: (MonadAttempt m, MonadIO m) => FilePath -> m String
Non-standard functions
join :: (FromAttempt m, Monad m) => m (Attempt v) -> m vSource

This is not a simple translation of the Control.Monad.join function. Instead, for Monads 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.

Exception types
data KeyNotFound k v Source
Exception type for the lookup function.
Constructors
KeyNotFound k [(k, v)]
show/hide Instances
data EmptyList Source
Exception type for functions which expect non-empty lists.
Constructors
EmptyList
show/hide Instances
newtype CouldNotRead Source
Report errors from the read function.
Constructors
CouldNotRead String
show/hide Instances
data NegativeIndex Source
For functions which expect index values >= 0.
Constructors
NegativeIndex
show/hide Instances
Standard functions reimplemented
lookup :: (Typeable k, Typeable v, Show k, Eq k, MonadAttempt m) => k -> [(k, v)] -> m vSource
tail :: MonadAttempt m => [a] -> m [a]Source
init :: MonadAttempt m => [a] -> m [a]Source
head :: MonadAttempt m => [a] -> m aSource
last :: MonadAttempt m => [a] -> m aSource
read :: (MonadAttempt m, Read a) => String -> m aSource
at :: MonadAttempt m => [a] -> Int -> m aSource
Same as Prelude.!!. Name stolen from safe library.
assert :: (MonadAttempt m, Exception e) => Bool -> v -> e -> m vSource
Assert a value to be true. If true, returns the first value as a succss. Otherwise, returns the second value as a failure.
IO functions with exceptions handled
readFile :: (MonadAttempt m, MonadIO m) => FilePath -> m StringSource
The standard readFile function with any IOExceptions returned as a failure instead of a runtime exception.
Produced by Haddock version 2.6.0