| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Either.Unpacked
Description
This module is intended to be a drop-in replacement
for base's Data.Either. To shave off pointer chasing, it
uses '-XUnboxedSums' to represent the type
as two machine words that are contiguous in memory, without
loss of expressiveness that Data.Either provides.Either
This library provides pattern synonyms and Left
that allow users to pattern match on an unpacked Either
in a familiar way.Right
Functions are also provided for converting an unpacked Either to the base library's Either, and vice versa.
This library is in alpha, and the internals are likely to change.
- data Either a b where
- left :: a -> Either a b
- right :: b -> Either a b
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- isLeft :: Either a b -> Bool
- isRight :: Either a b -> Bool
- lefts :: [Either a b] -> [a]
- rights :: [Either a b] -> [b]
- partitionEithers :: [Either a b] -> ([a], [b])
- fromLeft :: a -> Either a b -> a
- fromRight :: b -> Either a b -> b
- fromBaseEither :: Either a b -> Either a b
- toBaseEither :: Either a b -> Either 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 IntString 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>>>sLeft "foo">>>let n = Right 3 :: Either String Int>>>nRight 3>>>:type ss :: Either String Int>>>:type nn :: 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) sLeft "foo">>>fmap (*2) nRight 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)>>>:}
>>>parseMultipleRight 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)>>>:}
>>>parseMultipleLeft "parse error"
Constructors
| Either (#a | b#) |
Bundled Patterns
| pattern Left :: a -> Either a b | The |
| pattern Right :: b -> Either a b | The |
Instances
| Bitraversable Either Source # | |
| Bifoldable Either Source # | |
| Bifunctor Either Source # | |
| Eq2 Either Source # | |
| Ord2 Either Source # | |
| Read2 Either Source # | |
| Show2 Either Source # | |
| Monad (Either e) Source # | |
| Functor (Either a) Source # | |
| Applicative (Either e) Source # | |
| Foldable (Either a) Source # | |
| Traversable (Either a) Source # | |
| Eq a => Eq1 (Either a) Source # | |
| Ord a => Ord1 (Either a) Source # | |
| Read a => Read1 (Either a) Source # | |
| Show a => Show1 (Either a) Source # | |
| (Eq a, Eq b) => Eq (Either a b) Source # | |
| (Ord a, Ord b) => Ord (Either a b) Source # | |
| (Read a, Read b) => Read (Either a b) Source # | |
| (Show b, Show a) => Show (Either a b) Source # | |
| Semigroup b => Semigroup (Either a b) Source # | |
| Monoid b => Monoid (Either a b) Source # | |
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 IntLeft 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) s3>>>either length (*2) n6
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
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
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
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
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
fromBaseEither :: Either a b -> Either a b Source #
The fromBaseEither function converts base's Either to an
Either. This function is good for using
existing functions that return base's Either values.
Examples
Basic usage:
>>>import Text.Read ( readEither )>>>let parse = fromBaseEither . readEither :: String -> Either String Int>>>parse "3"Right 3>>>parse ""Left "Prelude.read: no parse"
toBaseEither :: Either a b -> Either a b Source #
The toBaseEither function converts an Either value to a
value of base's Either type.
This function is provided for testing an convenience but
it is not an idiomatic use of this library. It ruins the speed and space gains from
unpacking the Either. I implore you to destruct the Either with either instead.
Examples
Basic usage:
>>>import Data.List (unfoldr)>>>let ana n = if n == 5 then (left "stop here") else right (n+1,n+1)>>>unfoldr (toBaseMaybe . ana) 0[1,2,3,4,5]