errors-2.1.3: Simplified error-handling

Safe HaskellSafe
LanguageHaskell98

Control.Error.Safe

Contents

Description

This module extends the safe library's functions with corresponding versions compatible with Either and ExceptT, and also provides a few Maybe-compatible functions missing from safe.

I suffix the Either-compatible functions with Err and prefix the ExceptT-compatible functions with try.

Note that this library re-exports the Maybe compatible functions from safe in the Control.Error module, so they are not provided here.

The 'Z'-suffixed functions generalize the Maybe functions to also work with anything that implements MonadPlus, including:

Synopsis

Maybe-compatible functions

assertMay :: Bool -> Maybe () Source #

An assertion that fails in the Maybe monad

rightMay :: Either e a -> Maybe a Source #

A fromRight that fails in the Maybe monad

Either-compatible functions

tailErr :: e -> [a] -> Either e [a] Source #

A tail that fails in the Either monad

initErr :: e -> [a] -> Either e [a] Source #

An init that fails in the Either monad

headErr :: e -> [a] -> Either e a Source #

A head that fails in the Either monad

lastErr :: e -> [a] -> Either e a Source #

A last that fails in the Either monad

minimumErr :: Ord a => e -> [a] -> Either e a Source #

A minimum that fails in the Either monad

maximumErr :: Ord a => e -> [a] -> Either e a Source #

A maximum that fails in the Either monad

foldr1Err :: e -> (a -> a -> a) -> [a] -> Either e a Source #

A foldr1 that fails in the Either monad

foldl1Err :: e -> (a -> a -> a) -> [a] -> Either e a Source #

A foldl1 that fails in the Either monad

foldl1Err' :: e -> (a -> a -> a) -> [a] -> Either e a Source #

A foldl1' that fails in the Either monad

atErr :: e -> [a] -> Int -> Either e a Source #

A (!!) that fails in the Either monad

readErr :: Read a => e -> String -> Either e a Source #

A read that fails in the Either monad

assertErr :: e -> Bool -> Either e () Source #

An assertion that fails in the Either monad

justErr :: e -> Maybe a -> Either e a Source #

A fromJust that fails in the Either monad

ExceptT-compatible functions

tryTail :: Monad m => e -> [a] -> ExceptT e m [a] Source #

A tail that fails in the ExceptT monad

tryInit :: Monad m => e -> [a] -> ExceptT e m [a] Source #

An init that fails in the ExceptT monad

tryHead :: Monad m => e -> [a] -> ExceptT e m a Source #

A head that fails in the ExceptT monad

tryLast :: Monad m => e -> [a] -> ExceptT e m a Source #

A last that fails in the ExceptT monad

tryMinimum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a Source #

A minimum that fails in the ExceptT monad

tryMaximum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a Source #

A maximum that fails in the ExceptT monad

tryFoldr1 :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a Source #

A foldr1 that fails in the ExceptT monad

tryFoldl1 :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a Source #

A foldl1 that fails in the ExceptT monad

tryFoldl1' :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a Source #

A foldl1' that fails in the ExceptT monad

tryAt :: Monad m => e -> [a] -> Int -> ExceptT e m a Source #

A (!!) that fails in the ExceptT monad

tryRead :: (Monad m, Read a) => e -> String -> ExceptT e m a Source #

A read that fails in the ExceptT monad

tryAssert :: Monad m => e -> Bool -> ExceptT e m () Source #

An assertion that fails in the ExceptT monad

tryJust :: Monad m => e -> Maybe a -> ExceptT e m a Source #

A fromJust that fails in the ExceptT monad

tryRight :: Monad m => Either e a -> ExceptT e m a Source #

A fromRight that fails in the ExceptT monad

MonadPlus-compatible functions

tailZ :: MonadPlus m => [a] -> m [a] Source #

A tail that fails using mzero

initZ :: MonadPlus m => [a] -> m [a] Source #

An init that fails using mzero

headZ :: MonadPlus m => [a] -> m a Source #

A head that fails using mzero

lastZ :: MonadPlus m => [a] -> m a Source #

A last that fails using mzero

minimumZ :: MonadPlus m => Ord a => [a] -> m a Source #

A minimum that fails using mzero

maximumZ :: MonadPlus m => Ord a => [a] -> m a Source #

A maximum that fails using mzero

foldr1Z :: MonadPlus m => (a -> a -> a) -> [a] -> m a Source #

A foldr1 that fails using mzero

foldl1Z :: MonadPlus m => (a -> a -> a) -> [a] -> m a Source #

A foldl1 that fails using mzero

foldl1Z' :: MonadPlus m => (a -> a -> a) -> [a] -> m a Source #

A foldl1' that fails using mzero

atZ :: MonadPlus m => [a] -> Int -> m a Source #

A (!!) that fails using mzero

readZ :: MonadPlus m => Read a => String -> m a Source #

A read that fails using mzero

assertZ :: MonadPlus m => Bool -> m () Source #

An assertion that fails using mzero

justZ :: MonadPlus m => Maybe a -> m a Source #

A fromJust that fails using mzero

rightZ :: MonadPlus m => Either e a -> m a Source #

A fromRight that fails using mzero