hgeometry-0.5.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Data.PlanarGraph

Synopsis

Documentation

newtype Arc s Source

An Arc is a directed edge in a planar graph. The type s is used to tie this arc to a particular graph.

Constructors

Arc 

Fields

_unArc :: Int
 

Instances

Bounded (Arc k s) Source 
Enum (Arc k s) Source 
Eq (Arc k s) Source 
Ord (Arc k s) Source 
Show (Arc k s) Source 

rev :: Direction -> Direction Source

Reverse the direcion

data Dart s Source

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.

Constructors

Dart 

Fields

_arc :: !(Arc s)
 
_direction :: !Direction
 

Instances

Enum (Dart k s) Source 
Eq (Dart k s) Source 
Ord (Dart k s) Source 
Show (Dart k s) Source 

arc :: forall s s. Lens (Dart s) (Dart s) (Arc s) (Arc s) Source

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

data World Source

The world in which the graph lives

Constructors

Primal_ 
Dual_ 

type family Dual sp Source

newtype VertexId s w 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.

Constructors

VertexId 

Fields

_unVertexId :: Int
 

Instances

Enum (VertexId k s w) Source 
Eq (VertexId k s w) Source 
Ord (VertexId k s w) Source 
Show (VertexId k s w) Source 

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.

Instances

(Eq v, Eq e, Eq f) => Eq (PlanarGraph k s w v e f) Source 
(Show v, Show e, Show f) => Show (PlanarGraph k s w v e f) Source 

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 :: Permutation (Dart s) -> PlanarGraph s Primal_ () () () Source

Construct a planar graph

planarGraph' :: [[(Dart s, e)]] -> PlanarGraph s Primal_ () e () Source

Construct a planar graph.

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) Source

Enumerate all darts

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

faces :: PlanarGraph s w v e f -> Vector (FaceId s w, f) Source

All faces with their face data.

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

headOf :: Dart s -> PlanarGraph s w v e f -> VertexId s w Source

The vertex this dart is heading in to

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)

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.

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.

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!!

eDataOf :: Dart s -> Lens' (PlanarGraph s w v e f) e Source

Edge data of a given dart

fDataOf :: FaceId s w -> Lens' (PlanarGraph s w v e f) f Source

Data of a face of a given face

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

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

newtype FaceId s w Source

A face

Constructors

FaceId 

Fields

_unFaceId :: VertexId s (Dual w)
 

Instances

Eq (FaceId k s w) Source 
Ord (FaceId k s w) Source 
Show (FaceId k s w) Source 

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

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

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.