{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE DeriveGeneric #-}
module Data.Strict.Either (
Either(..)
, either
, isLeft, isRight
, fromLeft, fromRight
, lefts, rights
, partitionEithers
) where
import Prelude ( Functor (..), Eq (..), Ord (..), Show (..), Read (..), Bool (..), (.), ($)
, error, Ordering (..), showParen, showString, lex, return, readParen)
import Control.Applicative (pure, (<$>))
import Data.Semigroup (Semigroup (..))
import Data.Foldable (Foldable (..))
import Data.Traversable (Traversable (..))
import qualified Prelude as L
import Control.DeepSeq (NFData (..), NFData1 (..), NFData2 (..))
import Data.Bifoldable (Bifoldable (..))
import Data.Bifunctor (Bifunctor (..))
import Data.Bifunctor.Assoc (Assoc (..))
import Data.Bifunctor.Swap (Swap (..))
import Data.Binary (Binary (..))
import Data.Bitraversable (Bitraversable (..))
import Data.Data (Data (..), Typeable)
import Data.Hashable (Hashable(..))
import Data.Hashable.Lifted (Hashable1 (..), Hashable2 (..))
import GHC.Generics (Generic, Generic1)
import Data.Functor.Classes
(Eq1 (..), Eq2 (..), Ord1 (..), Ord2 (..), Read1 (..), Read2 (..),
Show1 (..), Show2 (..))
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, Typeable, Typeable (Either a b)
Typeable (Either a b) =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Either a b -> c (Either a b))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Either a b))
-> (Either a b -> Constr)
-> (Either a b -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Either a b)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Either a b)))
-> ((forall b. Data b => b -> b) -> Either a b -> Either a b)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r)
-> (forall u. (forall d. Data d => d -> u) -> Either a b -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> Either a b -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b))
-> Data (Either a b)
Either a b -> Constr
Either a b -> DataType
(forall b. Data b => b -> b) -> Either a b -> Either a b
forall a.
Typeable a =>
(forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Either a b -> u
forall u. (forall d. Data d => d -> u) -> Either a b -> [u]
forall a b. (Data a, Data b) => Typeable (Either a b)
forall a b. (Data a, Data b) => Either a b -> Constr
forall a b. (Data a, Data b) => Either a b -> DataType
forall a b.
(Data a, Data b) =>
(forall b. Data b => b -> b) -> Either a b -> Either a b
forall a b u.
(Data a, Data b) =>
Int -> (forall d. Data d => d -> u) -> Either a b -> u
forall a b u.
(Data a, Data b) =>
(forall d. Data d => d -> u) -> Either a b -> [u]
forall a b r r'.
(Data a, Data b) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
forall a b r r'.
(Data a, Data b) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
forall a b (m :: * -> *).
(Data a, Data b, Monad m) =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
forall a b (m :: * -> *).
(Data a, Data b, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
forall a b (c :: * -> *).
(Data a, Data b) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Either a b)
forall a b (c :: * -> *).
(Data a, Data b) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Either a b -> c (Either a b)
forall a b (t :: * -> *) (c :: * -> *).
(Data a, Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Either a b))
forall a b (t :: * -> * -> *) (c :: * -> *).
(Data a, Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Either a b))
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Either a b)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Either a b -> c (Either a b)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Either a b))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Either a b))
$cgfoldl :: forall a b (c :: * -> *).
(Data a, Data b) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Either a b -> c (Either a b)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Either a b -> c (Either a b)
$cgunfold :: forall a b (c :: * -> *).
(Data a, Data b) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Either a b)
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Either a b)
$ctoConstr :: forall a b. (Data a, Data b) => Either a b -> Constr
toConstr :: Either a b -> Constr
$cdataTypeOf :: forall a b. (Data a, Data b) => Either a b -> DataType
dataTypeOf :: Either a b -> DataType
$cdataCast1 :: forall a b (t :: * -> *) (c :: * -> *).
(Data a, Data b, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Either a b))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Either a b))
$cdataCast2 :: forall a b (t :: * -> * -> *) (c :: * -> *).
(Data a, Data b, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Either a b))
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Either a b))
$cgmapT :: forall a b.
(Data a, Data b) =>
(forall b. Data b => b -> b) -> Either a b -> Either a b
gmapT :: (forall b. Data b => b -> b) -> Either a b -> Either a b
$cgmapQl :: forall a b r r'.
(Data a, Data b) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
$cgmapQr :: forall a b r r'.
(Data a, Data b) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Either a b -> r
$cgmapQ :: forall a b u.
(Data a, Data b) =>
(forall d. Data d => d -> u) -> Either a b -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> Either a b -> [u]
$cgmapQi :: forall a b u.
(Data a, Data b) =>
Int -> (forall d. Data d => d -> u) -> Either a b -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Either a b -> u
$cgmapM :: forall a b (m :: * -> *).
(Data a, Data b, Monad m) =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
$cgmapMp :: forall a b (m :: * -> *).
(Data a, Data b, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
$cgmapMo :: forall a b (m :: * -> *).
(Data a, Data b, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Either a b -> m (Either a b)
Data, (forall x. Either a b -> Rep (Either a b) x)
-> (forall x. Rep (Either a b) x -> Either a b)
-> Generic (Either a b)
forall x. Rep (Either a b) x -> Either a b
forall x. Either a b -> Rep (Either a b) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a b x. Rep (Either a b) x -> Either a b
forall a b x. Either a b -> Rep (Either a b) x
$cfrom :: forall a b x. Either a b -> Rep (Either a b) x
from :: forall x. Either a b -> Rep (Either a b) x
$cto :: forall a b x. Rep (Either a b) x -> Either a b
to :: forall x. Rep (Either a b) x -> Either a b
Generic, (forall a. Either a a -> Rep1 (Either a) a)
-> (forall a. Rep1 (Either a) a -> Either a a)
-> Generic1 (Either a)
forall a. Rep1 (Either a) a -> Either a a
forall a. Either a a -> Rep1 (Either a) a
forall a a. Rep1 (Either a) a -> Either a a
forall a a. Either a a -> Rep1 (Either a) a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cfrom1 :: forall a a. Either a a -> Rep1 (Either a) a
from1 :: forall a. Either a a -> Rep1 (Either a) a
$cto1 :: forall a a. Rep1 (Either a) a -> Either a a
to1 :: forall a. Rep1 (Either a) a -> Either a a
Generic1)
toStrict :: L.Either a b -> Either a b
toStrict :: forall a b. Either a b -> Either a b
toStrict (L.Left a
x) = a -> Either a b
forall a b. a -> Either a b
Left a
x
toStrict (L.Right b
y) = b -> Either a b
forall a b. b -> Either a b
Right b
y
toLazy :: Either a b -> L.Either a b
toLazy :: forall a b. Either a b -> Either a b
toLazy (Left a
x) = a -> Either a b
forall a b. a -> Either a b
L.Left a
x
toLazy (Right b
y) = b -> Either a b
forall a b. b -> Either a b
L.Right b
y
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
isLeft :: Either a b -> Bool
isLeft :: forall a b. Either a b -> Bool
isLeft (Left a
_) = Bool
True
isLeft Either a b
_ = Bool
False
isRight :: Either a b -> Bool
isRight :: forall a b. Either a b -> Bool
isRight (Right b
_) = Bool
True
isRight Either a b
_ = Bool
False
fromLeft :: Either a b -> a
fromLeft :: forall a b. Either a b -> a
fromLeft (Left a
x) = a
x
fromLeft Either a b
_ = String -> a
forall a. HasCallStack => String -> a
error String
"Data.Strict.Either.fromLeft: Right"
fromRight :: Either a b -> b
fromRight :: forall a b. Either a b -> b
fromRight (Right b
x) = b
x
fromRight Either a b
_ = String -> b
forall a. HasCallStack => String -> a
error String
"Data.Strict.Either.fromRight: Left"
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]
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]
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
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
L.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)
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 Foldable (Either e) where
foldr :: forall a b. (a -> b -> b) -> b -> Either e a -> b
foldr a -> b -> b
_ b
y (Left e
_) = b
y
foldr a -> b -> b
f b
y (Right a
x) = a -> b -> b
f a
x b
y
foldl :: forall b a. (b -> a -> b) -> b -> Either e a -> b
foldl b -> a -> b
_ b
y (Left e
_) = b
y
foldl b -> a -> b
f b
y (Right a
x) = b -> a -> b
f b
y a
x
instance Traversable (Either e) where
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Either e a -> f (Either e b)
traverse a -> f b
_ (Left e
x) = Either e b -> f (Either e b)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (e -> Either e b
forall a b. a -> Either a b
Left e
x)
traverse a -> f b
f (Right a
x) = b -> Either e b
forall a b. b -> Either a b
Right (b -> Either e b) -> f b -> f (Either e b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f b
f a
x
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
instance (NFData a, NFData b) => NFData (Either a b) where
rnf :: Either a b -> ()
rnf = Either a b -> ()
forall a. NFData a => a -> ()
rnf (Either a b -> ())
-> (Either a b -> Either a b) -> Either a b -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a b -> Either a b
forall a b. Either a b -> Either a b
toLazy
instance (NFData a) => NFData1 (Either a) where
liftRnf :: forall a. (a -> ()) -> Either a a -> ()
liftRnf a -> ()
rnfA = (a -> ()) -> Either a a -> ()
forall a. (a -> ()) -> Either a a -> ()
forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf a -> ()
rnfA (Either a a -> ())
-> (Either a a -> Either a a) -> Either a a -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a a -> Either a a
forall a b. Either a b -> Either a b
toLazy
instance NFData2 Either where
liftRnf2 :: forall a b. (a -> ()) -> (b -> ()) -> Either a b -> ()
liftRnf2 a -> ()
rnfA b -> ()
rnfB = (a -> ()) -> (b -> ()) -> Either a b -> ()
forall a b. (a -> ()) -> (b -> ()) -> Either a b -> ()
forall (p :: * -> * -> *) a b.
NFData2 p =>
(a -> ()) -> (b -> ()) -> p a b -> ()
liftRnf2 a -> ()
rnfA b -> ()
rnfB (Either a b -> ())
-> (Either a b -> Either a b) -> Either a b -> ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a b -> Either a b
forall a b. Either a b -> Either a b
toLazy
instance (Binary a, Binary b) => Binary (Either a b) where
put :: Either a b -> Put
put = Either a b -> Put
forall t. Binary t => t -> Put
put (Either a b -> Put)
-> (Either a b -> Either a b) -> Either a b -> Put
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a b -> Either a b
forall a b. Either a b -> Either a b
toLazy
get :: Get (Either a b)
get = Either a b -> Either a b
forall a b. Either a b -> Either a b
toStrict (Either a b -> Either a b) -> Get (Either a b) -> Get (Either a b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get (Either a b)
forall t. Binary t => Get t
get
instance Bifunctor Either where
bimap :: forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
bimap a -> b
f c -> d
_ (Left a
a) = b -> Either b d
forall a b. a -> Either a b
Left (a -> b
f a
a)
bimap a -> b
_ c -> d
g (Right c
a) = d -> Either b d
forall a b. b -> Either a b
Right (c -> d
g c
a)
first :: forall a b c. (a -> b) -> Either a c -> Either b c
first a -> b
f = (a -> Either b c) -> (c -> Either b c) -> Either a c -> Either b c
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (b -> Either b c
forall a b. a -> Either a b
Left (b -> Either b c) -> (a -> b) -> a -> Either b c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f) c -> Either b c
forall a b. b -> Either a b
Right
second :: forall b c a. (b -> c) -> Either a b -> Either a c
second b -> c
g = (a -> Either a c) -> (b -> Either a c) -> Either a b -> Either a c
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either a -> Either a c
forall a b. a -> Either a b
Left (c -> Either a c
forall a b. b -> Either a b
Right (c -> Either a c) -> (b -> c) -> b -> Either a c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. b -> c
g)
instance Bifoldable Either where
bifold :: forall m. Monoid m => Either m m -> m
bifold (Left m
a) = m
a
bifold (Right m
b) = m
b
bifoldMap :: forall m a b. Monoid m => (a -> m) -> (b -> m) -> Either a b -> m
bifoldMap = (a -> m) -> (b -> m) -> Either a b -> m
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either
bifoldr :: forall a c b.
(a -> c -> c) -> (b -> c -> c) -> c -> Either a b -> c
bifoldr a -> c -> c
f b -> c -> c
_ c
c (Left a
a) = a -> c -> c
f a
a c
c
bifoldr a -> c -> c
_ b -> c -> c
g c
c (Right b
b) = b -> c -> c
g b
b c
c
bifoldl :: forall c a b.
(c -> a -> c) -> (c -> b -> c) -> c -> Either a b -> c
bifoldl c -> a -> c
f c -> b -> c
_ c
c (Left a
a) = c -> a -> c
f c
c a
a
bifoldl c -> a -> c
_ c -> b -> c
g c
c (Right b
b) = c -> b -> c
g c
c b
b
instance Bitraversable Either where
bitraverse :: forall (f :: * -> *) a c b d.
Applicative f =>
(a -> f c) -> (b -> f d) -> Either a b -> f (Either c d)
bitraverse a -> f c
f b -> f d
_ (Left a
a) = (c -> Either c d) -> f c -> f (Either c d)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap c -> Either c d
forall a b. a -> Either a b
Left (a -> f c
f a
a)
bitraverse a -> f c
_ b -> f d
g (Right b
b) = (d -> Either c d) -> f d -> f (Either c d)
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap d -> Either c d
forall a b. b -> Either a b
Right (b -> f d
g b
b)
instance (Hashable a, Hashable b) => Hashable (Either a b) where
hashWithSalt :: Int -> Either a b -> Int
hashWithSalt Int
salt = Int -> Either a b -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
salt (Either a b -> Int)
-> (Either a b -> Either a b) -> Either a b -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a b -> Either a b
forall a b. Either a b -> Either a b
toLazy
instance (Hashable a) => Hashable1 (Either a) where
liftHashWithSalt :: forall a. (Int -> a -> Int) -> Int -> Either a a -> Int
liftHashWithSalt Int -> a -> Int
hashA Int
salt = (Int -> a -> Int) -> Int -> Either a a -> Int
forall a. (Int -> a -> Int) -> Int -> Either a a -> Int
forall (t :: * -> *) a.
Hashable1 t =>
(Int -> a -> Int) -> Int -> t a -> Int
liftHashWithSalt Int -> a -> Int
hashA Int
salt (Either a a -> Int)
-> (Either a a -> Either a a) -> Either a a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a a -> Either a a
forall a b. Either a b -> Either a b
toLazy
instance Hashable2 Either where
liftHashWithSalt2 :: forall a b.
(Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int
liftHashWithSalt2 Int -> a -> Int
hashA Int -> b -> Int
hashB Int
salt = (Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int
forall a b.
(Int -> a -> Int) -> (Int -> b -> Int) -> Int -> Either a b -> Int
forall (t :: * -> * -> *) a b.
Hashable2 t =>
(Int -> a -> Int) -> (Int -> b -> Int) -> Int -> t a b -> Int
liftHashWithSalt2 Int -> a -> Int
hashA Int -> b -> Int
hashB Int
salt (Either a b -> Int)
-> (Either a b -> Either a b) -> Either a b -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either a b -> Either a b
forall a b. Either a b -> Either a b
toLazy
instance Assoc Either where
assoc :: forall a b c. Either (Either a b) c -> Either a (Either b c)
assoc (Left (Left a
a)) = a -> Either a (Either b c)
forall a b. a -> Either a b
Left a
a
assoc (Left (Right b
b)) = Either b c -> Either a (Either b c)
forall a b. b -> Either a b
Right (b -> Either b c
forall a b. a -> Either a b
Left b
b)
assoc (Right c
c) = Either b c -> Either a (Either b c)
forall a b. b -> Either a b
Right (c -> Either b c
forall a b. b -> Either a b
Right c
c)
unassoc :: forall a b c. Either a (Either b c) -> Either (Either a b) c
unassoc (Left a
a) = Either a b -> Either (Either a b) c
forall a b. a -> Either a b
Left (a -> Either a b
forall a b. a -> Either a b
Left a
a)
unassoc (Right (Left b
b)) = Either a b -> Either (Either a b) c
forall a b. a -> Either a b
Left (b -> Either a b
forall a b. b -> Either a b
Right b
b)
unassoc (Right (Right c
c)) = c -> Either (Either a b) c
forall a b. b -> Either a b
Right c
c
instance Swap Either where
swap :: forall a b. Either a b -> Either b a
swap (Left a
x) = a -> Either b a
forall a b. b -> Either a b
Right a
x
swap (Right b
x) = b -> Either b a
forall a b. a -> Either a b
Left b
x
instance Eq2 Either where
liftEq2 :: forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Either a c -> Either b d -> Bool
liftEq2 a -> b -> Bool
f c -> d -> Bool
_ (Left a
a) (Left b
a') = a -> b -> Bool
f a
a b
a'
liftEq2 a -> b -> Bool
_ c -> d -> Bool
g (Right c
b) (Right d
b') = c -> d -> Bool
g c
b d
b'
liftEq2 a -> b -> Bool
_ c -> d -> Bool
_ Either a c
_ Either b d
_ = Bool
False
instance Eq a => Eq1 (Either a) where
liftEq :: forall a b. (a -> b -> Bool) -> Either a a -> Either a b -> Bool
liftEq = (a -> a -> Bool)
-> (a -> b -> Bool) -> Either a a -> Either a b -> Bool
forall a b c d.
(a -> b -> Bool)
-> (c -> d -> Bool) -> Either a c -> Either b d -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
liftEq2 a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
instance Ord2 Either where
liftCompare2 :: forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering
liftCompare2 a -> b -> Ordering
f c -> d -> Ordering
_ (Left a
a) (Left b
a') = a -> b -> Ordering
f a
a b
a'
liftCompare2 a -> b -> Ordering
_ c -> d -> Ordering
_ (Left a
_) Either b d
_ = Ordering
LT
liftCompare2 a -> b -> Ordering
_ c -> d -> Ordering
_ Either a c
_ (Left b
_) = Ordering
GT
liftCompare2 a -> b -> Ordering
_ c -> d -> Ordering
g (Right c
b) (Right d
b') = c -> d -> Ordering
g c
b d
b'
instance Ord a => Ord1 (Either a) where
liftCompare :: forall a b.
(a -> b -> Ordering) -> Either a a -> Either a b -> Ordering
liftCompare = (a -> a -> Ordering)
-> (a -> b -> Ordering) -> Either a a -> Either a b -> Ordering
forall a b c d.
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> Either a c -> Either b d -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
liftCompare2 a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare
instance Show a => Show1 (Either a) where
liftShowsPrec :: forall a.
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Either a a -> ShowS
liftShowsPrec = (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> Either a a
-> ShowS
forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Either a b
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
forall a. Show a => Int -> a -> ShowS
showsPrec [a] -> ShowS
forall a. Show a => [a] -> ShowS
showList
instance Show2 Either where
liftShowsPrec2 :: forall a b.
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Either a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
sa [a] -> ShowS
_ Int -> b -> ShowS
_sb [b] -> ShowS
_ Int
d (Left a
a) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)
(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"Left "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> ShowS
sa Int
11 a
a
liftShowsPrec2 Int -> a -> ShowS
_sa [a] -> ShowS
_ Int -> b -> ShowS
sb [b] -> ShowS
_ Int
d (Right b
b) = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10)
(ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$ String -> ShowS
showString String
"Right "
ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> b -> ShowS
sb Int
11 b
b
instance Read2 Either where
liftReadsPrec2 :: forall a b.
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (Either a b)
liftReadsPrec2 Int -> ReadS a
ra ReadS [a]
_ Int -> ReadS b
rb ReadS [b]
_ Int
d = Bool -> ReadS (Either a b) -> ReadS (Either a b)
forall a. Bool -> ReadS a -> ReadS a
readParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ReadS (Either a b) -> ReadS (Either a b))
-> ReadS (Either a b) -> ReadS (Either a b)
forall a b. (a -> b) -> a -> b
$ \String
s -> ReadS (Either a b)
cons String
s
where
cons :: ReadS (Either a b)
cons String
s0 = do
(String
ident, String
s1) <- ReadS String
lex String
s0
case String
ident of
String
"Left" -> do
(a
a, String
s2) <- Int -> ReadS a
ra Int
11 String
s1
(Either a b, String) -> [(Either a b, String)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (a -> Either a b
forall a b. a -> Either a b
Left a
a, String
s2)
String
"Right" -> do
(b
b, String
s2) <- Int -> ReadS b
rb Int
11 String
s1
(Either a b, String) -> [(Either a b, String)]
forall a. a -> [a]
forall (m :: * -> *) a. Monad m => a -> m a
return (b -> Either a b
forall a b. b -> Either a b
Right b
b, String
s2)
String
_ -> []
instance Read a => Read1 (Either a) where
liftReadsPrec :: forall a.
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Either a a)
liftReadsPrec = (Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS a)
-> ReadS [a]
-> Int
-> ReadS (Either a a)
forall a b.
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (Either a b)
forall (f :: * -> * -> *) a b.
Read2 f =>
(Int -> ReadS a)
-> ReadS [a]
-> (Int -> ReadS b)
-> ReadS [b]
-> Int
-> ReadS (f a b)
liftReadsPrec2 Int -> ReadS a
forall a. Read a => Int -> ReadS a
readsPrec ReadS [a]
forall a. Read a => ReadS [a]
readList