module Algebra.Graph.Relation.Symmetric (
    
    Relation, toSymmetric, fromSymmetric,
    
    empty, vertex, edge, overlay, connect, vertices, edges, overlays, connects,
    
    isSubgraphOf,
    
    isEmpty, hasVertex, hasEdge, vertexCount, edgeCount, vertexList, edgeList,
    adjacencyList, vertexSet, edgeSet, neighbours,
    
    path, circuit, clique, biclique, star, stars, tree, forest,
    
    removeVertex, removeEdge, replaceVertex, mergeVertices, gmap, induce, induceJust,
    
    consistent
    ) where
import Control.DeepSeq
import Data.Coerce
import Data.Set (Set)
import Data.String
import Data.Tree
import qualified Data.Set as Set
import qualified Algebra.Graph.Relation as R
newtype Relation a = SR {
    
    
    
    
    
    
    
    
    Relation a -> Relation a
fromSymmetric :: R.Relation a
    } deriving (Relation a -> Relation a -> Bool
(Relation a -> Relation a -> Bool)
-> (Relation a -> Relation a -> Bool) -> Eq (Relation a)
forall a. Eq a => Relation a -> Relation a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Relation a -> Relation a -> Bool
$c/= :: forall a. Eq a => Relation a -> Relation a -> Bool
== :: Relation a -> Relation a -> Bool
$c== :: forall a. Eq a => Relation a -> Relation a -> Bool
Eq, String -> Relation a
(String -> Relation a) -> IsString (Relation a)
forall a. IsString a => String -> Relation a
forall a. (String -> a) -> IsString a
fromString :: String -> Relation a
$cfromString :: forall a. IsString a => String -> Relation a
IsString, Relation a -> ()
(Relation a -> ()) -> NFData (Relation a)
forall a. NFData a => Relation a -> ()
forall a. (a -> ()) -> NFData a
rnf :: Relation a -> ()
$crnf :: forall a. NFData a => Relation a -> ()
NFData)
instance (Ord a, Show a) => Show (Relation a) where
    show :: Relation a -> String
show = Relation a -> String
forall a. Show a => a -> String
show (Relation a -> String)
-> (Relation a -> Relation a) -> Relation a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toRelation
      where
        toRelation :: Relation a -> Relation a
toRelation Relation a
r = [a] -> Relation a
forall a. Ord a => [a] -> Relation a
R.vertices (Relation a -> [a]
forall a. Relation a -> [a]
vertexList Relation a
r) Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
`R.overlay` [(a, a)] -> Relation a
forall a. Ord a => [(a, a)] -> Relation a
R.edges (Relation a -> [(a, a)]
forall a. Ord a => Relation a -> [(a, a)]
edgeList Relation a
r)
instance Ord a => Ord (Relation a) where
    compare :: Relation a -> Relation a -> Ordering
compare Relation a
x Relation a
y = [Ordering] -> Ordering
forall a. Monoid a => [a] -> a
mconcat
        [ Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Relation a -> Int
forall a. Relation a -> Int
vertexCount Relation a
x) (Relation a -> Int
forall a. Relation a -> Int
vertexCount  Relation a
y)
        , Set a -> Set a -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Relation a -> Set a
forall a. Relation a -> Set a
vertexSet   Relation a
x) (Relation a -> Set a
forall a. Relation a -> Set a
vertexSet    Relation a
y)
        , Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Relation a -> Int
forall a. Ord a => Relation a -> Int
edgeCount   Relation a
x) (Relation a -> Int
forall a. Ord a => Relation a -> Int
edgeCount    Relation a
y)
        , Set (a, a) -> Set (a, a) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Relation a -> Set (a, a)
forall a. Ord a => Relation a -> Set (a, a)
edgeSet     Relation a
x) (Relation a -> Set (a, a)
forall a. Ord a => Relation a -> Set (a, a)
edgeSet      Relation a
y) ]
instance (Ord a, Num a) => Num (Relation a) where
    fromInteger :: Integer -> Relation a
fromInteger = a -> Relation a
forall a. a -> Relation a
vertex (a -> Relation a) -> (Integer -> a) -> Integer -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> a
forall a. Num a => Integer -> a
fromInteger
    + :: Relation a -> Relation a -> Relation a
(+)         = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
overlay
    * :: Relation a -> Relation a -> Relation a
(*)         = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
connect
    signum :: Relation a -> Relation a
signum      = Relation a -> Relation a -> Relation a
forall a b. a -> b -> a
const Relation a
forall a. Relation a
empty
    abs :: Relation a -> Relation a
abs         = Relation a -> Relation a
forall a. a -> a
id
    negate :: Relation a -> Relation a
negate      = Relation a -> Relation a
forall a. a -> a
id
instance Ord a => Semigroup (Relation a) where
    <> :: Relation a -> Relation a -> Relation a
(<>) = Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
overlay
instance Ord a => Monoid (Relation a) where
    mempty :: Relation a
mempty = Relation a
forall a. Relation a
empty
toSymmetric :: Ord a => R.Relation a -> Relation a
toSymmetric :: Relation a -> Relation a
toSymmetric = Relation a -> Relation a
forall a. Relation a -> Relation a
SR (Relation a -> Relation a)
-> (Relation a -> Relation a) -> Relation a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
R.symmetricClosure
empty :: Relation a
empty :: Relation a
empty = Relation a -> Relation a
coerce Relation a
forall a. Relation a
R.empty
vertex :: a -> Relation a
vertex :: a -> Relation a
vertex = (a -> Relation a) -> a -> Relation a
coerce a -> Relation a
forall a. a -> Relation a
R.vertex
edge :: Ord a => a -> a -> Relation a
edge :: a -> a -> Relation a
edge a
x a
y = Relation a -> Relation a
forall a. Relation a -> Relation a
SR (Relation a -> Relation a) -> Relation a -> Relation a
forall a b. (a -> b) -> a -> b
$ [(a, a)] -> Relation a
forall a. Ord a => [(a, a)] -> Relation a
R.edges [(a
x,a
y), (a
y,a
x)]
overlay :: Ord a => Relation a -> Relation a -> Relation a
overlay :: Relation a -> Relation a -> Relation a
overlay = (Relation a -> Relation a -> Relation a)
-> Relation a -> Relation a -> Relation a
coerce Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
R.overlay
connect :: Ord a => Relation a -> Relation a -> Relation a
connect :: Relation a -> Relation a -> Relation a
connect Relation a
x Relation a
y = (Relation a -> Relation a -> Relation a)
-> Relation a -> Relation a -> Relation a
coerce Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
R.connect Relation a
x Relation a
y Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
`overlay` [a] -> [a] -> Relation a
forall a. Ord a => [a] -> [a] -> Relation a
biclique (Relation a -> [a]
forall a. Relation a -> [a]
vertexList Relation a
y) (Relation a -> [a]
forall a. Relation a -> [a]
vertexList Relation a
x)
vertices :: Ord a => [a] -> Relation a
vertices :: [a] -> Relation a
vertices = ([a] -> Relation a) -> [a] -> Relation a
coerce [a] -> Relation a
forall a. Ord a => [a] -> Relation a
R.vertices
edges :: Ord a => [(a, a)] -> Relation a
edges :: [(a, a)] -> Relation a
edges = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([(a, a)] -> Relation a) -> [(a, a)] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(a, a)] -> Relation a
forall a. Ord a => [(a, a)] -> Relation a
R.edges
overlays :: Ord a => [Relation a] -> Relation a
overlays :: [Relation a] -> Relation a
overlays = ([Relation a] -> Relation a) -> [Relation a] -> Relation a
coerce [Relation a] -> Relation a
forall a. Ord a => [Relation a] -> Relation a
R.overlays
connects :: Ord a => [Relation a] -> Relation a
connects :: [Relation a] -> Relation a
connects = (Relation a -> Relation a -> Relation a)
-> Relation a -> [Relation a] -> Relation a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Relation a -> Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a -> Relation a
connect Relation a
forall a. Relation a
empty
isSubgraphOf :: Ord a => Relation a -> Relation a -> Bool
isSubgraphOf :: Relation a -> Relation a -> Bool
isSubgraphOf = (Relation a -> Relation a -> Bool)
-> Relation a -> Relation a -> Bool
coerce Relation a -> Relation a -> Bool
forall a. Ord a => Relation a -> Relation a -> Bool
R.isSubgraphOf
isEmpty :: Relation a -> Bool
isEmpty :: Relation a -> Bool
isEmpty = (Relation a -> Bool) -> Relation a -> Bool
coerce Relation a -> Bool
forall a. Relation a -> Bool
R.isEmpty
hasVertex :: Ord a => a -> Relation a -> Bool
hasVertex :: a -> Relation a -> Bool
hasVertex = (a -> Relation a -> Bool) -> a -> Relation a -> Bool
coerce a -> Relation a -> Bool
forall a. Ord a => a -> Relation a -> Bool
R.hasVertex
hasEdge :: Ord a => a -> a -> Relation a -> Bool
hasEdge :: a -> a -> Relation a -> Bool
hasEdge = (a -> a -> Relation a -> Bool) -> a -> a -> Relation a -> Bool
coerce a -> a -> Relation a -> Bool
forall a. Ord a => a -> a -> Relation a -> Bool
R.hasEdge
vertexCount :: Relation a -> Int
vertexCount :: Relation a -> Int
vertexCount = (Relation a -> Int) -> Relation a -> Int
coerce Relation a -> Int
forall a. Relation a -> Int
R.vertexCount
edgeCount :: Ord a => Relation a -> Int
edgeCount :: Relation a -> Int
edgeCount = Set (a, a) -> Int
forall a. Set a -> Int
Set.size (Set (a, a) -> Int)
-> (Relation a -> Set (a, a)) -> Relation a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Set (a, a)
forall a. Ord a => Relation a -> Set (a, a)
edgeSet
vertexList :: Relation a -> [a]
vertexList :: Relation a -> [a]
vertexList = (Relation a -> [a]) -> Relation a -> [a]
coerce Relation a -> [a]
forall a. Relation a -> [a]
R.vertexList
edgeList :: Ord a => Relation a -> [(a, a)]
edgeList :: Relation a -> [(a, a)]
edgeList = Set (a, a) -> [(a, a)]
forall a. Set a -> [a]
Set.toAscList (Set (a, a) -> [(a, a)])
-> (Relation a -> Set (a, a)) -> Relation a -> [(a, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Set (a, a)
forall a. Ord a => Relation a -> Set (a, a)
edgeSet
vertexSet :: Relation a -> Set a
vertexSet :: Relation a -> Set a
vertexSet = (Relation a -> Set a) -> Relation a -> Set a
coerce Relation a -> Set a
forall a. Relation a -> Set a
R.vertexSet
edgeSet :: Ord a => Relation a -> Set (a, a)
edgeSet :: Relation a -> Set (a, a)
edgeSet = ((a, a) -> Bool) -> Set (a, a) -> Set (a, a)
forall a. (a -> Bool) -> Set a -> Set a
Set.filter ((a -> a -> Bool) -> (a, a) -> Bool
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry a -> a -> Bool
forall a. Ord a => a -> a -> Bool
(<=)) (Set (a, a) -> Set (a, a))
-> (Relation a -> Set (a, a)) -> Relation a -> Set (a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Set (a, a)
forall a. Relation a -> Set (a, a)
R.edgeSet (Relation a -> Set (a, a))
-> (Relation a -> Relation a) -> Relation a -> Set (a, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Relation a
forall a. Relation a -> Relation a
fromSymmetric
adjacencyList :: Eq a => Relation a -> [(a, [a])]
adjacencyList :: Relation a -> [(a, [a])]
adjacencyList = (Relation a -> [(a, [a])]) -> Relation a -> [(a, [a])]
coerce Relation a -> [(a, [a])]
forall a. Eq a => Relation a -> [(a, [a])]
R.adjacencyList
path :: Ord a => [a] -> Relation a
path :: [a] -> Relation a
path = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([a] -> Relation a) -> [a] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Relation a
forall a. Ord a => [a] -> Relation a
R.path
circuit :: Ord a => [a] -> Relation a
circuit :: [a] -> Relation a
circuit = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([a] -> Relation a) -> [a] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Relation a
forall a. Ord a => [a] -> Relation a
R.circuit
clique :: Ord a => [a] -> Relation a
clique :: [a] -> Relation a
clique = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([a] -> Relation a) -> [a] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Relation a
forall a. Ord a => [a] -> Relation a
R.clique
biclique :: Ord a => [a] -> [a] -> Relation a
biclique :: [a] -> [a] -> Relation a
biclique [a]
xs [a]
ys = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric ([a] -> [a] -> Relation a
forall a. Ord a => [a] -> [a] -> Relation a
R.biclique [a]
xs [a]
ys)
star :: Ord a => a -> [a] -> Relation a
star :: a -> [a] -> Relation a
star a
x = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([a] -> Relation a) -> [a] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [a] -> Relation a
forall a. Ord a => a -> [a] -> Relation a
R.star a
x
stars :: Ord a => [(a, [a])] -> Relation a
stars :: [(a, [a])] -> Relation a
stars = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> ([(a, [a])] -> Relation a) -> [(a, [a])] -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(a, [a])] -> Relation a
forall a. Ord a => [(a, [a])] -> Relation a
R.stars
tree :: Ord a => Tree a -> Relation a
tree :: Tree a -> Relation a
tree = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> (Tree a -> Relation a) -> Tree a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Tree a -> Relation a
forall a. Ord a => Tree a -> Relation a
R.tree
forest :: Ord a => Forest a -> Relation a
forest :: Forest a -> Relation a
forest = Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
toSymmetric (Relation a -> Relation a)
-> (Forest a -> Relation a) -> Forest a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Forest a -> Relation a
forall a. Ord a => Forest a -> Relation a
R.forest
removeVertex :: Ord a => a -> Relation a -> Relation a
removeVertex :: a -> Relation a -> Relation a
removeVertex = (a -> Relation a -> Relation a) -> a -> Relation a -> Relation a
coerce a -> Relation a -> Relation a
forall a. Ord a => a -> Relation a -> Relation a
R.removeVertex
removeEdge :: Ord a => a -> a -> Relation a -> Relation a
removeEdge :: a -> a -> Relation a -> Relation a
removeEdge a
x a
y = Relation a -> Relation a
forall a. Relation a -> Relation a
SR (Relation a -> Relation a)
-> (Relation a -> Relation a) -> Relation a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> Relation a -> Relation a
forall a. Ord a => a -> a -> Relation a -> Relation a
R.removeEdge a
x a
y (Relation a -> Relation a)
-> (Relation a -> Relation a) -> Relation a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> a -> Relation a -> Relation a
forall a. Ord a => a -> a -> Relation a -> Relation a
R.removeEdge a
y a
x (Relation a -> Relation a)
-> (Relation a -> Relation a) -> Relation a -> Relation a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Relation a -> Relation a
forall a. Relation a -> Relation a
fromSymmetric
replaceVertex :: Ord a => a -> a -> Relation a -> Relation a
replaceVertex :: a -> a -> Relation a -> Relation a
replaceVertex = (a -> a -> Relation a -> Relation a)
-> a -> a -> Relation a -> Relation a
coerce a -> a -> Relation a -> Relation a
forall a. Ord a => a -> a -> Relation a -> Relation a
R.replaceVertex
mergeVertices :: Ord a => (a -> Bool) -> a -> Relation a -> Relation a
mergeVertices :: (a -> Bool) -> a -> Relation a -> Relation a
mergeVertices = ((a -> Bool) -> a -> Relation a -> Relation a)
-> (a -> Bool) -> a -> Relation a -> Relation a
coerce (a -> Bool) -> a -> Relation a -> Relation a
forall a. Ord a => (a -> Bool) -> a -> Relation a -> Relation a
R.mergeVertices
gmap :: Ord b => (a -> b) -> Relation a -> Relation b
gmap :: (a -> b) -> Relation a -> Relation b
gmap = ((a -> b) -> Relation a -> Relation b)
-> (a -> b) -> Relation a -> Relation b
coerce (a -> b) -> Relation a -> Relation b
forall b a. Ord b => (a -> b) -> Relation a -> Relation b
R.gmap
induce :: (a -> Bool) -> Relation a -> Relation a
induce :: (a -> Bool) -> Relation a -> Relation a
induce = ((a -> Bool) -> Relation a -> Relation a)
-> (a -> Bool) -> Relation a -> Relation a
coerce (a -> Bool) -> Relation a -> Relation a
forall a. (a -> Bool) -> Relation a -> Relation a
R.induce
induceJust :: Ord a => Relation (Maybe a) -> Relation a
induceJust :: Relation (Maybe a) -> Relation a
induceJust = (Relation (Maybe a) -> Relation a)
-> Relation (Maybe a) -> Relation a
coerce Relation (Maybe a) -> Relation a
forall a. Ord a => Relation (Maybe a) -> Relation a
R.induceJust
neighbours :: Ord a => a -> Relation a -> Set a
neighbours :: a -> Relation a -> Set a
neighbours = (a -> Relation a -> Set a) -> a -> Relation a -> Set a
coerce a -> Relation a -> Set a
forall a. Ord a => a -> Relation a -> Set a
R.postSet
consistent :: Ord a => Relation a -> Bool
consistent :: Relation a -> Bool
consistent (SR Relation a
r) = Relation a -> Bool
forall a. Ord a => Relation a -> Bool
R.consistent Relation a
r Bool -> Bool -> Bool
&& Relation a
r Relation a -> Relation a -> Bool
forall a. Eq a => a -> a -> Bool
== Relation a -> Relation a
forall a. Ord a => Relation a -> Relation a
R.transpose Relation a
r