base-4.15.0.0: Basic libraries
Copyright(c) The University of Glasgow 2001
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilityexperimental
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Either

Description

The Either type, and associated operations.

Synopsis

Documentation

data Either a b Source #

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").

Examples

Expand

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 Strings, and the Right constructor can be used only on Ints:

>>> 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 Ints.

>>> :{
    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"

Constructors

Left a 
Right b 

Instances

Instances details
Show2 Either #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> Either a b -> ShowS Source #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [Either a b] -> ShowS Source #

Read2 Either #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec2 :: (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

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering Source #

Eq2 Either #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Either a c -> Either b d -> Bool Source #

Bifunctor Either #

Since: base-4.8.0.0

Instance details

Defined in Data.Bifunctor

Methods

bimap :: (a -> b) -> (c -> d) -> Either a c -> Either b d Source #

first :: (a -> b) -> Either a c -> Either b c Source #

second :: (b -> c) -> Either a b -> Either a c Source #

Bifoldable Either #

Since: base-4.10.0.0

Instance details

Defined in Data.Bifoldable

Methods

bifold :: Monoid m => Either m m -> m Source #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Either a b -> m Source #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Either a b -> c Source #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Either a b -> c Source #

Bitraversable Either #

Since: base-4.10.0.0

Instance details

Defined in Data.Bitraversable

Methods

bitraverse :: 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

Instance details

Defined in Data.Either

Methods

(>>=) :: Either e a -> (a -> Either e b) -> Either e b Source #

(>>) :: Either e a -> Either e b -> Either e b Source #

return :: a -> Either e a Source #

Functor (Either a) #

Since: base-3.0

Instance details

Defined in Data.Either

Methods

fmap :: (a0 -> b) -> Either a a0 -> Either a b Source #

(<$) :: a0 -> Either a b -> Either a a0 Source #

MonadFix (Either e) #

Since: base-4.3.0.0

Instance details

Defined in Control.Monad.Fix

Methods

mfix :: (a -> Either e a) -> Either e a Source #

Applicative (Either e) #

Since: base-3.0

Instance details

Defined in Data.Either

Methods

pure :: a -> Either e a Source #

(<*>) :: Either e (a -> b) -> Either e a -> Either e b Source #

liftA2 :: (a -> b -> c) -> Either e a -> Either e b -> Either e c Source #

(*>) :: Either e a -> Either e b -> Either e b Source #

(<*) :: Either e a -> Either e b -> Either e a Source #

Foldable (Either a) #

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: 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 #

sum :: Num a0 => Either a a0 -> a0 Source #

product :: Num a0 => Either a a0 -> a0 Source #

Traversable (Either a) #

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a0 -> f b) -> Either a a0 -> f (Either a b) Source #

sequenceA :: Applicative f => Either a (f a0) -> f (Either a a0) Source #

mapM :: Monad m => (a0 -> m b) -> Either a a0 -> m (Either a b) Source #

sequence :: Monad m => Either a (m a0) -> m (Either a a0) Source #

Show a => Show1 (Either a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> Either a a0 -> ShowS Source #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [Either a a0] -> ShowS Source #

Read a => Read1 (Either a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (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

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a0 -> b -> Ordering) -> Either a a0 -> Either a b -> Ordering Source #

Eq a => Eq1 (Either a) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a0 -> b -> Bool) -> Either a a0 -> Either a b -> Bool Source #

Generic1 (Either a :: Type -> Type) #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (Either a) :: k -> Type Source #

Methods

from1 :: forall (a0 :: k). Either a a0 -> Rep1 (Either a) a0 Source #

to1 :: forall (a0 :: k). Rep1 (Either a) a0 -> Either a a0 Source #

(Eq a, Eq b) => Eq (Either a b) #

Since: base-2.1

Instance details

Defined in Data.Either

Methods

(==) :: Either a b -> Either a b -> Bool Source #

(/=) :: Either a b -> Either a b -> Bool Source #

(Data a, Data b) => Data (Either a b) #

Since: base-4.0.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (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

Instance details

Defined in Data.Either

Methods

compare :: 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 #

max :: Either a b -> Either a b -> Either a b Source #

min :: Either a b -> Either a b -> Either a b Source #

(Read a, Read b) => Read (Either a b) #

Since: base-3.0

Instance details

Defined in Data.Either

(Show a, Show b) => Show (Either a b) #

Since: base-3.0

Instance details

Defined in Data.Either

Methods

showsPrec :: Int -> Either a b -> ShowS Source #

show :: Either a b -> String Source #

showList :: [Either a b] -> ShowS Source #

Generic (Either a b) #

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep (Either a b) :: Type -> Type Source #

Methods

from :: Either a b -> Rep (Either a b) x Source #

to :: Rep (Either a b) x -> Either a b Source #

Semigroup (Either a b) #

Since: base-4.9.0.0

Instance details

Defined in Data.Either

Methods

(<>) :: Either a b -> Either a b -> Either a b Source #

sconcat :: NonEmpty (Either a b) -> Either a b Source #

stimes :: Integral b0 => b0 -> Either a b -> Either a b Source #

type Rep1 (Either a :: Type -> Type) # 
Instance details

Defined in GHC.Generics

type Rep (Either a b) # 
Instance details

Defined in GHC.Generics

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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.

Examples

Expand

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