| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell98 |
Control.Error
Contents
Description
Import this module in your code to access the entire library's functionality:
import Control.Error
This module exports the entire library as well as useful exports from other standard error-handling libraries:
- Control.Error.Safe: Generalizes the
safelibrary, includingEither,EitherT, andMonadPlusvariations on total functions - Control.Error.Script: Support for simple scripts that catch all errors
and transform them to
Text - Control.Error.Util: Utility functions and conversions between common error-handling types
Control.Monad.Trans.Except: TheExceptTmonad transformerControl.Monad.Trans.Maybe: TheMaybeTmonad transformerData.Either:Eitherutility functions- Data.EitherR: throw and catch functions, and their corresponding "success" monads
Data.Maybe:Maybeutility functionsSafe: Total versions of partial Prelude functions
This module does not re-export partial functions from other libraries.
Synopsis
- module Control.Error.Safe
- module Control.Error.Script
- module Control.Error.Util
- throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a
- newtype ExceptT e (m :: Type -> Type) a = ExceptT (m (Either e a))
- runExceptT :: ExceptT e m a -> m (Either e a)
- mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b
- withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a
- catchE :: forall (m :: Type -> Type) e a e'. Monad m => ExceptT e m a -> (e -> ExceptT e' m a) -> ExceptT e' m a
- newtype MaybeT (m :: Type -> Type) a = MaybeT {}
- liftCallCC :: CallCC m (Maybe a) (Maybe b) -> CallCC (MaybeT m) a b
- liftCatch :: Catch e m (Maybe a) -> Catch e (MaybeT m) a
- liftListen :: Monad m => Listen w m (Maybe a) -> Listen w (MaybeT m) a
- liftPass :: Monad m => Pass w m (Maybe a) -> Pass w (MaybeT m) a
- mapMaybeT :: (m (Maybe a) -> n (Maybe b)) -> MaybeT m a -> MaybeT n b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- partitionEithers :: [Either a b] -> ([a], [b])
- module Data.EitherR
- maybe :: b -> (a -> b) -> Maybe a -> b
- isJust :: Maybe a -> Bool
- isNothing :: Maybe a -> Bool
- fromMaybe :: a -> Maybe a -> a
- maybeToList :: Maybe a -> [a]
- listToMaybe :: [a] -> Maybe a
- catMaybes :: [Maybe a] -> [a]
- mapMaybe :: (a -> Maybe b) -> [a] -> [b]
- foldr1May :: (a -> a -> a) -> [a] -> Maybe a
- minimumMay :: Ord a => [a] -> Maybe a
- maximumMay :: Ord a => [a] -> Maybe a
- findJustDef :: a -> (a -> Bool) -> [a] -> a
- minimumDef :: Ord a => a -> [a] -> a
- maximumDef :: Ord a => a -> [a] -> a
- foldr1Def :: a -> (a -> a -> a) -> [a] -> a
- tailMay :: [a] -> Maybe [a]
- tailDef :: [a] -> [a] -> [a]
- tailSafe :: [a] -> [a]
- initMay :: [a] -> Maybe [a]
- initDef :: [a] -> [a] -> [a]
- initSafe :: [a] -> [a]
- headMay :: [a] -> Maybe a
- lastMay :: [a] -> Maybe a
- headDef :: a -> [a] -> a
- lastDef :: a -> [a] -> a
- foldl1May' :: (a -> a -> a) -> [a] -> Maybe a
- fromJustDef :: a -> Maybe a -> a
- atMay :: [a] -> Int -> Maybe a
- atDef :: a -> [a] -> Int -> a
- readMay :: Read a => String -> Maybe a
- readDef :: Read a => a -> String -> a
- lookupJustDef :: Eq a => b -> a -> [(a, b)] -> b
- foldl1Def' :: a -> (a -> a -> a) -> [a] -> a
Re-exports
module Control.Error.Safe
module Control.Error.Script
module Control.Error.Util
newtype ExceptT e (m :: Type -> Type) a #
A monad transformer that adds exceptions to other monads.
ExceptT constructs a monad parameterized over two things:
- e - The exception type.
- m - The inner monad.
The return function yields a computation that produces the given
value, while >>= sequences two subcomputations, exiting on the
first exception.
Instances
runExceptT :: ExceptT e m a -> m (Either e a) #
The inverse of ExceptT.
mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b #
Map the unwrapped computation using the given function.
runExceptT(mapExceptTf m) = f (runExceptTm)
withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a #
Transform any exceptions thrown by the computation using the given function.
newtype MaybeT (m :: Type -> Type) a #
The parameterizable maybe monad, obtained by composing an arbitrary
monad with the Maybe monad.
Computations are actions that may produce a value or exit.
The return function yields a computation that produces that
value, while >>= sequences two subcomputations, exiting if either
computation does.
Instances
| MonadTrans MaybeT | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| Functor m => Generic1 (MaybeT m :: Type -> Type) | |||||
Defined in Control.Monad.Trans.Maybe Associated Types
| |||||
| MonadIO m => MonadIO (MaybeT m) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| MonadZip m => MonadZip (MaybeT m) | |||||
| Eq1 m => Eq1 (MaybeT m) | |||||
| Ord1 m => Ord1 (MaybeT m) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| Read1 m => Read1 (MaybeT m) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| Show1 m => Show1 (MaybeT m) | |||||
| Contravariant m => Contravariant (MaybeT m) | |||||
| MonadCatch m => MonadCatch (MaybeT m) | Catches exceptions from the base monad. | ||||
Defined in Control.Monad.Catch | |||||
| MonadMask m => MonadMask (MaybeT m) | Since: exceptions-0.10.0 | ||||
Defined in Control.Monad.Catch Methods mask :: HasCallStack => ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b # uninterruptibleMask :: HasCallStack => ((forall a. MaybeT m a -> MaybeT m a) -> MaybeT m b) -> MaybeT m b # generalBracket :: HasCallStack => MaybeT m a -> (a -> ExitCase b -> MaybeT m c) -> (a -> MaybeT m b) -> MaybeT m (b, c) # | |||||
| MonadThrow m => MonadThrow (MaybeT m) | Throws exceptions into the base monad. | ||||
Defined in Control.Monad.Catch Methods throwM :: (HasCallStack, Exception e) => e -> MaybeT m a # | |||||
| (Functor m, Monad m) => Alternative (MaybeT m) | |||||
| (Functor m, Monad m) => Applicative (MaybeT m) | |||||
| Functor m => Functor (MaybeT m) | |||||
| Monad m => Monad (MaybeT m) | |||||
| Monad m => MonadPlus (MaybeT m) | |||||
| Monad m => MonadFail (MaybeT m) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| MonadFix m => MonadFix (MaybeT m) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| Foldable f => Foldable (MaybeT f) | |||||
Defined in Control.Monad.Trans.Maybe Methods fold :: Monoid m => MaybeT f m -> m # foldMap :: Monoid m => (a -> m) -> MaybeT f a -> m # foldMap' :: Monoid m => (a -> m) -> MaybeT f a -> m # foldr :: (a -> b -> b) -> b -> MaybeT f a -> b # foldr' :: (a -> b -> b) -> b -> MaybeT f a -> b # foldl :: (b -> a -> b) -> b -> MaybeT f a -> b # foldl' :: (b -> a -> b) -> b -> MaybeT f a -> b # foldr1 :: (a -> a -> a) -> MaybeT f a -> a # foldl1 :: (a -> a -> a) -> MaybeT f a -> a # elem :: Eq a => a -> MaybeT f a -> Bool # maximum :: Ord a => MaybeT f a -> a # minimum :: Ord a => MaybeT f a -> a # | |||||
| Traversable f => Traversable (MaybeT f) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| Generic (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe Associated Types
| |||||
| (Read1 m, Read a) => Read (MaybeT m a) | |||||
| (Show1 m, Show a) => Show (MaybeT m a) | |||||
| (Eq1 m, Eq a) => Eq (MaybeT m a) | |||||
| (Ord1 m, Ord a) => Ord (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| type Rep1 (MaybeT m :: Type -> Type) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
| type Rep (MaybeT m a) | |||||
Defined in Control.Monad.Trans.Maybe | |||||
liftCallCC :: CallCC m (Maybe a) (Maybe b) -> CallCC (MaybeT m) a b #
Lift a callCC operation to the new monad.
liftListen :: Monad m => Listen w m (Maybe a) -> Listen w (MaybeT m) a #
Lift a listen operation to the new monad.
liftPass :: Monad m => Pass w m (Maybe a) -> Pass w (MaybeT m) a #
Lift a pass operation to the new monad.
either :: (a -> c) -> (b -> c) -> Either a b -> c #
Case analysis for the Either type.
If the value is , apply the first function to Left aa;
if it is , apply the second function to Right bb.
Examples
We create two values of type , one using the
Either String IntLeft constructor and another using the Right constructor. Then
we apply "either" the length function (if we have a String)
or the "times-two" function (if we have an Int):
>>>let s = Left "foo" :: Either String Int>>>let n = Right 3 :: Either String Int>>>either length (*2) s3>>>either length (*2) n6
partitionEithers :: [Either a b] -> ([a], [b]) #
Partitions a list of Either into two lists.
All the Left elements are extracted, in order, to the first
component of the output. Similarly the Right elements are extracted
to the second component of the output.
Examples
Basic usage:
>>>let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]>>>partitionEithers list(["foo","bar","baz"],[3,7])
The pair returned by should be the same
pair as partitionEithers x(:lefts x, rights x)
>>>let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]>>>partitionEithers list == (lefts list, rights list)True
module Data.EitherR
maybe :: b -> (a -> b) -> Maybe a -> b #
The maybe function takes a default value, a function, and a Maybe
value. If the Maybe value is Nothing, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just and returns the result.
Examples
Basic usage:
>>>maybe False odd (Just 3)True
>>>maybe False odd NothingFalse
Read an integer from a string using readMaybe. If we succeed,
return twice the integer; that is, apply (*2) to it. If instead
we fail to parse an integer, return 0 by default:
>>>import GHC.Internal.Text.Read ( readMaybe )>>>maybe 0 (*2) (readMaybe "5")10>>>maybe 0 (*2) (readMaybe "")0
Apply show to a Maybe Int. If we have Just n, we want to show
the underlying Int n. But if we have Nothing, we return the
empty string instead of (for example) "Nothing":
>>>maybe "" show (Just 5)"5">>>maybe "" show Nothing""
fromMaybe :: a -> Maybe a -> a #
The fromMaybe function takes a default value and a Maybe
value. If the Maybe is Nothing, it returns the default value;
otherwise, it returns the value contained in the Maybe.
Examples
Basic usage:
>>>fromMaybe "" (Just "Hello, World!")"Hello, World!"
>>>fromMaybe "" Nothing""
Read an integer from a string using readMaybe. If we fail to
parse an integer, we want to return 0 by default:
>>>import GHC.Internal.Text.Read ( readMaybe )>>>fromMaybe 0 (readMaybe "5")5>>>fromMaybe 0 (readMaybe "")0
maybeToList :: Maybe a -> [a] #
The maybeToList function returns an empty list when given
Nothing or a singleton list when given Just.
Examples
Basic usage:
>>>maybeToList (Just 7)[7]
>>>maybeToList Nothing[]
One can use maybeToList to avoid pattern matching when combined
with a function that (safely) works on lists:
>>>import GHC.Internal.Text.Read ( readMaybe )>>>sum $ maybeToList (readMaybe "3")3>>>sum $ maybeToList (readMaybe "")0
listToMaybe :: [a] -> Maybe a #
The listToMaybe function returns Nothing on an empty list
or where Just aa is the first element of the list.
Examples
Basic usage:
>>>listToMaybe []Nothing
>>>listToMaybe [9]Just 9
>>>listToMaybe [1,2,3]Just 1
Composing maybeToList with listToMaybe should be the identity
on singleton/empty lists:
>>>maybeToList $ listToMaybe [5][5]>>>maybeToList $ listToMaybe [][]
But not on lists with more than one element:
>>>maybeToList $ listToMaybe [1,2,3][1]
catMaybes :: [Maybe a] -> [a] #
The catMaybes function takes a list of Maybes and returns
a list of all the Just values.
Examples
Basic usage:
>>>catMaybes [Just 1, Nothing, Just 3][1,3]
When constructing a list of Maybe values, catMaybes can be used
to return all of the "success" results (if the list is the result
of a map, then mapMaybe would be more appropriate):
>>>import GHC.Internal.Text.Read ( readMaybe )>>>[readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ][Just 1,Nothing,Just 3]>>>catMaybes $ [readMaybe x :: Maybe Int | x <- ["1", "Foo", "3"] ][1,3]
mapMaybe :: (a -> Maybe b) -> [a] -> [b] #
The mapMaybe function is a version of map which can throw
out elements. In particular, the functional argument returns
something of type . If this is Maybe bNothing, no element
is added on to the result list. If it is , then Just bb is
included in the result list.
Examples
Using is a shortcut for mapMaybe f x
in most cases:catMaybes $ map f x
>>>import GHC.Internal.Text.Read ( readMaybe )>>>let readMaybeInt = readMaybe :: String -> Maybe Int>>>mapMaybe readMaybeInt ["1", "Foo", "3"][1,3]>>>catMaybes $ map readMaybeInt ["1", "Foo", "3"][1,3]
If we map the Just constructor, the entire list should be returned:
>>>mapMaybe Just [1,2,3][1,2,3]
minimumMay :: Ord a => [a] -> Maybe a #
maximumMay :: Ord a => [a] -> Maybe a #
findJustDef :: a -> (a -> Bool) -> [a] -> a #
minimumDef :: Ord a => a -> [a] -> a #
New users are recommended to use minimumBound or maximumBound instead.
maximumDef :: Ord a => a -> [a] -> a #
New users are recommended to use minimumBound or maximumBound instead.
foldl1May' :: (a -> a -> a) -> [a] -> Maybe a #
fromJustDef :: a -> Maybe a -> a #
lookupJustDef :: Eq a => b -> a -> [(a, b)] -> b #
foldl1Def' :: a -> (a -> a -> a) -> [a] -> a #