monoids-in-the-category-of-.../src/Relation/Opposite.hs

24 lines
616 B
Haskell

module Relation.Opposite where
import Relation.Base
import Relation.Reflexive
import Relation.Transitive
type Opposite :: Relation k -> Relation k
newtype Opposite r x y = Opposite { getOpposite :: r y x }
instance Reflexive r => Reflexive (Opposite r) where
idL (Opposite f) = Opposite (idR f)
idR (Opposite f) = Opposite (idL f)
instance Wide r => Wide (Opposite r) where
id = Opposite id
instance Transitive r => Transitive (Opposite r) where
Opposite f . Opposite g = Opposite (g . f)
type Op :: Relation k -> Relation k
type family Op r where
Op (Opposite r) = r
Op r = Opposite r