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.IntSet as IntSet
import qualified Data.Set as Set
import qualified Algebra.Graph as G
import qualified Algebra.Graph.AdjacencyIntMap as AIM
import qualified Algebra.Graph.AdjacencyMap as AM
import qualified Algebra.Graph.ToGraph as T
import qualified Algebra.Graph.Relation as R
newtype Relation a = SR {
forall a. Relation a -> Relation a
fromSymmetric :: R.Relation a
} deriving (Relation a -> Relation a -> Bool
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
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 -> ()
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 = forall a. Show a => a -> String
show forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall {a}. Ord a => Relation a -> Relation a
toRelation
where
toRelation :: Relation a -> Relation a
toRelation Relation a
r = forall a. Ord a => [a] -> Relation a
R.vertices (forall a. Relation a -> [a]
vertexList Relation a
r) forall a. Ord a => Relation a -> Relation a -> Relation a
`R.overlay` forall a. Ord a => [(a, a)] -> Relation a
R.edges (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 = forall a. Monoid a => [a] -> a
mconcat
[ forall a. Ord a => a -> a -> Ordering
compare (forall a. Relation a -> Int
vertexCount Relation a
x) (forall a. Relation a -> Int
vertexCount Relation a
y)
, forall a. Ord a => a -> a -> Ordering
compare (forall a. Relation a -> Set a
vertexSet Relation a
x) (forall a. Relation a -> Set a
vertexSet Relation a
y)
, forall a. Ord a => a -> a -> Ordering
compare (forall a. Ord a => Relation a -> Int
edgeCount Relation a
x) (forall a. Ord a => Relation a -> Int
edgeCount Relation a
y)
, forall a. Ord a => a -> a -> Ordering
compare (forall a. Ord a => Relation a -> Set (a, a)
edgeSet Relation a
x) (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 = forall a. a -> Relation a
vertex forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Num a => Integer -> a
fromInteger
+ :: Relation a -> Relation a -> Relation a
(+) = forall a. Ord a => Relation a -> Relation a -> Relation a
overlay
* :: Relation a -> Relation a -> Relation a
(*) = forall a. Ord a => Relation a -> Relation a -> Relation a
connect
signum :: Relation a -> Relation a
signum = forall a b. a -> b -> a
const forall a. Relation a
empty
abs :: Relation a -> Relation a
abs = forall a. a -> a
id
negate :: Relation a -> Relation a
negate = forall a. a -> a
id
instance Ord a => Semigroup (Relation a) where
<> :: 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 = forall a. Relation a
empty
instance Ord a => T.ToGraph (Relation a) where
type ToVertex (Relation a) = a
toGraph :: Relation a -> Graph (ToVertex (Relation a))
toGraph = forall t. ToGraph t => t -> Graph (ToVertex t)
T.toGraph forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
isEmpty :: Relation a -> Bool
isEmpty = forall a. Relation a -> Bool
isEmpty
hasVertex :: Eq (ToVertex (Relation a)) =>
ToVertex (Relation a) -> Relation a -> Bool
hasVertex = forall a. Ord a => a -> Relation a -> Bool
hasVertex
hasEdge :: Eq (ToVertex (Relation a)) =>
ToVertex (Relation a)
-> ToVertex (Relation a) -> Relation a -> Bool
hasEdge = forall a. Ord a => a -> a -> Relation a -> Bool
hasEdge
vertexCount :: Ord (ToVertex (Relation a)) => Relation a -> Int
vertexCount = forall a. Relation a -> Int
vertexCount
edgeCount :: Ord (ToVertex (Relation a)) => Relation a -> Int
edgeCount = forall a. Relation a -> Int
R.edgeCount forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
vertexList :: Ord (ToVertex (Relation a)) =>
Relation a -> [ToVertex (Relation a)]
vertexList = forall a. Relation a -> [a]
vertexList
vertexSet :: Ord (ToVertex (Relation a)) =>
Relation a -> Set (ToVertex (Relation a))
vertexSet = forall a. Relation a -> Set a
vertexSet
vertexIntSet :: (ToVertex (Relation a) ~ Int) => Relation a -> IntSet
vertexIntSet = [Int] -> IntSet
IntSet.fromAscList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> [a]
vertexList
edgeList :: Ord (ToVertex (Relation a)) =>
Relation a -> [(ToVertex (Relation a), ToVertex (Relation a))]
edgeList = forall a. Relation a -> [(a, a)]
R.edgeList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
edgeSet :: Ord (ToVertex (Relation a)) =>
Relation a -> Set (ToVertex (Relation a), ToVertex (Relation a))
edgeSet = forall a. Relation a -> Set (a, a)
R.relation forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
adjacencyList :: Ord (ToVertex (Relation a)) =>
Relation a -> [(ToVertex (Relation a), [ToVertex (Relation a)])]
adjacencyList = forall a. Eq a => Relation a -> [(a, [a])]
adjacencyList
toAdjacencyMap :: Ord (ToVertex (Relation a)) =>
Relation a -> AdjacencyMap (ToVertex (Relation a))
toAdjacencyMap = forall t.
(ToGraph t, Ord (ToVertex t)) =>
t -> AdjacencyMap (ToVertex t)
T.toAdjacencyMap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
toAdjacencyIntMap :: (ToVertex (Relation a) ~ Int) => Relation a -> AdjacencyIntMap
toAdjacencyIntMap = forall t. (ToGraph t, ToVertex t ~ Int) => t -> AdjacencyIntMap
T.toAdjacencyIntMap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
toAdjacencyMapTranspose :: Ord (ToVertex (Relation a)) =>
Relation a -> AdjacencyMap (ToVertex (Relation a))
toAdjacencyMapTranspose = forall t.
(ToGraph t, Ord (ToVertex t)) =>
t -> AdjacencyMap (ToVertex t)
T.toAdjacencyMap
toAdjacencyIntMapTranspose :: (ToVertex (Relation a) ~ Int) => Relation a -> AdjacencyIntMap
toAdjacencyIntMapTranspose = forall t. (ToGraph t, ToVertex t ~ Int) => t -> AdjacencyIntMap
T.toAdjacencyIntMap
toSymmetric :: Ord a => R.Relation a -> Relation a
toSymmetric :: forall a. Ord a => Relation a -> Relation a
toSymmetric = forall a. Relation a -> Relation a
SR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => Relation a -> Relation a
R.symmetricClosure
empty :: Relation a
empty :: forall a. Relation a
empty = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Relation a
R.empty
vertex :: a -> Relation a
vertex :: forall a. a -> Relation a
vertex = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. a -> Relation a
R.vertex
edge :: Ord a => a -> a -> Relation a
edge :: forall a. Ord a => a -> a -> Relation a
edge a
x a
y = forall a. Relation a -> Relation a
SR forall a b. (a -> b) -> a -> b
$ 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 :: forall a. Ord a => Relation a -> Relation a -> Relation a
overlay = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => Relation a -> Relation a -> Relation a
R.overlay
connect :: Ord a => Relation a -> Relation a -> Relation a
connect :: forall a. Ord a => Relation a -> Relation a -> Relation a
connect Relation a
x Relation a
y = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => Relation a -> Relation a -> Relation a
R.connect Relation a
x Relation a
y forall a. Ord a => Relation a -> Relation a -> Relation a
`overlay` forall a. Ord a => [a] -> [a] -> Relation a
biclique (forall a. Relation a -> [a]
vertexList Relation a
y) (forall a. Relation a -> [a]
vertexList Relation a
x)
vertices :: Ord a => [a] -> Relation a
vertices :: forall a. Ord a => [a] -> Relation a
vertices = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => [a] -> Relation a
R.vertices
edges :: Ord a => [(a, a)] -> Relation a
edges :: forall a. Ord a => [(a, a)] -> Relation a
edges = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [(a, a)] -> Relation a
R.edges
overlays :: Ord a => [Relation a] -> Relation a
overlays :: forall a. Ord a => [Relation a] -> Relation a
overlays = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => [Relation a] -> Relation a
R.overlays
connects :: Ord a => [Relation a] -> Relation a
connects :: forall a. Ord a => [Relation a] -> Relation a
connects = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall a. Ord a => Relation a -> Relation a -> Relation a
connect forall a. Relation a
empty
isSubgraphOf :: Ord a => Relation a -> Relation a -> Bool
isSubgraphOf :: forall a. Ord a => Relation a -> Relation a -> Bool
isSubgraphOf = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => Relation a -> Relation a -> Bool
R.isSubgraphOf
isEmpty :: Relation a -> Bool
isEmpty :: forall a. Relation a -> Bool
isEmpty = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Relation a -> Bool
R.isEmpty
hasVertex :: Ord a => a -> Relation a -> Bool
hasVertex :: forall a. Ord a => a -> Relation a -> Bool
hasVertex = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => a -> Relation a -> Bool
R.hasVertex
hasEdge :: Ord a => a -> a -> Relation a -> Bool
hasEdge :: forall a. Ord a => a -> a -> Relation a -> Bool
hasEdge = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => a -> a -> Relation a -> Bool
R.hasEdge
vertexCount :: Relation a -> Int
vertexCount :: forall a. Relation a -> Int
vertexCount = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Relation a -> Int
R.vertexCount
edgeCount :: Ord a => Relation a -> Int
edgeCount :: forall a. Ord a => Relation a -> Int
edgeCount = forall a. Set a -> Int
Set.size forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => Relation a -> Set (a, a)
edgeSet
vertexList :: Relation a -> [a]
vertexList :: forall a. Relation a -> [a]
vertexList = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Relation a -> [a]
R.vertexList
edgeList :: Ord a => Relation a -> [(a, a)]
edgeList :: forall a. Ord a => Relation a -> [(a, a)]
edgeList = forall a. Set a -> [a]
Set.toAscList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => Relation a -> Set (a, a)
edgeSet
vertexSet :: Relation a -> Set a
vertexSet :: forall a. Relation a -> Set a
vertexSet = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Relation a -> Set a
R.vertexSet
edgeSet :: Ord a => Relation a -> Set (a, a)
edgeSet :: forall a. Ord a => Relation a -> Set (a, a)
edgeSet = forall a. (a -> Bool) -> Set a -> Set a
Set.filter (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry forall a. Ord a => a -> a -> Bool
(<=)) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Set (a, a)
R.edgeSet forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
adjacencyList :: Eq a => Relation a -> [(a, [a])]
adjacencyList :: forall a. Eq a => Relation a -> [(a, [a])]
adjacencyList = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Eq a => Relation a -> [(a, [a])]
R.adjacencyList
path :: Ord a => [a] -> Relation a
path :: forall a. Ord a => [a] -> Relation a
path = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Relation a
R.path
circuit :: Ord a => [a] -> Relation a
circuit :: forall a. Ord a => [a] -> Relation a
circuit = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Relation a
R.circuit
clique :: Ord a => [a] -> Relation a
clique :: forall a. Ord a => [a] -> Relation a
clique = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [a] -> Relation a
R.clique
biclique :: Ord a => [a] -> [a] -> Relation a
biclique :: forall a. Ord a => [a] -> [a] -> Relation a
biclique [a]
xs [a]
ys = forall a. Ord a => Relation a -> Relation a
toSymmetric (forall a. Ord a => [a] -> [a] -> Relation a
R.biclique [a]
xs [a]
ys)
star :: Ord a => a -> [a] -> Relation a
star :: forall a. Ord a => a -> [a] -> Relation a
star a
x = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> [a] -> Relation a
R.star a
x
stars :: Ord a => [(a, [a])] -> Relation a
stars :: forall a. Ord a => [(a, [a])] -> Relation a
stars = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => [(a, [a])] -> Relation a
R.stars
tree :: Ord a => Tree a -> Relation a
tree :: forall a. Ord a => Tree a -> Relation a
tree = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => Tree a -> Relation a
R.tree
forest :: Ord a => Forest a -> Relation a
forest :: forall a. Ord a => Forest a -> Relation a
forest = forall a. Ord a => Relation a -> Relation a
toSymmetric forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => Forest a -> Relation a
R.forest
removeVertex :: Ord a => a -> Relation a -> Relation a
removeVertex :: forall a. Ord a => a -> Relation a -> Relation a
removeVertex = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => a -> Relation a -> Relation a
R.removeVertex
removeEdge :: Ord a => a -> a -> Relation a -> Relation a
removeEdge :: forall a. Ord a => a -> a -> Relation a -> Relation a
removeEdge a
x a
y = forall a. Relation a -> Relation a
SR forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> Relation a -> Relation a
R.removeEdge a
x a
y forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Ord a => a -> a -> Relation a -> Relation a
R.removeEdge a
y a
x forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Relation a -> Relation a
fromSymmetric
replaceVertex :: Ord a => a -> a -> Relation a -> Relation a
replaceVertex :: forall a. Ord a => a -> a -> Relation a -> Relation a
replaceVertex = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => a -> a -> Relation a -> Relation a
R.replaceVertex
mergeVertices :: Ord a => (a -> Bool) -> a -> Relation a -> Relation a
mergeVertices :: forall a. Ord a => (a -> Bool) -> a -> Relation a -> Relation a
mergeVertices = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => (a -> Bool) -> a -> Relation a -> Relation a
R.mergeVertices
gmap :: Ord b => (a -> b) -> Relation a -> Relation b
gmap :: forall b a. Ord b => (a -> b) -> Relation a -> Relation b
gmap = coerce :: forall a b. Coercible a b => a -> b
coerce forall b a. Ord b => (a -> b) -> Relation a -> Relation b
R.gmap
induce :: (a -> Bool) -> Relation a -> Relation a
induce :: forall a. (a -> Bool) -> Relation a -> Relation a
induce = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. (a -> Bool) -> Relation a -> Relation a
R.induce
induceJust :: Ord a => Relation (Maybe a) -> Relation a
induceJust :: forall a. Ord a => Relation (Maybe a) -> Relation a
induceJust = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => Relation (Maybe a) -> Relation a
R.induceJust
neighbours :: Ord a => a -> Relation a -> Set a
neighbours :: forall a. Ord a => a -> Relation a -> Set a
neighbours = coerce :: forall a b. Coercible a b => a -> b
coerce forall a. Ord a => a -> Relation a -> Set a
R.postSet
consistent :: Ord a => Relation a -> Bool
consistent :: forall a. Ord a => Relation a -> Bool
consistent (SR Relation a
r) = forall a. Ord a => Relation a -> Bool
R.consistent Relation a
r Bool -> Bool -> Bool
&& Relation a
r forall a. Eq a => a -> a -> Bool
== forall a. Ord a => Relation a -> Relation a
R.transpose Relation a
r