{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.Either (
Either(..),
either,
lefts,
rights,
isLeft,
isRight,
fromLeft,
fromRight,
partitionEithers,
) where
import GHC.Base
import GHC.Show
import GHC.Read
data Either a b = Left a | Right b
deriving ( Either a b -> Either a b -> Bool
(Either a b -> Either a b -> Bool)
-> (Either a b -> Either a b -> Bool) -> Eq (Either a b)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall a b. (Eq a, Eq b) => Either a b -> Either a b -> Bool
$c== :: forall a b. (Eq a, Eq b) => Either a b -> Either a b -> Bool
== :: Either a b -> Either a b -> Bool
$c/= :: forall a b. (Eq a, Eq b) => Either a b -> Either a b -> Bool
/= :: Either a b -> Either a b -> Bool
Eq
, Eq (Either a b)
Eq (Either a b)
-> (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)
-> (Either a b -> Either a b -> Either a b)
-> (Either a b -> Either a b -> Either a b)
-> Ord (Either a b)
Either a b -> Either a b -> Bool
Either a b -> Either a b -> Ordering
Either a b -> Either a b -> Either a b
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall {a} {b}. (Ord a, Ord b) => Eq (Either a b)
forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Bool
forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Ordering
forall a b.
(Ord a, Ord b) =>
Either a b -> Either a b -> Either a b
$ccompare :: forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Ordering
compare :: Either a b -> Either a b -> Ordering
$c< :: forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Bool
< :: Either a b -> Either a b -> Bool
$c<= :: forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Bool
<= :: Either a b -> Either a b -> Bool
$c> :: forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Bool
> :: Either a b -> Either a b -> Bool
$c>= :: forall a b. (Ord a, Ord b) => Either a b -> Either a b -> Bool
>= :: Either a b -> Either a b -> Bool
$cmax :: forall a b.
(Ord a, Ord b) =>
Either a b -> Either a b -> Either a b
max :: Either a b -> Either a b -> Either a b
$cmin :: forall a b.
(Ord a, Ord b) =>
Either a b -> Either a b -> Either a b
min :: Either a b -> Either a b -> Either a b
Ord
, ReadPrec [Either a b]
ReadPrec (Either a b)
Int -> ReadS (Either a b)
ReadS [Either a b]
(Int -> ReadS (Either a b))
-> ReadS [Either a b]
-> ReadPrec (Either a b)
-> ReadPrec [Either a b]
-> Read (Either a b)
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
forall a b. (Read a, Read b) => ReadPrec [Either a b]
forall a b. (Read a, Read b) => ReadPrec (Either a b)
forall a b. (Read a, Read b) => Int -> ReadS (Either a b)
forall a b. (Read a, Read b) => ReadS [Either a b]
$creadsPrec :: forall a b. (Read a, Read b) => Int -> ReadS (Either a b)
readsPrec :: Int -> ReadS (Either a b)
$creadList :: forall a b. (Read a, Read b) => ReadS [Either a b]
readList :: ReadS [Either a b]
$creadPrec :: forall a b. (Read a, Read b) => ReadPrec (Either a b)
readPrec :: ReadPrec (Either a b)
$creadListPrec :: forall a b. (Read a, Read b) => ReadPrec [Either a b]
readListPrec :: ReadPrec [Either a b]
Read
, Int -> Either a b -> ShowS
[Either a b] -> ShowS
Either a b -> String
(Int -> Either a b -> ShowS)
-> (Either a b -> String)
-> ([Either a b] -> ShowS)
-> Show (Either a b)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall a b. (Show a, Show b) => Int -> Either a b -> ShowS
forall a b. (Show a, Show b) => [Either a b] -> ShowS
forall a b. (Show a, Show b) => Either a b -> String
$cshowsPrec :: forall a b. (Show a, Show b) => Int -> Either a b -> ShowS
showsPrec :: Int -> Either a b -> ShowS
$cshow :: forall a b. (Show a, Show b) => Either a b -> String
show :: Either a b -> String
$cshowList :: forall a b. (Show a, Show b) => [Either a b] -> ShowS
showList :: [Either a b] -> ShowS
Show
)
instance Functor (Either a) where
fmap :: forall a b. (a -> b) -> Either a a -> Either a b
fmap a -> b
_ (Left a
x) = a -> Either a b
forall a b. a -> Either a b
Left a
x
fmap a -> b
f (Right a
y) = b -> Either a b
forall a b. b -> Either a b
Right (a -> b
f a
y)
instance Semigroup (Either a b) where
Left a
_ <> :: Either a b -> Either a b -> Either a b
<> Either a b
b = Either a b
b
Either a b
a <> Either a b
_ = Either a b
a
#if !defined(__HADDOCK_VERSION__)
stimes n x
| n <= 0 = errorWithoutStackTrace "stimes: positive multiplier expected"
| otherwise = x
#endif
instance Applicative (Either e) where
pure :: forall a. a -> Either e a
pure = a -> Either e a
forall a b. b -> Either a b
Right
Left e
e <*> :: forall a b. Either e (a -> b) -> Either e a -> Either e b
<*> Either e a
_ = e -> Either e b
forall a b. a -> Either a b
Left e
e
Right a -> b
f <*> Either e a
r = (a -> b) -> Either e a -> Either e b
forall a b. (a -> b) -> Either e a -> Either e b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Either e a
r
instance Monad (Either e) where
Left e
l >>= :: forall a b. Either e a -> (a -> Either e b) -> Either e b
>>= a -> Either e b
_ = e -> Either e b
forall a b. a -> Either a b
Left e
l
Right a
r >>= a -> Either e b
k = a -> Either e b
k a
r
either :: (a -> c) -> (b -> c) -> Either a b -> c
either :: forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> c
f b -> c
_ (Left a
x) = a -> c
f a
x
either a -> c
_ b -> c
g (Right b
y) = b -> c
g b
y
lefts :: [Either a b] -> [a]
lefts :: forall a b. [Either a b] -> [a]
lefts [Either a b]
x = [a
a | Left a
a <- [Either a b]
x]
{-# INLINEABLE lefts #-}
rights :: [Either a b] -> [b]
rights :: forall a b. [Either a b] -> [b]
rights [Either a b]
x = [b
a | Right b
a <- [Either a b]
x]
{-# INLINEABLE rights #-}
partitionEithers :: [Either a b] -> ([a],[b])
partitionEithers :: forall a b. [Either a b] -> ([a], [b])
partitionEithers = (Either a b -> ([a], [b]) -> ([a], [b]))
-> ([a], [b]) -> [Either a b] -> ([a], [b])
forall a b. (a -> b -> b) -> b -> [a] -> b
foldr ((a -> ([a], [b]) -> ([a], [b]))
-> (b -> ([a], [b]) -> ([a], [b]))
-> Either a b
-> ([a], [b])
-> ([a], [b])
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> ([a], [b]) -> ([a], [b])
forall {a} {b}. a -> ([a], b) -> ([a], b)
left b -> ([a], [b]) -> ([a], [b])
forall {a} {a}. a -> (a, [a]) -> (a, [a])
right) ([],[])
where
left :: a -> ([a], b) -> ([a], b)
left a
a ~([a]
l, b
r) = (a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
l, b
r)
right :: a -> (a, [a]) -> (a, [a])
right a
a ~(a
l, [a]
r) = (a
l, a
aa -> [a] -> [a]
forall a. a -> [a] -> [a]
:[a]
r)
isLeft :: Either a b -> Bool
isLeft :: forall a b. Either a b -> Bool
isLeft (Left a
_) = Bool
True
isLeft (Right b
_) = Bool
False
isRight :: Either a b -> Bool
isRight :: forall a b. Either a b -> Bool
isRight (Left a
_) = Bool
False
isRight (Right b
_) = Bool
True
fromLeft :: a -> Either a b -> a
fromLeft :: forall a b. a -> Either a b -> a
fromLeft a
_ (Left a
a) = a
a
fromLeft a
a Either a b
_ = a
a
fromRight :: b -> Either a b -> b
fromRight :: forall b a. b -> Either a b -> b
fromRight b
_ (Right b
b) = b
b
fromRight b
b Either a b
_ = b
b