Copyright | (c) 2016 Stephen Diehl (c) 2016-2018 Serokell (c) 2018-2021 Kowainik |
---|---|
License | MIT |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Utilities to work with Either
data type.
Synopsis
- fromLeft :: a -> Either a b -> a
- fromRight :: b -> Either a b -> b
- maybeToLeft :: r -> Maybe l -> Either l r
- maybeToRight :: l -> Maybe r -> Either l r
- leftToMaybe :: Either l r -> Maybe l
- rightToMaybe :: Either l r -> Maybe r
- whenLeft :: Applicative f => a -> Either l r -> (l -> f a) -> f a
- whenLeft_ :: Applicative f => Either l r -> (l -> f ()) -> f ()
- whenLeftM :: Monad m => a -> m (Either l r) -> (l -> m a) -> m a
- whenLeftM_ :: Monad m => m (Either l r) -> (l -> m ()) -> m ()
- whenRight :: Applicative f => a -> Either l r -> (r -> f a) -> f a
- whenRight_ :: Applicative f => Either l r -> (r -> f ()) -> f ()
- whenRightM :: Monad m => a -> m (Either l r) -> (r -> m a) -> m a
- whenRightM_ :: Monad m => m (Either l r) -> (r -> m ()) -> m ()
Combinators
fromLeft :: a -> Either a b -> a #
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
Since: base-4.10.0.0
fromRight :: b -> Either a b -> b #
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
Since: base-4.10.0.0
maybeToLeft :: r -> Maybe l -> Either l r Source #
maybeToRight :: l -> Maybe r -> Either l r Source #
leftToMaybe :: Either l r -> Maybe l Source #
rightToMaybe :: Either l r -> Maybe r Source #
whenLeft :: Applicative f => a -> Either l r -> (l -> f a) -> f a Source #
whenLeft_ :: Applicative f => Either l r -> (l -> f ()) -> f () Source #
Monadic combinators
whenLeftM :: Monad m => a -> m (Either l r) -> (l -> m a) -> m a Source #
Monadic version of whenLeft
.
>>>
whenLeftM "bar" (pure $ Left 42) (\a -> "success!" <$ print a)
42 "success!"
>>>
whenLeftM "bar" (pure $ Right 42) (\a -> "success!" <$ print a)
"bar"
whenLeftM_ :: Monad m => m (Either l r) -> (l -> m ()) -> m () Source #
Monadic version of whenLeft_
.
>>>
whenLeftM_ (pure $ Right 42) putTextLn
>>>
whenLeftM_ (pure $ Left "foo") putTextLn
foo
whenRight :: Applicative f => a -> Either l r -> (r -> f a) -> f a Source #
whenRight_ :: Applicative f => Either l r -> (r -> f ()) -> f () Source #
whenRightM :: Monad m => a -> m (Either l r) -> (r -> m a) -> m a Source #
Monadic version of whenRight
.
>>>
whenRightM "bar" (pure $ Left "foo") (\a -> "success!" <$ print a)
"bar"
>>>
whenRightM "bar" (pure $ Right 42) (\a -> "success!" <$ print a)
42 "success!"
whenRightM_ :: Monad m => m (Either l r) -> (r -> m ()) -> m () Source #
Monadic version of whenRight_
.
>>>
whenRightM_ (pure $ Left "foo") print
>>>
whenRightM_ (pure $ Right 42) print
42