Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Data type for representing connected planar graphs
Synopsis
- data World
- type family DualOf (sp :: World) where ...
- dualDualIdentity :: forall w. DualOf (DualOf w) :~: w
- newtype VertexId s (w :: World) = VertexId {
- _unVertexId :: Int
- type VertexId' s = VertexId s Primal
- unVertexId :: Getter (VertexId s w) Int
- newtype FaceId s w = FaceId {}
- type FaceId' s = FaceId s Primal
- data PlanarGraph s (w :: World) v e f = PlanarGraph {
- _embedding :: Permutation (Dart s)
- _vertexData :: Vector v
- _rawDartData :: Vector e
- _faceData :: Vector f
- _dual :: PlanarGraph s (DualOf w) f e v
- embedding :: Getter (PlanarGraph s w v e f) (Permutation (Dart s))
- vertexData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v' e f) (Vector v) (Vector v')
- rawDartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector e) (Vector e')
- faceData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f') (Vector f) (Vector f')
- dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v)
- dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- updateData :: forall s w v e f v' e' f'. (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f'
- updateData' :: DualOf (DualOf w) ~ w => (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f'
- reorderEdgeData :: Foldable f => f (Dart s, e) -> Vector e
- traverseVertices :: Applicative m => (VertexId s w -> v -> m v') -> PlanarGraph s w v e f -> m (PlanarGraph s w v' e f)
- traverseDarts :: Applicative m => (Dart s -> e -> m e') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e' f)
- traverseFaces :: Applicative m => (FaceId s w -> f -> m f') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e f')
- planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () ()
- planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal () e ()
- toAdjacencyLists :: PlanarGraph s w v e f -> [(VertexId s w, Vector (VertexId s w))]
- numVertices :: PlanarGraph s w v e f -> Int
- numDarts :: PlanarGraph s w v e f -> Int
- numEdges :: PlanarGraph s w v e f -> Int
- numFaces :: PlanarGraph s w v e f -> Int
- vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w)
- vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v)
- darts' :: PlanarGraph s w v e f -> Vector (Dart s)
- darts :: PlanarGraph s w v e f -> Vector (Dart s, e)
- edges' :: PlanarGraph s w v e f -> Vector (Dart s)
- edges :: PlanarGraph s w v e f -> Vector (Dart s, e)
- tailOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w
- headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w
- endPoints :: Dart s -> PlanarGraph s w v e f -> (VertexId s w, VertexId s w)
- incidentEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- incomingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- neighboursOf :: VertexId s w -> PlanarGraph s w v e f -> Vector (VertexId s w)
- nextIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
- prevIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s
- class HasDataOf g i where
- endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v)
- endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v)
- computeDual :: forall s w v e f. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
- computeDual' :: DualOf (DualOf w) ~ w => PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v
Documentation
>>>
:{
let dart i s = Dart (Arc i) (read s) (aA:aB:aC:aD:aE:aG:_) = take 6 [Arc 0..] myGraph :: PlanarGraph () Primal () String () myGraph = planarGraph [ [ (Dart aA Negative, "a-") , (Dart aC Positive, "c+") , (Dart aB Positive, "b+") , (Dart aA Positive, "a+") ] , [ (Dart aE Negative, "e-") , (Dart aB Negative, "b-") , (Dart aD Negative, "d-") , (Dart aG Positive, "g+") ] , [ (Dart aE Positive, "e+") , (Dart aD Positive, "d+") , (Dart aC Negative, "c-") ] , [ (Dart aG Negative, "g-") ] ] :}
This represents the following graph. Note that the graph is undirected, the arrows are just to indicate what the Positive direction of the darts is.
Representing The World
The world in which the graph lives
type family DualOf (sp :: World) where ... Source #
We can take the dual of a world. For the Primal this gives us the Dual, for the Dual this gives us the Primal.
VertexId's
newtype VertexId s (w :: World) Source #
A vertex in a planar graph. A vertex is tied to a particular planar graph by the phantom type s, and to a particular world w.
Instances
FaceId's
The type to reprsent FaceId's
Instances
Enum (FaceId s w) Source # | |
Defined in Data.PlanarGraph.Core succ :: FaceId s w -> FaceId s w # pred :: FaceId s w -> FaceId s w # fromEnum :: FaceId s w -> Int # enumFrom :: FaceId s w -> [FaceId s w] # enumFromThen :: FaceId s w -> FaceId s w -> [FaceId s w] # enumFromTo :: FaceId s w -> FaceId s w -> [FaceId s w] # enumFromThenTo :: FaceId s w -> FaceId s w -> FaceId s w -> [FaceId s w] # | |
Eq (FaceId s w) Source # | |
Ord (FaceId s w) Source # | |
Show (FaceId s w) Source # | |
ToJSON (FaceId s w) Source # | |
Defined in Data.PlanarGraph.Core | |
FromJSON (FaceId s w) Source # | |
HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
Defined in Data.PlanarGraph.Core dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source # | |
type DataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
Defined in Data.PlanarGraph.Core |
The graph type itself
data PlanarGraph s (w :: World) v e f Source #
A *connected* Planar graph with bidirected edges. I.e. the edges (darts) are directed, however, for every directed edge, the edge in the oposite direction is also in the graph.
The types v, e, and f are the are the types of the data associated with the vertices, edges, and faces, respectively.
The orbits in the embedding are assumed to be in counterclockwise order. Therefore, every dart directly bounds the face to its right.
PlanarGraph | |
|
Instances
lenses and getters
embedding :: Getter (PlanarGraph s w v e f) (Permutation (Dart s)) Source #
Get the embedding, reprsented as a permutation of the darts, of this graph.
vertexData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v' e f) (Vector v) (Vector v') Source #
rawDartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector e) (Vector e') Source #
faceData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f') (Vector f) (Vector f') Source #
dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) Source #
Get the dual graph of this graph.
dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #
lens to access the Dart Data
edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e')) Source #
edgeData is just an alias for dartData
updateData :: forall s w v e f v' e' f'. (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f' Source #
Helper function to update the data in a planar graph. Takes care to update both the data in the original graph as well as in the dual.
updateData' :: DualOf (DualOf w) ~ w => (Vector v -> Vector v') -> (Vector e -> Vector e') -> (Vector f -> Vector f') -> PlanarGraph s w v e f -> PlanarGraph s w v' e' f' Source #
The function that does the actual work for updateData
reorderEdgeData :: Foldable f => f (Dart s, e) -> Vector e Source #
Reorders the edge data to be in the right order to set edgeData
traverseVertices :: Applicative m => (VertexId s w -> v -> m v') -> PlanarGraph s w v e f -> m (PlanarGraph s w v' e f) Source #
Traverse the vertices
(^.vertexData) $ traverseVertices (i x -> Just (i,x)) myGraph Just [(VertexId 0,()),(VertexId 1,()),(VertexId 2,()),(VertexId 3,())] >>> traverseVertices (i x -> print (i,x)) myGraph >> pure () (VertexId 0,()) (VertexId 1,()) (VertexId 2,()) (VertexId 3,())
traverseDarts :: Applicative m => (Dart s -> e -> m e') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e' f) Source #
Traverses the darts
>>>
traverseDarts (\d x -> print (d,x)) myGraph >> pure ()
(Dart (Arc 0) +1,"a+") (Dart (Arc 0) -1,"a-") (Dart (Arc 1) +1,"b+") (Dart (Arc 1) -1,"b-") (Dart (Arc 2) +1,"c+") (Dart (Arc 2) -1,"c-") (Dart (Arc 3) +1,"d+") (Dart (Arc 3) -1,"d-") (Dart (Arc 4) +1,"e+") (Dart (Arc 4) -1,"e-") (Dart (Arc 5) +1,"g+") (Dart (Arc 5) -1,"g-")
traverseFaces :: Applicative m => (FaceId s w -> f -> m f') -> PlanarGraph s w v e f -> m (PlanarGraph s w v e f') Source #
Traverses the faces
>>>
traverseFaces (\i x -> print (i,x)) myGraph >> pure ()
(FaceId 0,()) (FaceId 1,()) (FaceId 2,()) (FaceId 3,())
Constructing a Planar graph
planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () () Source #
Construct a planar graph
running time: \(O(n)\).
planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal () e () Source #
Construct a planar graph, given the darts in cyclic order around each vertex.
running time: \(O(n)\).
toAdjacencyLists :: PlanarGraph s w v e f -> [(VertexId s w, Vector (VertexId s w))] Source #
Produces the adjacencylists for all vertices in the graph. For every vertex, the adjacent vertices are given in counter clockwise order.
Note that in case a vertex u as a self loop, we have that this vertexId occurs twice in the list of neighbours, i.e.: u : [...,u,..,u,...]. Similarly, if there are multiple darts between a pair of edges they occur multiple times.
running time: \(O(n)\)
Convenience functions
numVertices :: PlanarGraph s w v e f -> Int Source #
Get the number of vertices
>>>
numVertices myGraph
4
numDarts :: PlanarGraph s w v e f -> Int Source #
Get the number of Darts
>>>
numDarts myGraph
12
numEdges :: PlanarGraph s w v e f -> Int Source #
Get the number of Edges
>>>
numEdges myGraph
6
numFaces :: PlanarGraph s w v e f -> Int Source #
Get the number of faces
>>>
numFaces myGraph
4
vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w) Source #
Enumerate all vertices
>>>
vertices' myGraph
[VertexId 0,VertexId 1,VertexId 2,VertexId 3]
vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v) Source #
Enumerate all vertices, together with their vertex data
darts :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #
Get all darts together with their data
>>>
mapM_ print $ darts myGraph
(Dart (Arc 0) -1,"a-") (Dart (Arc 2) +1,"c+") (Dart (Arc 1) +1,"b+") (Dart (Arc 0) +1,"a+") (Dart (Arc 4) -1,"e-") (Dart (Arc 1) -1,"b-") (Dart (Arc 3) -1,"d-") (Dart (Arc 5) +1,"g+") (Dart (Arc 4) +1,"e+") (Dart (Arc 3) +1,"d+") (Dart (Arc 2) -1,"c-") (Dart (Arc 5) -1,"g-")
edges' :: PlanarGraph s w v e f -> Vector (Dart s) Source #
Enumerate all edges. We report only the Positive darts
edges :: PlanarGraph s w v e f -> Vector (Dart s, e) Source #
Enumerate all edges with their edge data. We report only the Positive darts.
>>>
mapM_ print $ edges myGraph
(Dart (Arc 2) +1,"c+") (Dart (Arc 1) +1,"b+") (Dart (Arc 0) +1,"a+") (Dart (Arc 5) +1,"g+") (Dart (Arc 4) +1,"e+") (Dart (Arc 3) +1,"d+")
tailOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #
The tail of a dart, i.e. the vertex this dart is leaving from
running time: \(O(1)\)
headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source #
The vertex this dart is heading in to
running time: \(O(1)\)
endPoints :: Dart s -> PlanarGraph s w v e f -> (VertexId s w, VertexId s w) Source #
endPoints d g = (tailOf d g, headOf d g)
running time: \(O(1)\)
incidentEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All edges incident to vertex v, in counterclockwise order around v.
running time: \(O(k)\), where \(k\) is the output size
incomingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All edges incident to vertex v in incoming direction (i.e. pointing into v) in counterclockwise order around v.
running time: \(O(k)\), where (k) is the total number of incident edges of v
outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All edges incident to vertex v in outgoing direction (i.e. pointing away from v) in counterclockwise order around v.
running time: \(O(k)\), where (k) is the total number of incident edges of v
neighboursOf :: VertexId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) Source #
Gets the neighbours of a particular vertex, in counterclockwise order around the vertex.
running time: \(O(k)\), where \(k\) is the output size
nextIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #
Given a dart d that points into some vertex v, report the next dart in the cyclic order around v.
running time: \(O(1)\)
prevIncidentEdge :: Dart s -> PlanarGraph s w v e f -> Dart s Source #
Given a dart d that points into some vertex v, report the next dart in the cyclic order around v.
running time: \(O(1)\)
Access data
class HasDataOf g i where Source #
dataOf :: i -> Lens' g (DataOf g i) Source #
get the data associated with the value i.
running time: \(O(1)\) to read the data, \(O(n)\) to write it.
Instances
HasDataOf (PlanarGraph s w v e f) (Dart s) Source # | |
Defined in Data.PlanarGraph.Core dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source # | |
HasDataOf (PlanarGraph s w v e f) (FaceId s w) Source # | |
Defined in Data.PlanarGraph.Core dataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (FaceId s w)) Source # | |
HasDataOf (PlanarGraph s w v e f) (VertexId s w) Source # | |
Defined in Data.PlanarGraph.Core dataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (VertexId s w)) Source # |
endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v) Source #
Data corresponding to the endpoints of the dart
endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v) Source #
Data corresponding to the endpoints of the dart
running time: \(O(1)\)
The Dual graph
computeDual :: forall s w v e f. PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v Source #
The dual of this graph
>>>
:{
let fromList = V.fromList answer = fromList [ fromList [dart 0 "-1"] , fromList [dart 2 "+1",dart 4 "+1",dart 1 "-1",dart 0 "+1"] , fromList [dart 1 "+1",dart 3 "-1",dart 2 "-1"] , fromList [dart 4 "-1",dart 3 "+1",dart 5 "+1",dart 5 "-1"] ] in (computeDual myGraph)^.embedding.orbits == answer :} True
running time: \(O(n)\).
computeDual' :: DualOf (DualOf w) ~ w => PlanarGraph s w v e f -> PlanarGraph s (DualOf w) f e v Source #
Does the actual work for dualGraph