Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type VertexId' s = VertexId s Primal
- type FaceId' s = FaceId s Primal
- data VertexData r v = VertexData !(Point 2 r) !v
- vData :: forall r v v. Lens (VertexData r v) (VertexData r v) v v
- location :: forall r v r. Lens (VertexData r v) (VertexData r v) (Point 2 r) (Point 2 r)
- data FaceData h f = FaceData (Seq h) !f
- holes :: forall h f h. Lens (FaceData h f) (FaceData h f) (Seq h) (Seq h)
- fData :: forall h f f. Lens (FaceData h f) (FaceData h f) f f
- data PlanarSubdivision s v e f r = PlanarSubdivision (Vector (Component s r)) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (FaceId' (Wrap s)) f))
- type family Wrap (s :: k) :: k where ...
- type Component s r = PlaneGraph (Wrap s) (VertexId' s) (Dart s) (FaceData (Dart s) (FaceId' s)) r
- data ComponentId s
- data PolygonFaceData
- data PlanarGraph s (w :: World) v e f
- data PlaneGraph s v e f r
- fromSimplePolygon :: (Ord r, Fractional r) => proxy s -> SimplePolygon p r -> f -> f -> PlanarSubdivision s p () f r
- fromConnectedSegments :: (Foldable f, Ord r, Fractional r) => proxy s -> f (LineSegment 2 p r :+ e) -> PlanarSubdivision s (NonEmpty p) e () r
- fromPlaneGraph :: forall s v e f r. (Ord r, Fractional r) => PlaneGraph s v e f r -> PlanarSubdivision s v e f r
- fromPlaneGraph' :: forall s v e f r. PlaneGraph s v e f r -> Dart s -> PlanarSubdivision s v e f r
- numVertices :: PlanarSubdivision s v e f r -> Int
- numEdges :: PlanarSubdivision s v e f r -> Int
- numFaces :: PlanarSubdivision s v e f r -> Int
- numDarts :: PlanarSubdivision s v e f r -> Int
- dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v)
- components :: forall s v e f r r. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Component s r)) (Vector (Component s r))
- component :: ComponentId s -> Lens' (PlanarSubdivision s v e f r) (Component s r)
- vertices' :: PlanarSubdivision s v e f r -> Vector (VertexId' s)
- vertices :: PlanarSubdivision s v e f r -> Vector (VertexId' s, VertexData r v)
- edges' :: PlanarSubdivision s v e f r -> Vector (Dart s)
- edges :: PlanarSubdivision s v e f r -> Vector (Dart s, e)
- faces' :: PlanarSubdivision s v e f r -> Vector (FaceId' s)
- faces :: PlanarSubdivision s v e f r -> Vector (FaceId' s, FaceData (Dart s) f)
- internalFaces :: (Ord r, Fractional r) => PlanarSubdivision s v e f r -> Vector (FaceId' s, FaceData (Dart s) f)
- darts' :: PlanarSubdivision s v e f r -> Vector (Dart s)
- headOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s
- tailOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s
- twin :: Dart s -> Dart s
- endPoints :: Dart s -> PlanarSubdivision s v e f r -> (VertexId' s, VertexId' s)
- incidentEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s)
- incomingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s)
- outgoingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s)
- nextIncidentEdge :: Dart s -> PlanarSubdivision s v e f r -> Dart s
- neighboursOf :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (VertexId' s)
- leftFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s
- rightFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s
- outerBoundaryDarts :: FaceId' s -> PlanarSubdivision s v e f r -> Vector (Dart s)
- boundaryVertices :: FaceId' s -> PlanarSubdivision s v e f r -> Vector (VertexId' s)
- holesOf :: FaceId' s -> PlanarSubdivision s v e f r -> Seq (Dart s)
- outerFaceId :: PlanarSubdivision s v e f r -> FaceId' s
- boundary' :: Dart s -> PlanarSubdivision s v e f r -> Vector (Dart s)
- locationOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (Point 2 r)
- class HasDataOf g i where
- type DataOf g i
- endPointsOf :: Dart s -> Getter (PlanarSubdivision s v e f r) (VertexData r v, VertexData r v)
- endPointData :: Dart s -> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v)
- edgeSegment :: Dart s -> PlanarSubdivision s v e f r -> LineSegment 2 v r :+ e
- edgeSegments :: PlanarSubdivision s v e f r -> Vector (Dart s, LineSegment 2 v r :+ e)
- rawFacePolygon :: FaceId' s -> PlanarSubdivision s v e f r -> SomePolygon v r :+ f
- rawFaceBoundary :: FaceId' s -> PlanarSubdivision s v e f r -> SimplePolygon v r :+ f
- rawFacePolygons :: PlanarSubdivision s v e f r -> Vector (FaceId' s, SomePolygon v r :+ f)
- newtype VertexId s (w :: World) = VertexId {
- _unVertexId :: Int
- newtype FaceId s w = FaceId {}
- data Dart s
- data World
- rawVertexData :: forall s v e f r v. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (VertexId' (Wrap s)) v))
- rawDartData :: forall s v e f r e. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (Dart (Wrap s)) e))
- rawFaceData :: forall s v e f r f. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (FaceId' (Wrap s)) f)) (Vector (Raw s (FaceId' (Wrap s)) f))
- dataVal :: forall s ia a a. Lens (Raw s ia a) (Raw s ia a) a a
- dartMapping :: PlanarSubdivision s v e f r -> Vector (Dart (Wrap s), Dart s)
- data Raw s ia a = Raw {
- _compId :: !(ComponentId s)
- _idxVal :: !ia
- _dataVal :: !a
Documentation
data VertexData r v Source #
Note that the functor instance is in v
VertexData !(Point 2 r) !v |
Instances
vData :: forall r v v. Lens (VertexData r v) (VertexData r v) v v Source #
location :: forall r v r. Lens (VertexData r v) (VertexData r v) (Point 2 r) (Point 2 r) Source #
The Face data consists of the data itself and a list of holes
Instances
data PlanarSubdivision s v e f r Source #
A planarsubdivision is essentially a bunch of plane-graphs; one for every connected component. These graphs store the global ID's (darts, vertexId's, faceId's) in their data values. This essentially gives us a mapping between the two.
note that a face may actually occur in multiple graphs, hence when we store
the edges to the the holes, we store the global edgeId's rather than the
local
edgeId (dart)'s.
invariant: the outerface has faceId 0
PlanarSubdivision (Vector (Component s r)) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (FaceId' (Wrap s)) f)) |
Instances
type Component s r = PlaneGraph (Wrap s) (VertexId' s) (Dart s) (FaceData (Dart s) (FaceId' s)) r Source #
A connected component.
For every face f, and every hole in this face, the facedata points to a dart d on the hole s.t. this dart has the face f on its left. i.e. leftFace d = f
data ComponentId s Source #
Instances
data PolygonFaceData Source #
Data type that expresses whether or not we are inside or outside the polygon.
Instances
Eq PolygonFaceData Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic (==) :: PolygonFaceData -> PolygonFaceData -> Bool # (/=) :: PolygonFaceData -> PolygonFaceData -> Bool # | |
Read PolygonFaceData Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic | |
Show PolygonFaceData Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic showsPrec :: Int -> PolygonFaceData -> ShowS # show :: PolygonFaceData -> String # showList :: [PolygonFaceData] -> ShowS # |
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.
Instances
data PlaneGraph s v e f r Source #
Embedded, *connected*, planar graph
Instances
:: (Ord r, Fractional r) | |
=> proxy s | |
-> SimplePolygon p r | |
-> f | data inside |
-> f | data outside the polygon |
-> PlanarSubdivision s p () f r |
Construct a planar subdivision from a simple polygon
running time: \(O(n)\).
fromConnectedSegments :: (Foldable f, Ord r, Fractional r) => proxy s -> f (LineSegment 2 p r :+ e) -> PlanarSubdivision s (NonEmpty p) e () r Source #
Constructs a connected planar subdivision.
pre: the segments form a single connected component running time: \(O(n\log n)\)
fromPlaneGraph :: forall s v e f r. (Ord r, Fractional r) => PlaneGraph s v e f r -> PlanarSubdivision s v e f r Source #
Constructs a planarsubdivision from a PlaneGraph
runningTime: \(O(n)\)
fromPlaneGraph' :: forall s v e f r. PlaneGraph s v e f r -> Dart s -> PlanarSubdivision s v e f r Source #
Given a (connected) PlaneGraph and a dart that has the outerface on its left | Constructs a planarsubdivision
runningTime: \(O(n)\)
numVertices :: PlanarSubdivision s v e f r -> Int Source #
Get the number of vertices
>>>
numVertices myGraph
4
numEdges :: PlanarSubdivision s v e f r -> Int Source #
Get the number of Edges
>>>
numEdges myGraph
6
numFaces :: PlanarSubdivision s v e f r -> Int Source #
Get the number of faces
>>>
numFaces myGraph
4
numDarts :: PlanarSubdivision s v e f r -> Int Source #
Get the number of Darts
>>>
numDarts myGraph
12
dual :: Getter (PlanarGraph s w v e f) (PlanarGraph s (DualOf w) f e v) Source #
components :: forall s v e f r r. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Component s r)) (Vector (Component s r)) Source #
component :: ComponentId s -> Lens' (PlanarSubdivision s v e f r) (Component s r) Source #
vertices' :: PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #
Enumerate all vertices
>>>
vertices' myGraph
[VertexId 0,VertexId 1,VertexId 2,VertexId 3]
vertices :: PlanarSubdivision s v e f r -> Vector (VertexId' s, VertexData r v) Source #
Enumerate all vertices, together with their vertex data
edges' :: PlanarSubdivision s v e f r -> Vector (Dart s) Source #
Enumerate all edges. We report only the Positive darts
edges :: PlanarSubdivision s v e f r -> 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+")
internalFaces :: (Ord r, Fractional r) => PlanarSubdivision s v e f r -> Vector (FaceId' s, FaceData (Dart s) f) Source #
Enumerates all faces with their face data exlcluding the outer face
headOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s Source #
The vertex this dart is heading in to
running time: \(O(1)\)
tailOf :: Dart s -> PlanarSubdivision s v e f r -> VertexId' s Source #
The tail of a dart, i.e. the vertex this dart is leaving from
running time: \(O(1)\)
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
endPoints :: Dart s -> PlanarSubdivision s v e f r -> (VertexId' s, VertexId' s) Source #
endPoints d g = (tailOf d g, headOf d g)
running time: \(O(1)\)
incidentEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #
All edges incident to vertex v, in counterclockwise order around v.
running time: \(O(k)\), where \(k\) is the number of edges reported.
incomingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #
All incoming edges incident to vertex v, in counterclockwise order around v.
outgoingEdges :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #
All outgoing edges incident to vertex v, in counterclockwise order around v.
nextIncidentEdge :: Dart s -> PlanarSubdivision s v e f r -> Dart s Source #
Given a dart d that points into some vertex v, report the next dart e in the cyclic order around v.
running time: \(O(1)\)
neighboursOf :: VertexId' s -> PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #
Gets the neighbours of a particular vertex, in counterclockwise order around the vertex.
running time: \(O(k)\), where \(k\) is the output size
leftFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s Source #
The face to the left of the dart
running time: \(O(1)\).
rightFace :: Dart s -> PlanarSubdivision s v e f r -> FaceId' s Source #
The face to the right of the dart
running time: \(O(1)\).
outerBoundaryDarts :: FaceId' s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #
The darts on the outer boundary of the 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 -> PlanarSubdivision s v e f r -> Vector (VertexId' s) Source #
The vertices of the outer boundary of the 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.
holesOf :: FaceId' s -> PlanarSubdivision s v e f r -> Seq (Dart s) Source #
Lists the holes in this face, given as a list of darts to arbitrary darts on those faces.
running time: \(O(k)\), where \(k\) is the number of darts returned.
outerFaceId :: PlanarSubdivision s v e f r -> FaceId' s Source #
gets the id of the outer face
running time: \(O(1)\)
boundary' :: Dart s -> PlanarSubdivision s v e f r -> Vector (Dart s) Source #
Generates the darts incident to a face, starting with the given dart.
\(O(k)\), where \(k\) is the number of darts reported
locationOf :: VertexId' s -> Lens' (PlanarSubdivision s v e f r) (Point 2 r) Source #
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
endPointsOf :: Dart s -> Getter (PlanarSubdivision s v e f r) (VertexData r v, VertexData r v) Source #
Getter for the data at the endpoints of a dart
running time: \(O(1)\)
endPointData :: Dart s -> PlanarSubdivision s v e f r -> (VertexData r v, VertexData r v) Source #
data corresponding to the endpoints of the dart
running time: \(O(1)\)
edgeSegment :: Dart s -> PlanarSubdivision s v e f r -> LineSegment 2 v r :+ e Source #
Given a dart and the subdivision constructs the line segment representing it
\(O(1)\)
edgeSegments :: PlanarSubdivision s v e f r -> Vector (Dart s, LineSegment 2 v r :+ e) Source #
Reports all edges as line segments
rawFacePolygon :: FaceId' s -> PlanarSubdivision s v e f r -> SomePolygon v r :+ f Source #
Constructs the boundary of the given face
\(O(k)\), where \(k\) is the complexity of the face
rawFaceBoundary :: FaceId' s -> PlanarSubdivision s v e f r -> SimplePolygon v r :+ f Source #
Constructs the outer boundary of the face
\(O(k)\), where \(k\) is the complexity of the outer boundary of the face
rawFacePolygons :: PlanarSubdivision s v e f r -> Vector (FaceId' s, SomePolygon v r :+ f) Source #
Lists all faces of the planar subdivision.
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
A face
Instances
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.
Instances
Enum (Dart s) Source # | |
Defined in Data.PlanarGraph | |
Eq (Dart s) Source # | |
Ord (Dart s) Source # | |
Show (Dart s) Source # | |
HasDataOf (PlanarGraph s w v e f) (Dart s) Source # | |
Defined in Data.PlanarGraph dataOf :: Dart s -> Lens' (PlanarGraph s w v e f) (DataOf (PlanarGraph s w v e f) (Dart s)) Source # | |
HasDataOf (PlaneGraph s v e f r) (Dart s) Source # | |
Defined in Data.PlaneGraph dataOf :: Dart s -> Lens' (PlaneGraph s v e f r) (DataOf (PlaneGraph s v e f r) (Dart s)) Source # | |
HasDataOf (PlanarSubdivision s v e f r) (Dart s) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic dataOf :: Dart s -> Lens' (PlanarSubdivision s v e f r) (DataOf (PlanarSubdivision s v e f r) (Dart s)) Source # | |
type DataOf (PlanarGraph s w v e f) (Dart s) Source # | |
Defined in Data.PlanarGraph | |
type DataOf (PlaneGraph s v e f r) (Dart s) Source # | |
Defined in Data.PlaneGraph | |
type DataOf (PlanarSubdivision s v e f r) (Dart s) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic |
The world in which the graph lives
rawVertexData :: forall s v e f r v. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (VertexId' (Wrap s)) v)) (Vector (Raw s (VertexId' (Wrap s)) v)) Source #
rawDartData :: forall s v e f r e. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (Dart (Wrap s)) e)) (Vector (Raw s (Dart (Wrap s)) e)) Source #
rawFaceData :: forall s v e f r f. Lens (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (Vector (Raw s (FaceId' (Wrap s)) f)) (Vector (Raw s (FaceId' (Wrap s)) f)) Source #
dartMapping :: PlanarSubdivision s v e f r -> Vector (Dart (Wrap s), Dart s) Source #
Raw | |
|
Instances
Functor (Raw s ia) Source # | |
Foldable (Raw s ia) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic fold :: Monoid m => Raw s ia m -> m # foldMap :: Monoid m => (a -> m) -> Raw s ia a -> m # foldr :: (a -> b -> b) -> b -> Raw s ia a -> b # foldr' :: (a -> b -> b) -> b -> Raw s ia a -> b # foldl :: (b -> a -> b) -> b -> Raw s ia a -> b # foldl' :: (b -> a -> b) -> b -> Raw s ia a -> b # foldr1 :: (a -> a -> a) -> Raw s ia a -> a # foldl1 :: (a -> a -> a) -> Raw s ia a -> a # elem :: Eq a => a -> Raw s ia a -> Bool # maximum :: Ord a => Raw s ia a -> a # minimum :: Ord a => Raw s ia a -> a # | |
Traversable (Raw s ia) Source # | |
Defined in Data.Geometry.PlanarSubdivision.Basic | |
(Eq ia, Eq a) => Eq (Raw s ia a) Source # | |
(Show ia, Show a) => Show (Raw s ia a) Source # | |