Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | [email protected] |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
The Either type, and associated operations.
The Either
type represents values with two possibilities: a value of type Either a b
is either Left a
or Right b
.
The Either
type is sometimes used to represent a value which is either correct or an error; by convention, the Left
constructor is used to hold an error value and the Right
constructor is used to hold a correct value (mnemonic: "right" also means "correct").
The type Either String Int
is the type of values which can be either a String
or an Int
. The Left
constructor can be used only on String
s, and the Right
constructor can be used only on Int
s:
>>> let s = Left "foo" :: Either String Int >>> s Left "foo" >>> let n = Right 3 :: Either String Int >>> n Right 3 >>> :type s s :: Either String Int >>> :type n n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but will apply the supplied function to values contained in a Right
:
>>> let s = Left "foo" :: Either String Int >>> let n = Right 3 :: Either String Int >>> fmap (*2) s Left "foo" >>> fmap (*2) n Right 6
The Monad
instance for Either
allows us to chain together multiple actions which may fail, and fail overall if any of the individual steps failed. First we'll write a function that can either parse an Int
from a Char
, or fail.
>>> import Data.Char ( digitToInt, isDigit ) >>> :{ let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error" >>> :}
The following should work, since both '1'
and '2'
can be parsed as Int
s.
>>> :{ let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y) >>> :}
>>> parseMultiple Right 3
But the following should fail overall, since the first operation where we attempt to parse 'm'
as an Int
will fail:
>>> :{ let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y) >>> :}
>>> parseMultiple Left "parse error"
Show2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes MethodsliftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) Source liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] Source liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) Source liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] Source | |
Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq2 Either | Since: base-4.9.0.0 |
Bifunctor Either | Since: base-4.8.0.0 |
Bifoldable Either | Since: base-4.10.0.0 |
Bitraversable Either | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methodsbitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) Source | |
Monad (Either e) | Since: base-4.4.0.0 |
Functor (Either a) | Since: base-3.0 |
MonadFix (Either e) | Since: base-4.3.0.0 |
Defined in Control.Monad.Fix | |
Applicative (Either e) | Since: base-3.0 |
Defined in Data.Either | |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methodsfold :: Monoid m => Either a m -> m Source foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m Source foldMap' :: Monoid m => (a0 -> m) -> Either a a0 -> m Source foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b Source foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b Source foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b Source foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b Source foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 Source toList :: Either a a0 -> [a0] Source null :: Either a a0 -> Bool Source length :: Either a a0 -> Int Source elem :: Eq a0 => a0 -> Either a a0 -> Bool Source maximum :: Ord a0 => Either a a0 -> a0 Source minimum :: Ord a0 => Either a a0 -> a0 Source | |
Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes MethodsliftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) Source liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] Source liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) Source liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] Source | |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Generic1 (Either a :: Type -> Type) | Since: base-4.6.0.0 |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methodsgfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) Source gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) Source toConstr :: Either a b -> Constr Source dataTypeOf :: Either a b -> DataType Source dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) Source dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) Source gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b Source gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r Source gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] Source gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u Source gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) Source | |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
Defined in Data.Either Methodscompare :: Either a b -> Either a b -> Ordering Source (<) :: Either a b -> Either a b -> Bool Source (<=) :: Either a b -> Either a b -> Bool Source (>) :: Either a b -> Either a b -> Bool Source (>=) :: Either a b -> Either a b -> Bool Source | |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
Generic (Either a b) | Since: base-4.6.0.0 |
Semigroup (Either a b) | Since: base-4.9.0.0 |
type Rep1 (Either a :: Type -> Type) | |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1)) | |
type Rep (Either a b) | |
Defined in GHC.Generics type Rep (Either a b) = D1 ('MetaData "Either" "Data.Either" "base" 'False) (C1 ('MetaCons "Left" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "Right" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b))) |
either :: (a -> c) -> (b -> c) -> Either a b -> c Source
Case analysis for the Either
type. If the value is Left a
, apply the first function to a
; if it is Right b
, apply the second function to b
.
We create two values of type Either String Int
, one using the Left
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) s 3 >>> either length (*2) n 6
lefts :: [Either a b] -> [a] Source
Extracts from a list of Either
all the Left
elements. All the Left
elements are extracted in order.
Basic usage:
>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] >>> lefts list ["foo","bar","baz"]
rights :: [Either a b] -> [b] Source
Extracts from a list of Either
all the Right
elements. All the Right
elements are extracted in order.
Basic usage:
>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] >>> rights list [3,7]
isLeft :: Either a b -> Bool Source
Return True
if the given value is a Left
-value, False
otherwise.
Basic usage:
>>> isLeft (Left "foo") True >>> isLeft (Right 3) False
Assuming a Left
value signifies some sort of error, we can use isLeft
to write a very simple error-reporting function that does absolutely nothing in the case of success, and outputs "ERROR" if any error occurred.
This example shows how isLeft
might be used to avoid pattern matching when one does not care about the value contained in the constructor:
>>> import Control.Monad ( when ) >>> let report e = when (isLeft e) $ putStrLn "ERROR" >>> report (Right 1) >>> report (Left "parse error") ERROR
Since: base-4.7.0.0
isRight :: Either a b -> Bool Source
Return True
if the given value is a Right
-value, False
otherwise.
Basic usage:
>>> isRight (Left "foo") False >>> isRight (Right 3) True
Assuming a Left
value signifies some sort of error, we can use isRight
to write a very simple reporting function that only outputs "SUCCESS" when a computation has succeeded.
This example shows how isRight
might be used to avoid pattern matching when one does not care about the value contained in the constructor:
>>> import Control.Monad ( when ) >>> let report e = when (isRight e) $ putStrLn "SUCCESS" >>> report (Left "parse error") >>> report (Right 1) SUCCESS
Since: base-4.7.0.0
fromLeft :: a -> Either a b -> a Source
Return the contents of a Left
-value or a default value otherwise.
Basic usage:
>>> fromLeft 1 (Left 3) 3 >>> fromLeft 1 (Right "foo") 1
Since: base-4.10.0.0
fromRight :: b -> Either a b -> b Source
Return the contents of a Right
-value or a default value otherwise.
Basic usage:
>>> fromRight 1 (Right 3) 3 >>> fromRight 1 (Left "foo") 1
Since: base-4.10.0.0
partitionEithers :: [Either a b] -> ([a], [b]) Source
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.
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 partitionEithers x
should be the same pair as (lefts x, rights x)
:
>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ] >>> partitionEithers list == (lefts list, rights list) True
© The University of Glasgow and others
Licensed under a BSD-style license (see top of the page).
https://downloads.haskell.org/~ghc/8.8.3/docs/html/libraries/base-4.13.0.0/Data-Either.html