| 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 |
Data.Either
Description
The Either type, and associated operations.
TheEither type represents values with two possibilities: a value oftype is eitherEither a b orLeft a.Right b
TheEither type is sometimes used to represent a value which iseither correct or an error; by convention, theLeft constructor isused to hold an error value and theRight constructor is used tohold a correct value (mnemonic: "right" also means "correct").
The type is the type of values which can be eitheraEitherStringIntString or anInt. TheLeft constructor can be used only onStrings, and theRight constructor can be used only onInts:
>>>let s = Left "foo" :: Either String Int>>>sLeft "foo">>>let n = Right 3 :: Either String Int>>>nRight 3>>>:type ss :: Either String Int>>>:type nn :: Either String Int
Thefmap from ourFunctor instance will ignoreLeft values, butwill apply the supplied function to values contained in aRight:
>>>let s = Left "foo" :: Either String Int>>>let n = Right 3 :: Either String Int>>>fmap (*2) sLeft "foo">>>fmap (*2) nRight 6
TheMonad instance forEither allows us to chain together multipleactions which may fail, and fail overall if any of the individualsteps failed. First we'll write a function that can either parse anInt from aChar, 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 beparsed asInts.
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleRight 3
But the following should fail overall, since the first operation wherewe attempt to parse'm' as anInt will fail:
>>>:{let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>:}
>>>parseMultipleLeft "parse error"
| Show2EitherSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Read2EitherSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.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# | |
| Ord2EitherSource# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Eq2EitherSource# | Since: 4.9.0.0 |
| BifunctorEitherSource# | Since: 4.8.0.0 |
| BifoldableEitherSource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bifoldable | |
| BitraversableEitherSource# | Since: 4.10.0.0 |
Instance detailsDefined inData.Bitraversable Methods bitraverse ::Applicative f => (a -> f c) -> (b -> f d) ->Either a b -> f (Either c d)Source# | |
| Monad (Either e)Source# | Since: 4.4.0.0 |
| Functor (Either a)Source# | Since: 3.0 |
| MonadFix (Either e)Source# | Since: 4.3.0.0 |
| Applicative (Either e)Source# | Since: 3.0 |
Instance detailsDefined inData.Either | |
| Foldable (Either a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Foldable Methods fold ::Monoid m =>Either a m -> mSource# foldMap ::Monoid m => (a0 -> m) ->Either a a0 -> mSource# foldr :: (a0 -> b -> b) -> b ->Either a a0 -> bSource# foldr' :: (a0 -> b -> b) -> b ->Either a a0 -> bSource# foldl :: (b -> a0 -> b) -> b ->Either a a0 -> bSource# foldl' :: (b -> a0 -> b) -> b ->Either a a0 -> bSource# foldr1 :: (a0 -> a0 -> a0) ->Either a a0 -> a0Source# foldl1 :: (a0 -> a0 -> a0) ->Either a a0 -> a0Source# toList ::Either a a0 -> [a0]Source# null ::Either a a0 ->BoolSource# length ::Either a a0 ->IntSource# elem ::Eq a0 => a0 ->Either a a0 ->BoolSource# maximum ::Ord a0 =>Either a a0 -> a0Source# minimum ::Ord a0 =>Either a a0 -> a0Source# | |
| Traversable (Either a)Source# | Since: 4.7.0.0 |
Instance detailsDefined inData.Traversable | |
| Show a =>Show1 (Either a)Source# | Since: 4.9.0.0 |
| Read a =>Read1 (Either a)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.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)Source# | Since: 4.9.0.0 |
Instance detailsDefined inData.Functor.Classes | |
| Eq a =>Eq1 (Either a)Source# | Since: 4.9.0.0 |
| Generic1 (Either a ::Type ->Type)Source# | |
| (Eq a,Eq b) =>Eq (Either a b)Source# | Since: 2.1 |
| (Data a,Data b) =>Data (Either a b)Source# | Since: 4.0.0.0 |
Instance detailsDefined inData.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 ->ConstrSource# dataTypeOf ::Either a b ->DataTypeSource# 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 bSource# gmapQl :: (r -> r' -> r) -> r -> (forall d.Data d => d -> r') ->Either a b -> rSource# gmapQr :: (r' -> r -> r) -> r -> (forall d.Data d => d -> r') ->Either a b -> rSource# gmapQ :: (forall d.Data d => d -> u) ->Either a b -> [u]Source# gmapQi ::Int -> (forall d.Data d => d -> u) ->Either a b -> uSource# 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)Source# | Since: 2.1 |
Instance detailsDefined inData.Either | |
| (Read a,Read b) =>Read (Either a b)Source# | Since: 3.0 |
| (Show a,Show b) =>Show (Either a b)Source# | Since: 3.0 |
| Generic (Either a b)Source# | |
| Semigroup (Either a b)Source# | Since: 4.9.0.0 |
| typeRep1 (Either a ::Type ->Type)Source# | Since: 4.6.0.0 |
Instance detailsDefined inGHC.Generics typeRep1 (Either a ::Type ->Type) =D1 (MetaData "Either" "Data.Either" "base"False) (C1 (MetaCons "Left"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)):+:C1 (MetaCons "Right"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy)Par1)) | |
| typeRep (Either a b)Source# | Since: 4.6.0.0 |
Instance detailsDefined inGHC.Generics typeRep (Either a b) =D1 (MetaData "Either" "Data.Either" "base"False) (C1 (MetaCons "Left"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 a)):+:C1 (MetaCons "Right"PrefixIFalse) (S1 (MetaSel (Nothing ::MaybeSymbol)NoSourceUnpackednessNoSourceStrictnessDecidedLazy) (Rec0 b))) | |
either :: (a -> c) -> (b -> c) ->Either a b -> cSource#
Case analysis for theEither type. If the value is, apply the first function toLeft aa; if it is, apply the second function toRight bb.
We create two values of type, one using theEitherStringIntLeft constructor and another using theRight constructor. Then we apply "either" thelength function (if we have aString) or the "times-two" function (if we have anInt):
>>>let s = Left "foo" :: Either String Int>>>let n = Right 3 :: Either String Int>>>either length (*2) s3>>>either length (*2) n6
isLeft ::Either a b ->BoolSource#
ReturnTrue if the given value is aLeft-value,False otherwise.
Basic usage:
>>>isLeft (Left "foo")True>>>isLeft (Right 3)False
Assuming aLeft value signifies some sort of error, we can useisLeft 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 howisLeft 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 ->BoolSource#
ReturnTrue if the given value is aRight-value,False otherwise.
Basic usage:
>>>isRight (Left "foo")False>>>isRight (Right 3)True
Assuming aLeft value signifies some sort of error, we can useisRight to write a very simple reporting function that only outputs "SUCCESS" when a computation has succeeded.
This example shows howisRight 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 -> aSource#
Return the contents of aLeft-value or a default value otherwise.
Basic usage:
>>>fromLeft 1 (Left 3)3>>>fromLeft 1 (Right "foo")1
Since: 4.10.0.0
fromRight :: b ->Either a b -> bSource#
Return the contents of aRight-value or a default value otherwise.
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 ofEither into two lists. All theLeft elements are extracted, in order, to the first component of the output. Similarly theRight 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 should be the same pair aspartitionEithers x(:lefts x,rights x)
>>>let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]>>>partitionEithers list == (lefts list, rights list)True
Produced byHaddock version 2.20.0