unpacked-either-0.1.0.0: An unpacked either data type

Safe HaskellNone
LanguageHaskell2010

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 Either type as two machine words that are contiguous in memory, without loss of expressiveness that Data.Either provides.

This library provides pattern synonyms Left and Right that allow users to pattern match on an unpacked Either in a familiar way.

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.

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

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

Either (#a | b#) 

Bundled Patterns

pattern Left :: a -> Either a b

The Left pattern synonym mimics the functionality of base's Left constructor

pattern Right :: b -> Either a b

The Right pattern synonym mimics the functionality of base's Right constructor

Instances

Bitraversable Either Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) #

Bifoldable Either Source # 

Methods

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

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

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

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

Bifunctor Either Source # 

Methods

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

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

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

Eq2 Either Source # 

Methods

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

Ord2 Either Source # 

Methods

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

Read2 Either Source # 

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] #

Show2 Either Source # 

Methods

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

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

Monad (Either e) Source # 

Methods

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

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

return :: a -> Either e a #

fail :: String -> Either e a #

Functor (Either a) Source # 

Methods

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

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

Applicative (Either e) Source # 

Methods

pure :: a -> Either e a #

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

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

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

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

Foldable (Either a) Source # 

Methods

fold :: Monoid m => Either a m -> m #

foldMap :: Monoid m => (a -> m) -> Either a a -> m #

foldr :: (a -> b -> b) -> b -> Either a a -> b #

foldr' :: (a -> b -> b) -> b -> Either a a -> b #

foldl :: (b -> a -> b) -> b -> Either a a -> b #

foldl' :: (b -> a -> b) -> b -> Either a a -> b #

foldr1 :: (a -> a -> a) -> Either a a -> a #

foldl1 :: (a -> a -> a) -> Either a a -> a #

toList :: Either a a -> [a] #

null :: Either a a -> Bool #

length :: Either a a -> Int #

elem :: Eq a => a -> Either a a -> Bool #

maximum :: Ord a => Either a a -> a #

minimum :: Ord a => Either a a -> a #

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

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

Traversable (Either a) Source # 

Methods

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

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

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

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

Eq a => Eq1 (Either a) Source # 

Methods

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

Ord a => Ord1 (Either a) Source # 

Methods

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

Read a => Read1 (Either a) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Either a a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Either a a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Either a a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Either a a] #

Show a => Show1 (Either a) Source # 

Methods

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

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

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

Methods

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

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

(Ord a, Ord b) => Ord (Either a b) Source # 

Methods

compare :: Either a b -> Either a b -> Ordering #

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

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

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

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

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

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

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

Methods

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

show :: Either a b -> String #

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

Semigroup b => Semigroup (Either a b) Source # 

Methods

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

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

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

Monoid b => Monoid (Either a b) Source # 

Methods

mempty :: Either a b #

mappend :: Either a b -> Either a b -> Either a b #

mconcat :: [Either a b] -> Either a b #

left :: a -> Either a b Source #

This is the same as Left.

right :: b -> Either a b Source #

This is the same as Right.

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

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

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

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

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

Basic usage:

>>> let list = [ Left "foo", Right 3, Left "bar", Right 7, Left "baz" ]
>>> rights list
[3,7]

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

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]