Copyright | (C) David Himmelstrup |
---|---|
License | see the LICENSE file |
Maintainer | David Himmelstrup |
Safe Haskell | None |
Language | Haskell2010 |
A graph is planar if it can be drawn on a flat piece of paper without any crossing edges. More theory is explained on wikipedia: https://en.wikipedia.org/wiki/Planar_graph
This module describes the connectivity of planar graphs without knowing the 2D coordinates of each vertex. Algorithms that require the vertex positions (such as planar point locators or mesh smoothers) have to store that information somewhere else. Vertices are identified by dense, consecutive integers and can be efficiently used with arrays or finite maps.
A planar graph consists of directed edges (also called half-edges or darts), vertices, and faces. If a face lies on the outside of a set of vertices, this face is called a boundary.
The simplest planar graph has just three vertices and three edges:
pgFromFaces
[[0,1,2]]
The above pictures shows three vertices (named '0'
, '1'
, and '2'
), a single face
(named '0'
with an underscore), and 6 half-edges (named '0'
through '5'
).
Vertices, faces, and half-edges can be efficiently queried and traversed.
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
pgFaces pg
[Face 0]>>>
faceBoundary (Face 0) pg
[Vertex 1,Vertex 2,Vertex 0]
Planar graph examples:
Faces in planar graphs do not have to be triangular:
pgFromFaces
[[0,1,2,3]]
Vertices may be interior or lie on a boundary:
pgFromFaces
[[0,1,2,3],[4,3,2,1]]
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
pgFaces pg
[Face 0,Face 1]>>>
vertexIsBoundary (Vertex 0) pg
True>>>
vertexIsBoundary (Vertex 2) pg
False
Planar graphs may have multiple boundaries. Notice how the area between vertices
'1'
, '2'
and '3'
does not have a face ID:
pgFromFaces
[[0,4,1],[0,1,2],[4,3,1],[4,5,3],[3,5,2],[2,5,0]]
>>>
let pg = pgFromFaces [[0,4,1],[0,1,2],[4,3,1],[4,5,3],[3,5,2],[2,5,0]]
>>>
pgFaces pg
[Face 0,Face 1,Face 2,Face 3,Face 4,Face 5]>>>
pgBoundaries pg
[Boundary 0,Boundary 1]>>>
faceBoundary (Boundary 0) pg {- Outer boundary -}
[Vertex 0,Vertex 4,Vertex 5]>>>
faceBoundary (Boundary 1) pg {- Inner boundary -}
[Vertex 1,Vertex 2,Vertex 3]
Planar graphs may also have multiple unconnected components but they cannot be automatically rendered:
>>>
let pg = pgFromFaces [[0,1,2], [3,4,5]]
>>>
pgFaces pg
[Face 0,Face 1]>>>
pgBoundaries pg
[Boundary 0,Boundary 1]>>>
faceBoundary (Boundary 0) pg
[Vertex 0,Vertex 1,Vertex 2]>>>
faceBoundary (Boundary 1) pg
[Vertex 3,Vertex 4,Vertex 5]
Big-O Notation
When describing runtime complexity, n
refers to the size of the graph
(vertices, half-edges, faces, etcs). Some functions are output-sensitive
and use k
to indicate the amount of data consumed. For example,
vertexNeighbours
runs in \( O(k) \) and taking the first neighbour is therefore
an \( O(1) \) operation (because k=1).
Synopsis
- data PlanarGraph
- pgFromFaces :: [[VertexId]] -> PlanarGraph
- pgFromFacesCV :: [CircularVector VertexId] -> PlanarGraph
- pgVertices :: PlanarGraph -> [Vertex]
- pgEdges :: PlanarGraph -> [Edge]
- pgHalfEdges :: PlanarGraph -> [HalfEdge]
- pgFaces :: PlanarGraph -> [Face]
- pgBoundaries :: PlanarGraph -> [Face]
- newtype Vertex = Vertex {}
- vertexHalfEdge :: Vertex -> PlanarGraph -> HalfEdge
- vertexIsInterior :: Vertex -> PlanarGraph -> Bool
- vertexIsBoundary :: Vertex -> PlanarGraph -> Bool
- vertexOutgoingHalfEdges :: Vertex -> PlanarGraph -> [HalfEdge]
- vertexIncomingHalfEdges :: Vertex -> PlanarGraph -> [HalfEdge]
- vertexNeighbours :: Vertex -> PlanarGraph -> [Vertex]
- newtype Edge = Edge {}
- edgeHalfEdges :: Edge -> (HalfEdge, HalfEdge)
- newtype HalfEdge = HalfEdge {
- halfEdgeId :: Int
- halfEdgeNext :: HalfEdge -> PlanarGraph -> HalfEdge
- halfEdgePrev :: HalfEdge -> PlanarGraph -> HalfEdge
- halfEdgeTwin :: HalfEdge -> HalfEdge
- halfEdgeNextOutgoing :: HalfEdge -> PlanarGraph -> HalfEdge
- halfEdgeNextIncoming :: HalfEdge -> PlanarGraph -> HalfEdge
- halfEdgeVertex :: HalfEdge -> PlanarGraph -> Vertex
- halfEdgeTailVertex :: HalfEdge -> PlanarGraph -> Vertex
- halfEdgeTipVertex :: HalfEdge -> PlanarGraph -> Vertex
- halfEdgeFace :: HalfEdge -> PlanarGraph -> Face
- halfEdgeIsInterior :: HalfEdge -> PlanarGraph -> Bool
- halfEdgeIsBoundary :: HalfEdge -> PlanarGraph -> Bool
- data Face
- type FaceId = Int
- faceMember :: Face -> PlanarGraph -> Bool
- faceId :: Face -> FaceId
- faceHalfEdge :: Face -> PlanarGraph -> HalfEdge
- faceIsInterior :: Face -> Bool
- faceIsBoundary :: Face -> Bool
- faceHalfEdges :: Face -> PlanarGraph -> [HalfEdge]
- faceBoundary :: Face -> PlanarGraph -> [Vertex]
- pgMutate :: PlanarGraph -> (forall s. PlanarGraph s -> ST s ()) -> PlanarGraph
- pgCreate :: (forall s. ST s (PlanarGraph s)) -> PlanarGraph
- pgThaw :: PlanarGraph -> ST s (PlanarGraph s)
- pgFreeze :: PlanarGraph s -> ST s PlanarGraph
- pgUnsafeThaw :: PlanarGraph -> ST s (PlanarGraph s)
- pgUnsafeFreeze :: PlanarGraph s -> ST s PlanarGraph
- tutteEmbedding :: PlanarGraph -> Vector (V2 Double)
Planar graphs
data PlanarGraph Source #
Immutable planar graph.
Instances
Eq PlanarGraph Source # | |
Defined in Data.PlanarGraph.Immutable (==) :: PlanarGraph -> PlanarGraph -> Bool # (/=) :: PlanarGraph -> PlanarGraph -> Bool # | |
Hashable PlanarGraph Source # | |
Defined in Data.PlanarGraph.Immutable hashWithSalt :: Int -> PlanarGraph -> Int # hash :: PlanarGraph -> Int # |
pgFromFaces :: [[VertexId]] -> PlanarGraph Source #
\( O(n \log n) \)
Construct a planar graph from a list of faces. Vertices are assumed to be dense
(ie without gaps) but this only affects performance, not correctness. Memory
usage is defined by the largest vertex ID. That means
has the same connectivity as pgFromFaces
[[0,1,2]]
but uses three times less
memory.pgFromFaces
[[7,8,9]]
Examples:
Since: 0.12.0.0
pgFromFacesCV :: [CircularVector VertexId] -> PlanarGraph Source #
\( O(n \log n) \)
Construct a planar graph from a list of faces. This is a slightly more
efficient version of pgFromFacesCV
.
Since: 0.12.0.0
pgVertices :: PlanarGraph -> [Vertex] Source #
\( O(k) \)
List all vertices in a graph.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
pgVertices pg
[Vertex 0,Vertex 1,Vertex 2]
Since: 0.12.0.0
pgEdges :: PlanarGraph -> [Edge] Source #
\( O(k) \)
List all edges in a graph.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
pgEdges pg
[Edge 0,Edge 1,Edge 2]
>>>
map edgeHalfEdges $ pgEdges pg
[(HalfEdge 0,HalfEdge 1),(HalfEdge 2,HalfEdge 3),(HalfEdge 4,HalfEdge 5)]
Since: 0.12.0.0
pgHalfEdges :: PlanarGraph -> [HalfEdge] Source #
\( O(k) \)
List all half-edges in a graph.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
pgHalfEdges pg
[HalfEdge 0,HalfEdge 1,HalfEdge 2,HalfEdge 3,HalfEdge 4,HalfEdge 5]
Since: 0.12.0.0
pgFaces :: PlanarGraph -> [Face] Source #
\( O(k) \)
List all faces in a graph.
Examples:
>>>
let pg = pgFromFaces [[0,4,1],[0,1,2],[4,3,1],[4,5,3],[3,5,2],[2,5,0]]
>>>
pgFaces pg
[Face 0,Face 1,Face 2,Face 3,Face 4,Face 5]
Since: 0.12.0.0
pgBoundaries :: PlanarGraph -> [Face] Source #
\( O(k) \)
List all boundaries (ie external faces) in a graph. There may be multiple boundaries and they may or may not be reachable from each other.
Examples:
>>>
let pg = pgFromFaces [[0,4,1],[0,1,2],[4,3,1],[4,5,3],[3,5,2],[2,5,0]]
>>>
pgBoundaries pg
[Boundary 0,Boundary 1]
>>>
faceBoundary (Boundary 0) pg
[Vertex 0,Vertex 4,Vertex 5]
>>>
faceBoundary (Boundary 1) pg
[Vertex 1,Vertex 2,Vertex 3]
Since: 0.12.0.0
Elements
Vertices
Graph vertices. For best performance, make sure to use consecutive numbers.
vertexHalfEdge :: Vertex -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Each vertex has an assigned half-edge with the following properties:
halfEdgeVertex
(vertexHalfEdge
vertex pg) pg = vertex
faceIsInterior
(halfEdgeFace
(vertexHalfEdge
vertex pg) pg) = True
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
vertexHalfEdge (Vertex 0) pg
HalfEdge 4
>>>
vertexHalfEdge (Vertex 1) pg
HalfEdge 0
>>>
vertexHalfEdge (Vertex 6) pg
... Exception: Data.PlanarGraph.Immutable.vertexHalfEdge: Out-of-bounds vertex access: 6 ...
>>>
vertexHalfEdge (Vertex (-10)) pg
... Exception: Data.PlanarGraph.Immutable.vertexHalfEdge: Out-of-bounds vertex access: -10 ...
>>>
halfEdgeVertex (vertexHalfEdge (Vertex 2) pg) pg
Vertex 2
>>>
halfEdgeFace (vertexHalfEdge (Vertex 0) pg) pg
Face 0
Since: 0.12.0.0
vertexIsInterior :: Vertex -> PlanarGraph -> Bool Source #
\( O(1) \)
Returns True
iff the vertex is interior, ie. does not lie on a boundary.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
vertexIsInterior (Vertex 0) pg
False
>>>
vertexIsInterior (Vertex 2) pg
True
>>>
vertexIsInterior (Vertex 4) pg
False
>>>
vertexIsInterior (Vertex 12) pg
... Exception: Data.PlanarGraph.Immutable.vertexIsInterior: Out-of-bounds vertex access: 12 ...
Since: 0.12.0.0
vertexIsBoundary :: Vertex -> PlanarGraph -> Bool Source #
\( O(1) \)
Returns True
iff the vertex lies on a boundary.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
vertexIsBoundary (Vertex 0) pg
True
>>>
vertexIsBoundary (Vertex 2) pg
False
>>>
vertexIsBoundary (Vertex 4) pg
True
>>>
vertexIsBoundary (Vertex 12) pg
... Exception: Data.PlanarGraph.Immutable.vertexIsBoundary: Out-of-bounds vertex access: 12 ...
Since: 0.12.0.0
vertexOutgoingHalfEdges :: Vertex -> PlanarGraph -> [HalfEdge] Source #
\( O(k) \)
Query outgoing half-edges from a given vertex in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
vertexOutgoingHalfEdges (Vertex 1) pg
[HalfEdge 0,HalfEdge 11,HalfEdge 3]
Each half-edge will point out from the origin vertex:
>>>
map (`halfEdgeVertex` pg) $ vertexOutgoingHalfEdges (Vertex 1) pg
[Vertex 1,Vertex 1,Vertex 1]
>>>
map (`halfEdgeTipVertex` pg) $ vertexOutgoingHalfEdges (Vertex 1) pg
[Vertex 0,Vertex 4,Vertex 2]
>>>
vertexOutgoingHalfEdges (Vertex 2) pg
[HalfEdge 2,HalfEdge 5]
>>>
vertexOutgoingHalfEdges (Vertex 12) pg
... Exception: Data.PlanarGraph.Immutable.vertexOutgoingHalfEdges: Out-of-bounds vertex access: 12 ...
Since: 0.12.0.0
vertexIncomingHalfEdges :: Vertex -> PlanarGraph -> [HalfEdge] Source #
\( O(k) \)
Query incoming half-edges from a given vertex in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
vertexIncomingHalfEdges (Vertex 1) pg
[HalfEdge 1,HalfEdge 10,HalfEdge 2]
>>>
map (`halfEdgeVertex` pg) $ vertexIncomingHalfEdges (Vertex 1) pg
[Vertex 0,Vertex 4,Vertex 2]
>>>
map (`halfEdgeTipVertex` pg) $ vertexIncomingHalfEdges (Vertex 1) pg
[Vertex 1,Vertex 1,Vertex 1]
>>>
vertexIncomingHalfEdges (Vertex 2) pg
[HalfEdge 3,HalfEdge 4]
>>>
vertexIncomingHalfEdges (Vertex 12) pg
... Exception: Data.PlanarGraph.Immutable.vertexIncomingHalfEdges: Out-of-bounds vertex access: 12 ...
Since: 0.12.0.0
vertexNeighbours :: Vertex -> PlanarGraph -> [Vertex] Source #
\( O(k) \)
Query vertex neighbours in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
vertexNeighbours (Vertex 0) pg
[Vertex 3,Vertex 1]
>>>
vertexNeighbours (Vertex 1) pg
[Vertex 0,Vertex 4,Vertex 2]
>>>
vertexNeighbours (Vertex 2) pg
[Vertex 1,Vertex 3]
>>>
vertexNeighbours (Vertex 12) pg
... Exception: Data.PlanarGraph.Immutable.vertexNeighbours: Out-of-bounds vertex access: 12 ...
Since: 0.12.0.0
Edges
Edges are bidirectional and connect two vertices. No two edges are allowed to cross.
edgeHalfEdges :: Edge -> (HalfEdge, HalfEdge) Source #
\( O(1) \)
Split a bidirectional edge into directed half-edges.
Since: 0.12.0.0
Half-edges
Half-edges are directed edges between vertices. All Half-edge have a twin in the opposite direction. Half-edges have individual identity but are always created in pairs.
halfEdgeNext :: HalfEdge -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Query the half-edge in the pointed direction. Internal half-edges are arranged clockwise and external half-edges go counter-clockwise.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
halfEdgeNext (HalfEdge 4) pg {- clockwise -}
HalfEdge 2
>>>
halfEdgeNext (HalfEdge 3) pg {- clockwise -}
HalfEdge 5
>>>
halfEdgeNext (HalfEdge 1) pg {- counter-clockwise -}
HalfEdge 11
>>>
halfEdgeNext (HalfEdge 12) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeNext: Out-of-bounds half-edge access: 12 ...
Since: 0.12.0.0
halfEdgePrev :: HalfEdge -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Query the half-edge opposite the pointed direction. This means counter-clockwise for internal half-edges and clockwise for external half-edges.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
halfEdgePrev (HalfEdge 4) pg {- counter-clockwise -}
HalfEdge 6
>>>
halfEdgePrev (HalfEdge 3) pg {- counter-clockwise -}
HalfEdge 10
>>>
halfEdgePrev (HalfEdge 1) pg {- clockwise -}
HalfEdge 7
>>>
halfEdgePrev (HalfEdge 12) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgePrev: Out-of-bounds half-edge access: 12 ...
Since: 0.12.0.0
halfEdgeTwin :: HalfEdge -> HalfEdge Source #
halfEdgeNextOutgoing :: HalfEdge -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Next half-edge with the same vertex in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
HalfEdge 0
is poiting out from Vertex 1
. Moving counter-clockwise
around Vertex 1
yields HalfEdge 11
and HalfEdge 3
.
>>>
halfEdgeNextOutgoing (HalfEdge 0) pg
HalfEdge 11
>>>
halfEdgeNextOutgoing (HalfEdge 11) pg
HalfEdge 3
>>>
halfEdgeNextOutgoing (HalfEdge 3) pg
HalfEdge 0
>>>
halfEdgeNextOutgoing (HalfEdge 12) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeNextOutgoing: Out-of-bounds half-edge access: 12 ...
Since: 0.12.0.0
halfEdgeNextIncoming :: HalfEdge -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Next half-edge with the same vertex in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
HalfEdge 6
is poiting towards Vertex 3
. Moving clockwise
around Vertex 3
yields HalfEdge 11
and HalfEdge 3
.
>>>
halfEdgeNextIncoming (HalfEdge 6) pg
HalfEdge 5
>>>
halfEdgeNextIncoming (HalfEdge 5) pg
HalfEdge 9
>>>
halfEdgeNextIncoming (HalfEdge 9) pg
HalfEdge 6
>>>
halfEdgeNextIncoming (HalfEdge 12) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeNextIncoming: Out-of-bounds half-edge access: 12 ...
Since: 0.12.0.0
halfEdgeVertex :: HalfEdge -> PlanarGraph -> Vertex Source #
\( O(1) \)
Tail-end of a half-edge. Synonym of halfEdgeTailVertex
.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeVertex (HalfEdge 1) pg
Vertex 0
>>>
halfEdgeVertex (HalfEdge 2) pg
Vertex 2
>>>
halfEdgeVertex (HalfEdge 6) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeVertex: Out-of-bounds half-edge access: 6 ...
Since: 0.12.0.0
halfEdgeTailVertex :: HalfEdge -> PlanarGraph -> Vertex Source #
O(1)
Tail-end of a half-edge. Synonym of halfEdgeVertex
.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeTailVertex (HalfEdge 1) pg
Vertex 0
>>>
halfEdgeTailVertex (HalfEdge 2) pg
Vertex 2
Since: 0.12.0.0
halfEdgeTipVertex :: HalfEdge -> PlanarGraph -> Vertex Source #
O(1)
Tip-end of a half-edge. This is the tail-end vertex of the twin half-edge.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeTipVertex (HalfEdge 1) pg
Vertex 1
>>>
halfEdgeTipVertex (HalfEdge 5) pg
Vertex 0
Since: 0.12.0.0
halfEdgeFace :: HalfEdge -> PlanarGraph -> Face Source #
\( O(1) \)
Query the face of a half-edge.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeFace (HalfEdge 0) pg
Face 0
>>>
halfEdgeFace (HalfEdge 1) pg
Boundary 0
>>>
halfEdgeFace (HalfEdge 6) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeFace: Out-of-bounds half-edge access: 6 ...
Since: 0.12.0.0
halfEdgeIsInterior :: HalfEdge -> PlanarGraph -> Bool Source #
\( O(1) \)
Check if a half-edge's face is interior.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeIsInterior (HalfEdge 0) pg
True
>>>
halfEdgeIsInterior (HalfEdge 1) pg
False
>>>
halfEdgeIsInterior (HalfEdge 2) pg
True
>>>
halfEdgeIsInterior (HalfEdge 3) pg
False
>>>
halfEdgeIsInterior (HalfEdge 6) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeIsInterior: Out-of-bounds half-edge access: 6 ...
Since: 0.12.0.0
halfEdgeIsBoundary :: HalfEdge -> PlanarGraph -> Bool Source #
\( O(1) \)
Check if a half-edge's face is on a boundary.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
halfEdgeIsBoundary (HalfEdge 0) pg
False
>>>
halfEdgeIsBoundary (HalfEdge 1) pg
True
>>>
halfEdgeIsBoundary (HalfEdge 2) pg
False
>>>
halfEdgeIsBoundary (HalfEdge 3) pg
True
>>>
halfEdgeIsBoundary (HalfEdge 6) pg
... Exception: Data.PlanarGraph.Immutable.halfEdgeIsBoundary: Out-of-bounds half-edge access: 6 ...
Since: 0.12.0.0
Faces
Faces are the areas divided by edges. If a face is not surrounded by a set of vertices, it is called a boundary.
Numerical face identifier. Negative numbers indicate boundaries, non-negative numbers are internal faces.
faceMember :: Face -> PlanarGraph -> Bool Source #
\( O(1) \)
Returns True
iff a face or boundary is part of the planar graph.
Examples:
>>>
let pg = pgFromFaces [[0,1,2]]
>>>
faceMember (Face 0) pg
True
>>>
faceMember (Face 1) pg
False
>>>
faceMember (Face 100) pg
False
>>>
faceMember (Face (-100)) pg
False
>>>
faceMember (Boundary 0) pg
True
>>>
faceMember (Boundary 1) pg
False
Since: 0.12.0.0
faceId :: Face -> FaceId Source #
\( O(1) \)
Maps interior faces to positive integers and boundary faces to negative integers.
Examples:
>>>
faceId (Face 0)
0
>>>
faceId (Face 10)
10
>>>
faceId (Boundary 0)
-1
>>>
faceId (Boundary 10)
-11
Since: 0.12.0.0
faceHalfEdge :: Face -> PlanarGraph -> HalfEdge Source #
\( O(1) \)
Query the half-edge associated with a face or boundary.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
faceHalfEdge (Face 0) pg
HalfEdge 0
>>>
faceHalfEdge (Face 1) pg
HalfEdge 8
>>>
faceHalfEdge (Boundary 0) pg
HalfEdge 1
>>>
faceHalfEdge (Face 10) pg {- Invalid face -}
... Exception: Data.PlanarGraph.Immutable.faceHalfEdge: Out-of-bounds face access: 10 ...
Since: 0.12.0.0
faceIsInterior :: Face -> Bool Source #
\( O(1) \)
Returns True
iff a face is interior. Does not check if the face actually exists.
Examples:
>>>
faceIsInterior (Face 0)
True
>>>
faceIsInterior (Face 10000)
True
>>>
faceIsInterior (Boundary 0)
False
Since: 0.12.0.0
faceIsBoundary :: Face -> Bool Source #
\( O(1) \)
Returns True
iff a face is a boundary. Does not check if the face actually exists.
Examples:
>>>
faceIsBoundary (Face 0)
False
>>>
faceIsBoundary (Face 10000)
False
>>>
faceIsBoundary (Boundary 0)
True
Since: 0.12.0.0
faceHalfEdges :: Face -> PlanarGraph -> [HalfEdge] Source #
\( O(k) \)
Query the half-edges around a face in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
faceHalfEdges (Face 0) pg
[HalfEdge 0,HalfEdge 2,HalfEdge 4,HalfEdge 6]
>>>
faceHalfEdges (Face 1) pg
[HalfEdge 8,HalfEdge 5,HalfEdge 3,HalfEdge 10]
>>>
faceHalfEdges (Boundary 0) pg
[HalfEdge 1,HalfEdge 11,HalfEdge 9,HalfEdge 7]
>>>
faceHalfEdges (Face 10) pg
... Exception: Data.PlanarGraph.Immutable.faceHalfEdges: Out-of-bounds face access: 10 ...
Since: 0.12.0.0
faceBoundary :: Face -> PlanarGraph -> [Vertex] Source #
\( O(k) \)
Query the vertices of a face in counter-clockwise order.
Examples:
>>>
let pg = pgFromFaces [[0,1,2,3],[4,3,2,1]]
>>>
faceBoundary (Face 0) pg
[Vertex 1,Vertex 2,Vertex 3,Vertex 0]
>>>
faceBoundary (Face 1) pg
[Vertex 3,Vertex 2,Vertex 1,Vertex 4]
>>>
faceBoundary (Boundary 0) pg
[Vertex 0,Vertex 1,Vertex 4,Vertex 3]
>>>
faceBoundary (Face 10) pg
... Exception: Data.PlanarGraph.Immutable.faceBoundary: Out-of-bounds face access: 10 ...
Since: 0.12.0.0
Mutation
pgMutate :: PlanarGraph -> (forall s. PlanarGraph s -> ST s ()) -> PlanarGraph Source #
\( O(n) \)
Since: 0.12.0.0
pgCreate :: (forall s. ST s (PlanarGraph s)) -> PlanarGraph Source #
\( O(1) \)
Since: 0.12.0.0
pgThaw :: PlanarGraph -> ST s (PlanarGraph s) Source #
\( O(n) \)
Since: 0.12.0.0
pgFreeze :: PlanarGraph s -> ST s PlanarGraph Source #
\( O(n) \)
Since: 0.12.0.0
pgUnsafeThaw :: PlanarGraph -> ST s (PlanarGraph s) Source #
\( O(1) \)
Since: 0.12.0.0
pgUnsafeFreeze :: PlanarGraph s -> ST s PlanarGraph Source #
\( O(1) \)
Since: 0.12.0.0
Misc
tutteEmbedding :: PlanarGraph -> Vector (V2 Double) Source #
\( O(n^3) \)
Since: 0.12.0.0