| Copyright | (c) Andrey Mokhov 2016-2019 |
|---|---|
| License | MIT (see the file LICENSE) |
| Maintainer | andrey.mokhov@gmail.com |
| Stability | unstable |
| Safe Haskell | None |
| Language | Haskell2010 |
Algebra.Graph.Relation.Symmetric.Internal
Description
This module exposes the implementation of symmetric binary relation data type. The API is unstable and unsafe, and is exposed only for documentation. You should use the non-internal module Algebra.Graph.Relation.Symmetric instead.
Synopsis
- newtype Relation a = SR (Relation a)
- fromSymmetric :: Relation a -> Relation a
- empty :: Relation a
- vertex :: a -> Relation a
- overlay :: Ord a => Relation a -> Relation a -> Relation a
- connect :: Ord a => Relation a -> Relation a -> Relation a
- edgeSet :: Ord a => Relation a -> Set (a, a)
- consistent :: Ord a => Relation a -> Bool
Implementation of symmetric binary relations
This data type represents a symmetric binary relation over a set of
elements of type a. Symmetric relations satisfy all laws of the
Undirected type class, including the commutativity of
connect:
connectx y ==connecty x
The Show instance lists edge vertices in non-decreasing order:
show (empty :: Relation Int) == "empty" show (1 :: Relation Int) == "vertex 1" show (1 + 2 :: Relation Int) == "vertices [1,2]" show (1 * 2 :: Relation Int) == "edge 1 2" show (2 * 1 :: Relation Int) == "edge 1 2" show (1 * 2 * 1 :: Relation Int) == "edges [(1,1),(1,2)]" show (3 * 2 * 1 :: Relation Int) == "edges [(1,2),(1,3),(2,3)]" show (1 * 2 + 3 :: Relation Int) == "overlay (vertex 3) (edge 1 2)"
The total order on graphs is defined using size-lexicographic comparison:
- Compare the number of vertices. In case of a tie, continue.
- Compare the sets of vertices. In case of a tie, continue.
- Compare the number of edges. In case of a tie, continue.
- Compare the sets of edges.
Here are a few examples:
vertex1 <vertex2vertex3 <edge1 2vertex1 <edge1 1edge1 1 <edge1 2edge1 2 <edge1 1 +edge2 2edge2 1 <edge1 3
edge1 2 ==edge2 1
Note that the resulting order refines the
isSubgraphOf relation and is compatible with
overlay and connect operations:
isSubgraphOf x y ==> x <= yempty <= x
x <= x + y
x + y <= x * yInstances
fromSymmetric :: Relation a -> Relation a Source #
Extract the underlying symmetric Algebra.Graph.Relation. Complexity: O(1) time and memory.
fromSymmetric (edge1 2) ==edges[(1,2), (2,1)]vertexCount. fromSymmetric ==vertexCountedgeCount. fromSymmetric <= (*2) .edgeCount
Construct the empty graph. Complexity: O(1) time and memory.
isEmptyempty == TruehasVertexx empty == FalsevertexCountempty == 0edgeCountempty == 0
vertex :: a -> Relation a Source #
Construct the graph comprising a single isolated vertex. Complexity: O(1) time and memory.
isEmpty(vertex x) == FalsehasVertexx (vertex x) == TruevertexCount(vertex x) == 1edgeCount(vertex x) == 0
overlay :: Ord a => Relation a -> Relation a -> Relation a Source #
Overlay two graphs. This is a commutative, associative and idempotent
operation with the identity empty.
Complexity: O((n + m) * log(n)) time and O(n + m) memory.
isEmpty(overlay x y) ==isEmptyx &&isEmptyyhasVertexz (overlay x y) ==hasVertexz x ||hasVertexz yvertexCount(overlay x y) >=vertexCountxvertexCount(overlay x y) <=vertexCountx +vertexCountyedgeCount(overlay x y) >=edgeCountxedgeCount(overlay x y) <=edgeCountx +edgeCountyvertexCount(overlay 1 2) == 2edgeCount(overlay 1 2) == 0
connect :: Ord a => Relation a -> Relation a -> Relation a Source #
Connect two graphs. This is a commutative and associative operation with
the identity empty, which distributes over overlay and obeys the
decomposition axiom.
Complexity: O((n + m) * log(n)) time and O(n + m) memory. Note that the
number of edges in the resulting graph is quadratic with respect to the number
of vertices of the arguments: m = O(m1 + m2 + n1 * n2).
connect x y == connect y xisEmpty(connect x y) ==isEmptyx &&isEmptyyhasVertexz (connect x y) ==hasVertexz x ||hasVertexz yvertexCount(connect x y) >=vertexCountxvertexCount(connect x y) <=vertexCountx +vertexCountyedgeCount(connect x y) >=edgeCountxedgeCount(connect x y) >=edgeCountyedgeCount(connect x y) >=vertexCountx *vertexCounty `div` 2vertexCount(connect 1 2) == 2edgeCount(connect 1 2) == 1
edgeSet :: Ord a => Relation a -> Set (a, a) Source #
The set of edges of a given graph, where edge vertices appear in the non-decreasing order. Complexity: O(m) time.
Note: If you need the set of edges where an edge appears in both directions,
use . The latter is much
faster than this function, and takes only O(1) time and memory.relation . fromSymmetric
edgeSetempty== Set.emptyedgeSet (vertexx) == Set.emptyedgeSet (edgex y) == Set.singleton(min x y, max x y)
consistent :: Ord a => Relation a -> Bool Source #
Check if the internal representation of a symmetric relation is consistent,
i.e. if (i) all pairs of elements in the relation refer to existing
elements in the domain, and (ii) all edges have their symmetric
counterparts. It should be impossible to create an inconsistent Relation,
and we use this function in testing.
Note: this function is for internal use only.
consistentempty== True consistent (vertexx) == True consistent (overlayx y) == True consistent (connectx y) == True consistent (edgex y) == True consistent (edgesxs) == True consistent (starsxs) == True