Safe Haskell | Safe |
---|---|
Language | Haskell98 |
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:
- assertMay :: Bool -> Maybe ()
- rightMay :: Either e a -> Maybe a
- tailErr :: e -> [a] -> Either e [a]
- initErr :: e -> [a] -> Either e [a]
- headErr :: e -> [a] -> Either e a
- lastErr :: e -> [a] -> Either e a
- minimumErr :: Ord a => e -> [a] -> Either e a
- maximumErr :: Ord a => e -> [a] -> Either e a
- foldr1Err :: e -> (a -> a -> a) -> [a] -> Either e a
- foldl1Err :: e -> (a -> a -> a) -> [a] -> Either e a
- foldl1Err' :: e -> (a -> a -> a) -> [a] -> Either e a
- atErr :: e -> [a] -> Int -> Either e a
- readErr :: Read a => e -> String -> Either e a
- assertErr :: e -> Bool -> Either e ()
- justErr :: e -> Maybe a -> Either e a
- tryTail :: Monad m => e -> [a] -> ExceptT e m [a]
- tryInit :: Monad m => e -> [a] -> ExceptT e m [a]
- tryHead :: Monad m => e -> [a] -> ExceptT e m a
- tryLast :: Monad m => e -> [a] -> ExceptT e m a
- tryMinimum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a
- tryMaximum :: (Monad m, Ord a) => e -> [a] -> ExceptT e m a
- tryFoldr1 :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a
- tryFoldl1 :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a
- tryFoldl1' :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a
- tryAt :: Monad m => e -> [a] -> Int -> ExceptT e m a
- tryRead :: (Monad m, Read a) => e -> String -> ExceptT e m a
- tryAssert :: Monad m => e -> Bool -> ExceptT e m ()
- tryJust :: Monad m => e -> Maybe a -> ExceptT e m a
- tryRight :: Monad m => Either e a -> ExceptT e m a
- tailZ :: MonadPlus m => [a] -> m [a]
- initZ :: MonadPlus m => [a] -> m [a]
- headZ :: MonadPlus m => [a] -> m a
- lastZ :: MonadPlus m => [a] -> m a
- minimumZ :: MonadPlus m => Ord a => [a] -> m a
- maximumZ :: MonadPlus m => Ord a => [a] -> m a
- foldr1Z :: MonadPlus m => (a -> a -> a) -> [a] -> m a
- foldl1Z :: MonadPlus m => (a -> a -> a) -> [a] -> m a
- foldl1Z' :: MonadPlus m => (a -> a -> a) -> [a] -> m a
- atZ :: MonadPlus m => [a] -> Int -> m a
- readZ :: MonadPlus m => Read a => String -> m a
- assertZ :: MonadPlus m => Bool -> m ()
- justZ :: MonadPlus m => Maybe a -> m a
- rightZ :: MonadPlus m => Either e a -> m a
Maybe-compatible functions
Either-compatible functions
foldl1Err' :: e -> (a -> a -> a) -> [a] -> Either e a Source #
A foldl1'
that fails in the Either
monad
ExceptT-compatible functions
tryFoldl1' :: Monad m => e -> (a -> a -> a) -> [a] -> ExceptT e m a Source #
A foldl1'
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