| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Prologue.Data.Either
Synopsis
- eitherIf :: Bool -> ok -> fail -> Either fail ok
- fromRight :: r -> Either l r -> r
- fromRightM :: Applicative m => m r -> Either l r -> m r
- fromLeft :: l -> Either l r -> l
- fromLeftM :: Applicative m => m l -> Either l r -> m l
- unsafeFromRightM :: (Monad m, MonadFail m) => Either l r -> m r
- unsafeFromRight :: Either l r -> r
- unsafeFromLeftM :: (Monad m, MonadFail m) => Either l r -> m l
- unsafeFromLeft :: Either l r -> l
- withRight :: (Applicative m, Mempty out) => Either l r -> (r -> m out) -> m out
- withRight_ :: Applicative m => Either l r -> (r -> m out) -> m ()
- withRightM :: (Monad m, Mempty out) => m (Either l r) -> (r -> m out) -> m out
- withRightM_ :: Monad m => m (Either l r) -> (r -> m out) -> m ()
- withLeft :: (Applicative m, Mempty out) => Either l r -> (l -> m out) -> m out
- withLeft_ :: Applicative m => Either l r -> (l -> m out) -> m ()
- withLeftM :: (Monad m, Mempty out) => m (Either l r) -> (l -> m out) -> m out
- withLeftM_ :: Monad m => m (Either l r) -> (l -> m out) -> m ()
- whenRight :: (Applicative m, Mempty out) => Either l r -> m out -> m out
- whenRight_ :: Applicative m => Either l r -> m out -> m ()
- whenRightM :: (Monad m, Mempty out) => m (Either l r) -> m out -> m out
- whenRightM_ :: Monad m => m (Either l r) -> m out -> m ()
- whenLeft :: (Applicative m, Mempty out) => Either l r -> m out -> m out
- whenLeft_ :: Applicative m => Either l r -> m out -> m ()
- whenLeftM :: (Monad m, Mempty out) => m (Either l r) -> m out -> m out
- whenLeftM_ :: Monad m => m (Either l r) -> m out -> m ()
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- partitionEithers :: [Either a b] -> ([a], [b])
- swapEither :: Either e a -> Either a e
- rightToMaybe :: Either a b -> Maybe b
- leftToMaybe :: Either a b -> Maybe a
- mapRight :: (b -> c) -> Either a b -> Either a c
- mapLeft :: (a -> c) -> Either a b -> Either c b
- isRight :: Either a b -> Bool
- isLeft :: Either a b -> Bool
Documentation
fromRightM :: Applicative m => m r -> Either l r -> m r Source #
fromLeftM :: Applicative m => m l -> Either l r -> m l Source #
unsafeFromRight :: Either l r -> r Source #
Warning: Do not use in production code
unsafeFromLeft :: Either l r -> l Source #
Warning: Do not use in production code
withRight_ :: Applicative m => Either l r -> (r -> m out) -> m () Source #
withRightM_ :: Monad m => m (Either l r) -> (r -> m out) -> m () Source #
withLeft_ :: Applicative m => Either l r -> (l -> m out) -> m () Source #
withLeftM_ :: Monad m => m (Either l r) -> (l -> m out) -> m () Source #
whenRight_ :: Applicative m => Either l r -> m out -> m () Source #
whenRightM_ :: Monad m => m (Either l r) -> m out -> m () Source #
whenLeft_ :: Applicative m => Either l r -> m out -> m () 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 , 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
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
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
swapEither :: Either e a -> Either a e #
rightToMaybe :: Either a b -> Maybe b #
Maybe get the Right side of an Either.
rightToMaybe≡either(constNothing)Just
Using Control.Lens:
rightToMaybe≡ preview _RightrightToMaybex ≡ 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.
leftToMaybe≡eitherJust(constNothing)
Using Control.Lens:
leftToMaybe≡ preview _LeftleftToMaybex ≡ 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"