Copyright | (c) The University of Glasgow 2001 |
---|---|
License | BSD-style (see the file libraries/base/LICENSE) |
Maintainer | libraries@haskell.org |
Stability | experimental |
Portability | portable |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
The Either type, and associated operations.
Documentation
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.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").
Examples
The type
is the type of values which can be either
a Either
String
Int
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: 4.9.0.0 |
Read2 Either # | Since: 4.9.0.0 |
Ord2 Either # | Since: 4.9.0.0 |
Eq2 Either # | Since: 4.9.0.0 |
Bifunctor Either # | Since: 4.8.0.0 |
Bifoldable Either # | Since: 4.10.0.0 |
Bitraversable Either # | Since: 4.10.0.0 |
Monad (Either e) # | Since: 4.4.0.0 |
Functor (Either a) # | Since: 3.0 |
MonadFix (Either e) # | Since: 4.3.0.0 |
Applicative (Either e) # | Since: 3.0 |
Foldable (Either a) # | Since: 4.7.0.0 |
Traversable (Either a) # | Since: 4.7.0.0 |
Show a => Show1 (Either a) # | Since: 4.9.0.0 |
Read a => Read1 (Either a) # | Since: 4.9.0.0 |
Ord a => Ord1 (Either a) # | Since: 4.9.0.0 |
Eq a => Eq1 (Either a) # | Since: 4.9.0.0 |
Generic1 * (Either a) # | |
(Eq b, Eq a) => Eq (Either a b) # | |
(Data a, Data b) => Data (Either a b) # | Since: 4.0.0.0 |
(Ord b, Ord a) => Ord (Either a b) # | |
(Read b, Read a) => Read (Either a b) # | |
(Show b, Show a) => Show (Either a b) # | |
Generic (Either a b) # | |
Semigroup (Either a b) # | Since: 4.9.0.0 |
type Rep1 * (Either a) # | |
type Rep (Either a b) # | |
type (==) (Either k1 k2) a b # | |
either :: (a -> c) -> (b -> c) -> Either a b -> c Source #
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
Int
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
isLeft :: Either a b -> Bool Source #
Return True
if the given value is a Left
-value, False
otherwise.
Examples
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: 4.7.0.0
isRight :: Either a b -> Bool Source #
Return True
if the given value is a Right
-value, False
otherwise.
Examples
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: 4.7.0.0
fromLeft :: a -> Either a b -> a Source #
Return the contents of a Left
-value or a default value otherwise.
Examples
Basic usage:
>>>
fromLeft 1 (Left 3)
3>>>
fromLeft 1 (Right "foo")
1
Since: 4.10.0.0
fromRight :: b -> Either a b -> b Source #
Return the contents of a Right
-value or a default value otherwise.
Examples
Basic usage:
>>>
fromRight 1 (Right 3)
3>>>
fromRight 1 (Left "foo")
1
Since: 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.
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