Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module contains useful functions for working with Either
s.
Synopsis
- data Either a b
- either :: (a %1 -> c) -> (b %1 -> c) -> Either a b %1 -> c
- lefts :: Consumable b => [Either a b] %1 -> [a]
- rights :: Consumable a => [Either a b] %1 -> [b]
- fromLeft :: (Consumable a, Consumable b) => a %1 -> Either a b %1 -> a
- fromRight :: (Consumable a, Consumable b) => b %1 -> Either a b %1 -> b
- partitionEithers :: [Either a b] %1 -> ([a], [b])
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"
Instances
either :: (a %1 -> c) -> (b %1 -> c) -> Either a b %1 -> c Source #
Linearly consume an Either
by applying the first linear function on a
value constructed with Left
and the second linear function on a value
constructed with Right
.
lefts :: Consumable b => [Either a b] %1 -> [a] Source #
Get all the left elements in order, and consume the right ones.
rights :: Consumable a => [Either a b] %1 -> [b] Source #
Get all the right elements in order, and consume the left ones.
fromLeft :: (Consumable a, Consumable b) => a %1 -> Either a b %1 -> a Source #
Get the left element of a consumable Either
with a default
fromRight :: (Consumable a, Consumable b) => b %1 -> Either a b %1 -> b Source #
Get the right element of a consumable Either
with a default
partitionEithers :: [Either a b] %1 -> ([a], [b]) Source #
Partition and consume a list of Either
s into two lists with all the
lefts in one and the rights in the second, in the order they appeared in the
initial list.