{-# LANGUAGE GADTs #-}
module OAlg.Data.Either
(
Either(..)
, Either2(..)
)
where
import OAlg.Data.Show
import OAlg.Data.Equal
data Either2 f g a b where
Left2 :: f a b -> Either2 f g a b
Right2 :: g a b -> Either2 f g a b
instance (Show2 f, Show2 g) => Show2 (Either2 f g) where
show2 :: forall a b. Either2 f g a b -> String
show2 (Left2 f a b
f) = String
"Left2 (" forall a. [a] -> [a] -> [a]
++ forall (h :: * -> * -> *) a b. Show2 h => h a b -> String
show2 f a b
f forall a. [a] -> [a] -> [a]
++ String
")"
show2 (Right2 g a b
g) = String
"Right2 (" forall a. [a] -> [a] -> [a]
++ forall (h :: * -> * -> *) a b. Show2 h => h a b -> String
show2 g a b
g forall a. [a] -> [a] -> [a]
++ String
")"
instance (Show2 f, Show2 g) => Show (Either2 f g x y) where
show :: Either2 f g x y -> String
show = forall (h :: * -> * -> *) a b. Show2 h => h a b -> String
show2
instance (Eq2 f, Eq2 g) => Eq2 (Either2 f g) where
eq2 :: forall x y. Either2 f g x y -> Either2 f g x y -> Bool
eq2 (Left2 f x y
f) (Left2 f x y
g) = forall (h :: * -> * -> *) x y. Eq2 h => h x y -> h x y -> Bool
eq2 f x y
f f x y
g
eq2 (Right2 g x y
f) (Right2 g x y
g) = forall (h :: * -> * -> *) x y. Eq2 h => h x y -> h x y -> Bool
eq2 g x y
f g x y
g
eq2 Either2 f g x y
_ Either2 f g x y
_ = Bool
False