Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype Arc s = Arc {}
- data Direction
- rev :: Direction -> Direction
- data Dart s = Dart {
- _arc :: !(Arc s)
- _direction :: !Direction
- arc :: forall s s. Lens (Dart s) (Dart s) (Arc s) (Arc s)
- direction :: forall s. Lens' (Dart s) Direction
- twin :: Dart s -> Dart s
- isPositive :: Dart s -> Bool
- data World
- type family Dual (sp :: World) where ...
- newtype VertexId s w = VertexId {
- _unVertexId :: Int
- data PlanarGraph s w v e f
- embedding :: forall s w v e f s w. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Permutation (Dart s)) (Permutation (Dart s))
- vertexData :: forall s w v e f w v. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Vector v) (Vector v)
- dartData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- faceData :: forall s w v e f w f. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Vector f) (Vector f)
- edgeData :: Lens (PlanarGraph s w v e f) (PlanarGraph s w v e' f) (Vector (Dart s, e)) (Vector (Dart s, e'))
- planarGraph :: [[(Dart s, e)]] -> PlanarGraph s Primal_ () e ()
- planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () ()
- fromAdjacencyLists :: forall s w f. (Foldable f, Functor f) => [(VertexId s w, f (VertexId s w))] -> PlanarGraph 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
- 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)
- vertices' :: PlanarGraph s w v e f -> Vector (VertexId s w)
- vertices :: PlanarGraph s w v e f -> Vector (VertexId s w, v)
- faces' :: PlanarGraph s w v e f -> Vector (FaceId s w)
- faces :: PlanarGraph s w v e f -> Vector (FaceId s w, f)
- 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)
- vDataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) v
- eDataOf :: Dart s -> Lens' (PlanarGraph s w v e f) e
- fDataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) f
- endPointDataOf :: Dart s -> Getter (PlanarGraph s w v e f) (v, v)
- endPointData :: Dart s -> PlanarGraph s w v e f -> (v, v)
- dual :: PlanarGraph s w v e f -> PlanarGraph s (Dual w) f e v
- newtype FaceId s w = FaceId {}
- leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
- rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w
- boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s)
- boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w)
- data EdgeOracle s w a
- edgeOracle :: PlanarGraph s w v e f -> EdgeOracle s w ()
- buildEdgeOracle :: forall f s w e. Foldable f => [(VertexId s w, f (VertexId s w :+ e))] -> EdgeOracle s w e
- findEdge :: VertexId s w -> VertexId s w -> EdgeOracle s w a -> Maybe a
- hasEdge :: VertexId s w -> VertexId s w -> EdgeOracle s w a -> Bool
Documentation
An Arc is a directed edge in a planar graph. The type s is used to tie this arc to a particular graph.
A dart represents a bi-directed edge. I.e. a dart has a direction, however the dart of the oposite direction is always present in the planar graph as well.
Dart | |
|
twin :: Dart s -> Dart s Source #
Get the twin of this dart (edge)
>>>
twin (dart 0 "+1")
Dart (Arc 0) -1>>>
twin (dart 0 "-1")
Dart (Arc 0) +1
isPositive :: Dart s -> Bool Source #
test if a dart is Positive
The world in which the graph lives
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.
data PlanarGraph s w 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.
embedding :: forall s w v e f s w. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Permutation (Dart s)) (Permutation (Dart s)) Source #
vertexData :: forall s w v e f w v. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Vector v) (Vector v) Source #
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
faceData :: forall s w v e f w f. Lens (PlanarGraph s w v e f) (PlanarGraph s w v e f) (Vector f) (Vector f) Source #
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
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)\).
planarGraph' :: Permutation (Dart s) -> PlanarGraph s w () () () Source #
Construct a planar graph
fromAdjacencyLists :: forall s w f. (Foldable f, Functor f) => [(VertexId s w, f (VertexId s w))] -> PlanarGraph s w () () () Source #
Construct a planar graph from a adjacency matrix. For every vertex, all vertices should be given in counter clockwise order.
running time: \(O(n)\).
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
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+")
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
faces' :: PlanarGraph s w v e f -> Vector (FaceId s w) Source #
Enumerate all faces in the planar graph
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 incoming edges incident to vertex v, in counterclockwise order around v.
outgoingEdges :: VertexId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
All outgoing edges incident to vertex v, in counterclockwise order around 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
vDataOf :: VertexId s w -> Lens' (PlanarGraph s w v e f) v Source #
Get the vertex data associated with a node. Note that updating this data may be expensive!!
running time: \(O(1)\)
eDataOf :: Dart s -> Lens' (PlanarGraph s w v e f) e Source #
Edge data of a given dart
running time: \(O(1)\)
fDataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) f Source #
Data of a face of a given face
running time: \(O(1)\)
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)\)
dual :: PlanarGraph s w v e f -> PlanarGraph s (Dual 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 (dual myGraph)^.embedding.orbits == answer :} True
running time: \(O(n)\).
A face
leftFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #
The face to the left of the dart
>>>
leftFace (dart 1 "+1") myGraph
FaceId 1>>>
leftFace (dart 1 "-1") myGraph
FaceId 2>>>
leftFace (dart 2 "+1") myGraph
FaceId 2>>>
leftFace (dart 0 "+1") myGraph
FaceId 0
running time: \(O(1)\).
rightFace :: Dart s -> PlanarGraph s w v e f -> FaceId s w Source #
The face to the right of the dart
>>>
rightFace (dart 1 "+1") myGraph
FaceId 2>>>
rightFace (dart 1 "-1") myGraph
FaceId 1>>>
rightFace (dart 2 "+1") myGraph
FaceId 1>>>
rightFace (dart 0 "+1") myGraph
FaceId 1
running time: \(O(1)\).
boundary :: FaceId s w -> PlanarGraph s w v e f -> Vector (Dart s) Source #
The darts bounding this face, for internal faces in clockwise order, for the outer face in counter clockwise order.
running time: \(O(k)\), where \(k\) is the output size.
boundaryVertices :: FaceId s w -> PlanarGraph s w v e f -> Vector (VertexId s w) Source #
The vertices bounding this face, for internal faces in clockwise order, for the outer face in counter clockwise order.
running time: \(O(k)\), where \(k\) is the output size.
data EdgeOracle s w a Source #
Edge Oracle:
main idea: store adjacency lists in such a way that we store an edge (u,v) either in u's adjacency list or in v's. This can be done s.t. all adjacency lists have length at most 6.
note: Every edge is stored exactly once (i.e. either at u or at v, but not both)
Functor (EdgeOracle k s w) Source # | |
Foldable (EdgeOracle k s w) Source # | |
Traversable (EdgeOracle k s w) Source # | |
Eq a => Eq (EdgeOracle k s w a) Source # | |
Show a => Show (EdgeOracle k s w a) Source # | |
edgeOracle :: PlanarGraph s w v e f -> EdgeOracle s w () Source #
buildEdgeOracle :: forall f s w e. Foldable f => [(VertexId s w, f (VertexId s w :+ e))] -> EdgeOracle s w e Source #
Builds an edge oracle that can be used to efficiently test if two vertices are connected by an edge.
running time: \(O(n)\)