prologue-3.2.6: Better, more general Prelude exporting common utilities.

Safe HaskellNone
LanguageHaskell2010

Prologue.Data.Either

Synopsis

Documentation

eitherIf :: Bool -> ok -> fail -> Either fail ok Source #

fromRight :: r -> Either l r -> r Source #

fromRightM :: Applicative m => m r -> Either l r -> m r Source #

fromLeft :: l -> Either l r -> l Source #

fromLeftM :: Applicative m => m l -> Either l r -> m l Source #

unsafeFromRightM :: (Monad m, MonadFail m) => Either l r -> m r Source #

unsafeFromRight :: Either l r -> r Source #

Warning: Do not use in production code

unsafeFromLeftM :: (Monad m, MonadFail m) => Either l r -> m l Source #

unsafeFromLeft :: Either l r -> l Source #

Warning: Do not use in production code

withRight :: (Applicative m, Mempty out) => Either l r -> (r -> m out) -> m out Source #

withRight_ :: Applicative m => Either l r -> (r -> m out) -> m () Source #

withRightM :: (Monad m, Mempty out) => m (Either l r) -> (r -> m out) -> m out Source #

withRightM_ :: Monad m => m (Either l r) -> (r -> m out) -> m () Source #

withLeft :: (Applicative m, Mempty out) => Either l r -> (l -> m out) -> m out Source #

withLeft_ :: Applicative m => Either l r -> (l -> m out) -> m () Source #

withLeftM :: (Monad m, Mempty out) => m (Either l r) -> (l -> m out) -> m out Source #

withLeftM_ :: Monad m => m (Either l r) -> (l -> m out) -> m () Source #

whenRight :: (Applicative m, Mempty out) => Either l r -> m out -> m out Source #

whenRight_ :: Applicative m => Either l r -> m out -> m () Source #

whenRightM :: (Monad m, Mempty out) => m (Either l r) -> m out -> m out Source #

whenRightM_ :: Monad m => m (Either l r) -> m out -> m () Source #

whenLeft :: (Applicative m, Mempty out) => Either l r -> m out -> m out Source #

whenLeft_ :: Applicative m => Either l r -> m out -> m () Source #

whenLeftM :: (Monad m, Mempty out) => m (Either l r) -> m out -> m out Source #

whenLeftM_ :: Monad m => m (Either l r) -> m out -> m () Source #

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

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

partitionEithers :: [Either a b] -> ([a], [b]) #

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

swapEither :: Either e a -> Either a e #

Swap the Left and Right sides of an Either.

>>> swapEither (Right 3)
Left 3

>>> swapEither (Left "error")
Right "error"

rightToMaybe :: Either a b -> Maybe b #

Maybe get the Right side of an Either.

rightToMaybeeither (const Nothing) Just

Using Control.Lens:

rightToMaybe ≡ preview _Right
rightToMaybe x ≡ x^?_Right
>>> rightToMaybe (Left 12)
Nothing
>>> rightToMaybe (Right 12)
Just 12

leftToMaybe :: Either a b -> Maybe a #

Maybe get the Left side of an Either.

leftToMaybeeither Just (const Nothing)

Using Control.Lens:

leftToMaybe ≡ preview _Left
leftToMaybe x ≡ x^?_Left
>>> leftToMaybe (Left 12)
Just 12
>>> leftToMaybe (Right 12)
Nothing

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

The mapRight function takes a function and applies it to an Either value iff the value takes the form Right _.

Using Data.Bifunctor:

mapRight = second

Using Control.Arrow:

mapRight = (right)

Using Control.Lens:

mapRight = over _Right
>>> mapRight (*2) (Left "hello")
Left "hello"
>>> mapRight (*2) (Right 4)
Right 8

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

The mapLeft function takes a function and applies it to an Either value iff the value takes the form Left _.

Using Data.Bifunctor:

mapLeft = first

Using Control.Arrow:

mapLeft = (left)

Using Control.Lens:

mapLeft = over _Left
>>> mapLeft (*2) (Left 4)
Left 8
>>> mapLeft (*2) (Right "hello")
Right "hello"

isRight :: Either a b -> Bool #

The isRight function returns True iff its argument is of the form Right _.

Using Control.Lens:

isRight ≡ has _Right
>>> isRight (Left 12)
False
>>> isRight (Right 12)
True

isLeft :: Either a b -> Bool #

The isLeft function returns True iff its argument is of the form Left _.

Using Control.Lens:

isLeft ≡ has _Left
>>> isLeft (Left 12)
True
>>> isLeft (Right 12)
False