| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.PlanarGraph.Mutable
Synopsis
- data PlanarGraph s
 - pgFromFaces :: [[VertexId]] -> ST s (PlanarGraph s)
 - pgFromFacesCV :: [CircularVector VertexId] -> ST s (PlanarGraph s)
 - pgClone :: PlanarGraph s -> ST s (PlanarGraph s)
 - pgHash :: PlanarGraph s -> ST s Int
 - data Vertex s
 - type VertexId = Int
 - vertexFromId :: VertexId -> PlanarGraph s -> Vertex s
 - vertexToId :: Vertex s -> VertexId
 - vertexHalfEdge :: Vertex s -> ST s (HalfEdge s)
 - vertexIsBoundary :: Vertex s -> ST s Bool
 - vertexOutgoingHalfEdges :: Vertex s -> ST s (CircularVector (HalfEdge s))
 - vertexWithOutgoingHalfEdges :: Vertex s -> (HalfEdge s -> ST s ()) -> ST s ()
 - vertexIncomingHalfEdges :: Vertex s -> ST s (CircularVector (HalfEdge s))
 - vertexWithIncomingHalfEdges :: Vertex s -> (HalfEdge s -> ST s ()) -> ST s ()
 - vertexNeighbours :: Vertex s -> ST s (CircularVector (Vertex s))
 - data Edge s
 - type EdgeId = Int
 - edgeFromId :: EdgeId -> PlanarGraph s -> Edge s
 - edgeToId :: Edge s -> EdgeId
 - edgeFromHalfEdge :: HalfEdge s -> Edge s
 - data HalfEdge s
 - type HalfEdgeId = Int
 - halfEdgeFromId :: HalfEdgeId -> PlanarGraph s -> HalfEdge s
 - halfEdgeToId :: HalfEdge s -> HalfEdgeId
 - halfEdgeNext :: HalfEdge s -> ST s (HalfEdge s)
 - halfEdgePrev :: HalfEdge s -> ST s (HalfEdge s)
 - halfEdgeNextOutgoing :: HalfEdge s -> ST s (HalfEdge s)
 - halfEdgeNextIncoming :: HalfEdge s -> ST s (HalfEdge s)
 - halfEdgeVertex :: HalfEdge s -> ST s (Vertex s)
 - halfEdgeTwin :: HalfEdge s -> HalfEdge s
 - halfEdgeTailVertex :: HalfEdge s -> ST s (Vertex s)
 - halfEdgeTipVertex :: HalfEdge s -> ST s (Vertex s)
 - halfEdgeFace :: HalfEdge s -> ST s (Face s)
 - halfEdgeIsInterior :: HalfEdge s -> ST s Bool
 - data Face s
 - type FaceId = Int
 - faceInvalid :: PlanarGraph s -> Face s
 - faceIsValid :: Face s -> Bool
 - faceIsInvalid :: Face s -> Bool
 - faceFromId :: FaceId -> PlanarGraph s -> Face s
 - faceToId :: Face s -> FaceId
 - faceHalfEdge :: Face s -> ST s (HalfEdge s)
 - faceIsInterior :: Face s -> Bool
 - faceIsBoundary :: Face s -> Bool
 - faceHalfEdges :: Face s -> ST s (CircularVector (HalfEdge s))
 - faceBoundary :: Face s -> ST s (CircularVector (Vertex s))
 - pgConnectVertices :: HalfEdge s -> HalfEdge s -> ST s (Edge s)
 
Planar graphs
data PlanarGraph s Source #
Instances
| Eq (PlanarGraph s) Source # | |
Defined in Data.PlanarGraph.Internal Methods (==) :: PlanarGraph s -> PlanarGraph s -> Bool # (/=) :: PlanarGraph s -> PlanarGraph s -> Bool #  | |
pgFromFaces :: [[VertexId]] -> ST s (PlanarGraph s) Source #
pgFromFacesCV :: [CircularVector VertexId] -> ST s (PlanarGraph s) Source #
pgClone :: PlanarGraph s -> ST s (PlanarGraph s) Source #
\( O(n) \)
Elements
Vertices
vertexFromId :: VertexId -> PlanarGraph s -> Vertex s Source #
\( O(1) \)
vertexToId :: Vertex s -> VertexId Source #
\( O(1) \)
vertexOutgoingHalfEdges :: Vertex s -> ST s (CircularVector (HalfEdge s)) Source #
O(k)
vertexWithOutgoingHalfEdges :: Vertex s -> (HalfEdge s -> ST s ()) -> ST s () Source #
O(k), more efficient than vertexOutgoingHalfEdges.
vertexIncomingHalfEdges :: Vertex s -> ST s (CircularVector (HalfEdge s)) Source #
O(k)
vertexNeighbours :: Vertex s -> ST s (CircularVector (Vertex s)) Source #
O(k)
Edges
edgeFromId :: EdgeId -> PlanarGraph s -> Edge s Source #
O(1)
edgeFromHalfEdge :: HalfEdge s -> Edge s Source #
O(1)
Half-edges
type HalfEdgeId = Int Source #
halfEdgeFromId :: HalfEdgeId -> PlanarGraph s -> HalfEdge s Source #
O(1)
halfEdgeToId :: HalfEdge s -> HalfEdgeId Source #
O(1)
halfEdgeNextOutgoing :: HalfEdge s -> ST s (HalfEdge s) Source #
O(1) Next half-edge with the same vertex.
halfEdgeNextIncoming :: HalfEdge s -> ST s (HalfEdge s) Source #
O(1) Next half-edge with the same vertex.
halfEdgeTwin :: HalfEdge s -> HalfEdge s Source #
O(1)
halfEdgeTailVertex :: HalfEdge s -> ST s (Vertex s) Source #
O(1) Tail vertex. IE. the vertex of the twin edge.
halfEdgeTipVertex :: HalfEdge s -> ST s (Vertex s) Source #
O(1)
   Synonym of halfEdgeVertex.
halfEdgeFace :: HalfEdge s -> ST s (Face s) Source #
\( O(1) \)
Examples:
pgFromFaces [[0,1,2]]
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; show <$> halfEdgeFace (halfEdgeFromId 0 pg)"Face 0"
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; show <$> halfEdgeFace (halfEdgeFromId 1 pg)"Boundary 0"
halfEdgeIsInterior :: HalfEdge s -> ST s Bool Source #
\( O(1) \) Check if a half-edge's face is interior or exterior.
Examples:
pgFromFaces [[0,1,2]]
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; halfEdgeIsInterior (halfEdgeFromId 0 pg)True
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; halfEdgeIsInterior (halfEdgeFromId 1 pg)False
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; halfEdgeIsInterior (halfEdgeFromId 2 pg)True
>>>runST $ do pg <- pgFromFaces [[0,1,2]]; halfEdgeIsInterior (halfEdgeFromId 3 pg)False
Faces
Instances
Numerical face identifier. Negative numbers indicate boundaries, non-negative numbers are internal faces.
faceInvalid :: PlanarGraph s -> Face s Source #
O(1)
faceIsValid :: Face s -> Bool Source #
O(1)
faceIsInvalid :: Face s -> Bool Source #
O(1)
faceFromId :: FaceId -> PlanarGraph s -> Face s Source #
O(1)
faceIsInterior :: Face s -> Bool Source #
O(1)
faceIsBoundary :: Face s -> Bool Source #
O(1)
faceHalfEdges :: Face s -> ST s (CircularVector (HalfEdge s)) Source #
O(k) Counterclockwise vector of edges.
faceBoundary :: Face s -> ST s (CircularVector (Vertex s)) Source #
O(k)
Mutation
pgConnectVertices :: HalfEdge s -> HalfEdge s -> ST s (Edge s) Source #
O(k) where k is the number of edges in new face.
The two half-edges must be different, must have the same face, and may not be consecutive. The first half-edge will stay in the original face. The second half-edge will be in the newly created face.
Examples:
pgFromFaces [[0,1,2,3]]
do pg <-pgFromFaces[[0,1,2,3]] let he0 =halfEdgeFromId0 pg' he4 =halfEdgeFromId4 pg'pgConnectVerticeshe0 he4