module Algebra.Graph.Relation.Reflexive (
ReflexiveRelation, fromRelation, toRelation
) where
import Algebra.Graph.Relation
import Control.DeepSeq
import Data.String
import qualified Algebra.Graph.Class as C
newtype ReflexiveRelation a = ReflexiveRelation { ReflexiveRelation a -> Relation a
fromReflexive :: Relation a }
deriving (String -> ReflexiveRelation a
(String -> ReflexiveRelation a) -> IsString (ReflexiveRelation a)
forall a. IsString a => String -> ReflexiveRelation a
forall a. (String -> a) -> IsString a
fromString :: String -> ReflexiveRelation a
$cfromString :: forall a. IsString a => String -> ReflexiveRelation a
IsString, ReflexiveRelation a -> ()
(ReflexiveRelation a -> ()) -> NFData (ReflexiveRelation a)
forall a. NFData a => ReflexiveRelation a -> ()
forall a. (a -> ()) -> NFData a
rnf :: ReflexiveRelation a -> ()
$crnf :: forall a. NFData a => ReflexiveRelation a -> ()
NFData, Integer -> ReflexiveRelation a
ReflexiveRelation a -> ReflexiveRelation a
ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
(ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a)
-> (ReflexiveRelation a
-> ReflexiveRelation a -> ReflexiveRelation a)
-> (ReflexiveRelation a
-> ReflexiveRelation a -> ReflexiveRelation a)
-> (ReflexiveRelation a -> ReflexiveRelation a)
-> (ReflexiveRelation a -> ReflexiveRelation a)
-> (ReflexiveRelation a -> ReflexiveRelation a)
-> (Integer -> ReflexiveRelation a)
-> Num (ReflexiveRelation a)
forall a. (Ord a, Num a) => Integer -> ReflexiveRelation a
forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a
forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> ReflexiveRelation a
$cfromInteger :: forall a. (Ord a, Num a) => Integer -> ReflexiveRelation a
signum :: ReflexiveRelation a -> ReflexiveRelation a
$csignum :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a
abs :: ReflexiveRelation a -> ReflexiveRelation a
$cabs :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a
negate :: ReflexiveRelation a -> ReflexiveRelation a
$cnegate :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a
* :: ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
$c* :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
- :: ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
$c- :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
+ :: ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
$c+ :: forall a.
(Ord a, Num a) =>
ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
Num)
instance Ord a => Eq (ReflexiveRelation a) where
ReflexiveRelation a
x == :: ReflexiveRelation a -> ReflexiveRelation a -> Bool
== ReflexiveRelation a
y = ReflexiveRelation a -> Relation a
forall a. Ord a => ReflexiveRelation a -> Relation a
toRelation ReflexiveRelation a
x Relation a -> Relation a -> Bool
forall a. Eq a => a -> a -> Bool
== ReflexiveRelation a -> Relation a
forall a. Ord a => ReflexiveRelation a -> Relation a
toRelation ReflexiveRelation a
y
instance Ord a => Ord (ReflexiveRelation a) where
compare :: ReflexiveRelation a -> ReflexiveRelation a -> Ordering
compare ReflexiveRelation a
x ReflexiveRelation a
y = Relation a -> Relation a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (ReflexiveRelation a -> Relation a
forall a. Ord a => ReflexiveRelation a -> Relation a
toRelation ReflexiveRelation a
x) (ReflexiveRelation a -> Relation a
forall a. Ord a => ReflexiveRelation a -> Relation a
toRelation ReflexiveRelation a
y)
instance (Ord a, Show a) => Show (ReflexiveRelation a) where
show :: ReflexiveRelation a -> String
show = Relation a -> String
forall a. Show a => a -> String
show (Relation a -> String)
-> (ReflexiveRelation a -> Relation a)
-> ReflexiveRelation a
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReflexiveRelation a -> Relation a
forall a. Ord a => ReflexiveRelation a -> Relation a
toRelation
instance Ord a => C.Graph (ReflexiveRelation a) where
type Vertex (ReflexiveRelation a) = a
empty :: ReflexiveRelation a
empty = Relation a -> ReflexiveRelation a
forall a. Relation a -> ReflexiveRelation a
ReflexiveRelation Relation a
forall a. Relation a
empty
vertex :: Vertex (ReflexiveRelation a) -> ReflexiveRelation a
vertex = Relation a -> ReflexiveRelation a
forall a. Relation a -> ReflexiveRelation a
ReflexiveRelation (Relation a -> ReflexiveRelation a)
-> (a -> Relation a) -> a -> ReflexiveRelation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Relation a
forall a. a -> Relation a
vertex
overlay :: ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
overlay ReflexiveRelation a
x ReflexiveRelation a
y = Relation a -> ReflexiveRelation a
forall a. Relation a -> ReflexiveRelation a
ReflexiveRelation (Relation a -> ReflexiveRelation a)
-> Relation a -> ReflexiveRelation a
forall a b. (a -> b) -> a -> b
$ ReflexiveRelation a -> Relation a
forall a. ReflexiveRelation a -> Relation a
fromReflexive ReflexiveRelation a
x Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
`overlay` ReflexiveRelation a -> Relation a
forall a. ReflexiveRelation a -> Relation a
fromReflexive ReflexiveRelation a
y
connect :: ReflexiveRelation a -> ReflexiveRelation a -> ReflexiveRelation a
connect ReflexiveRelation a
x ReflexiveRelation a
y = Relation a -> ReflexiveRelation a
forall a. Relation a -> ReflexiveRelation a
ReflexiveRelation (Relation a -> ReflexiveRelation a)
-> Relation a -> ReflexiveRelation a
forall a b. (a -> b) -> a -> b
$ ReflexiveRelation a -> Relation a
forall a. ReflexiveRelation a -> Relation a
fromReflexive ReflexiveRelation a
x Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
`connect` ReflexiveRelation a -> Relation a
forall a. ReflexiveRelation a -> Relation a
fromReflexive ReflexiveRelation a
y
instance Ord a => C.Reflexive (ReflexiveRelation a)
fromRelation :: Relation a -> ReflexiveRelation a
fromRelation :: Relation a -> ReflexiveRelation a
fromRelation = Relation a -> ReflexiveRelation a
forall a. Relation a -> ReflexiveRelation a
ReflexiveRelation
toRelation :: Ord a => ReflexiveRelation a -> Relation a
toRelation :: ReflexiveRelation a -> Relation a
toRelation = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
reflexiveClosure (Relation a -> Relation a)
-> (ReflexiveRelation a -> Relation a)
-> ReflexiveRelation a
-> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ReflexiveRelation a -> Relation a
forall a. ReflexiveRelation a -> Relation a
fromReflexive