module OAlg.Data.Opposite
(
Op(..), fromOp, fromOpOp
, Op2(..)
) where
import OAlg.Data.Show
import OAlg.Data.Equal
newtype Op x = Op x deriving (Int -> Op x -> ShowS
forall x. Show x => Int -> Op x -> ShowS
forall x. Show x => [Op x] -> ShowS
forall x. Show x => Op x -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Op x] -> ShowS
$cshowList :: forall x. Show x => [Op x] -> ShowS
show :: Op x -> String
$cshow :: forall x. Show x => Op x -> String
showsPrec :: Int -> Op x -> ShowS
$cshowsPrec :: forall x. Show x => Int -> Op x -> ShowS
Show,ReadPrec [Op x]
ReadPrec (Op x)
ReadS [Op x]
forall x. Read x => ReadPrec [Op x]
forall x. Read x => ReadPrec (Op x)
forall x. Read x => Int -> ReadS (Op x)
forall x. Read x => ReadS [Op x]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Op x]
$creadListPrec :: forall x. Read x => ReadPrec [Op x]
readPrec :: ReadPrec (Op x)
$creadPrec :: forall x. Read x => ReadPrec (Op x)
readList :: ReadS [Op x]
$creadList :: forall x. Read x => ReadS [Op x]
readsPrec :: Int -> ReadS (Op x)
$creadsPrec :: forall x. Read x => Int -> ReadS (Op x)
Read,Op x -> Op x -> Bool
forall x. Eq x => Op x -> Op x -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Op x -> Op x -> Bool
$c/= :: forall x. Eq x => Op x -> Op x -> Bool
== :: Op x -> Op x -> Bool
$c== :: forall x. Eq x => Op x -> Op x -> Bool
Eq)
fromOp :: Op x -> x
fromOp :: forall x. Op x -> x
fromOp (Op x
x) = x
x
fromOpOp :: Op (Op x) -> x
fromOpOp :: forall x. Op (Op x) -> x
fromOpOp (Op (Op x
x)) = x
x
newtype Op2 h x y = Op2 (h y x)
instance Show2 h => Show2 (Op2 h) where
show2 :: forall a b. Op2 h a b -> String
show2 (Op2 h b a
h) = String
"Op2[" forall a. [a] -> [a] -> [a]
++ forall (h :: * -> * -> *) a b. Show2 h => h a b -> String
show2 h b a
h forall a. [a] -> [a] -> [a]
++ String
"]"
instance Eq2 h => Eq2 (Op2 h) where
eq2 :: forall x y. Op2 h x y -> Op2 h x y -> Bool
eq2 (Op2 h y x
f) (Op2 h y x
g) = forall (h :: * -> * -> *) x y. Eq2 h => h x y -> h x y -> Bool
eq2 h y x
f h y x
g