Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data VertexData r v = VertexData {}
- 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 EdgeType
- data EdgeData e = EdgeData {}
- edgeType :: forall e. Lens' (EdgeData e) EdgeType
- eData :: forall e e. Lens (EdgeData e) (EdgeData e) e e
- data FaceData h f = FaceData {}
- holes :: forall h f h. Lens (FaceData h f) (FaceData h f) [h] [h]
- fData :: forall h f f. Lens (FaceData h f) (FaceData h f) f f
- newtype PlanarSubdivision s v e f r = PlanarSubdivision {
- _graph :: PlanarGraph s Primal_ (VertexData r v) (EdgeData e) (FaceData (Dart s) f)
- graph :: forall s v e f r s v e f r. Iso (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (PlanarGraph s Primal_ (VertexData r v) (EdgeData e) (FaceData (Dart s) f)) (PlanarGraph s Primal_ (VertexData r v) (EdgeData e) (FaceData (Dart s) f))
- fromPolygon :: proxy s -> SimplePolygon p r -> f -> f -> PlanarSubdivision s p () f r
- fromVertices :: proxy s -> CSeq (Point 2 r :+ p) -> PlanarGraph s Primal_ (VertexData r p) () ()
- fromConnectedSegments :: (Foldable f, Ord r, Num r) => proxy s -> f (LineSegment 2 p r :+ EdgeData e) -> PlanarSubdivision s [p] e () r
- fromConnectedSegments' :: (Foldable f, Ord r, Num r) => proxy s -> f (LineSegment 2 p r :+ e) -> PlanarGraph s Primal_ (VertexData r [p]) e ()
Documentation
data VertexData r v Source #
Note that the functor instance is in v
Bifunctor VertexData Source # | |
Functor (VertexData r) Source # | |
Foldable (VertexData r) Source # | |
Traversable (VertexData r) Source # | |
(Eq v, Eq r) => Eq (VertexData r v) Source # | |
(Ord v, Ord r) => Ord (VertexData r v) Source # | |
(Show v, Show r) => Show (VertexData r v) Source # | |
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
newtype PlanarSubdivision s v e f r Source #
PlanarSubdivision | |
|
graph :: forall s v e f r s v e f r. Iso (PlanarSubdivision s v e f r) (PlanarSubdivision s v e f r) (PlanarGraph s Primal_ (VertexData r v) (EdgeData e) (FaceData (Dart s) f)) (PlanarGraph s Primal_ (VertexData r v) (EdgeData e) (FaceData (Dart s) f)) Source #
:: proxy s | |
-> SimplePolygon p r | |
-> f | data inside |
-> f | data outside the polygon |
-> PlanarSubdivision s p () f r |
Construct a planar subdivision from a polygon
running time: \(O(n)\).
fromVertices :: proxy s -> CSeq (Point 2 r :+ p) -> PlanarGraph s Primal_ (VertexData r p) () () Source #
fromConnectedSegments :: (Foldable f, Ord r, Num r) => proxy s -> f (LineSegment 2 p r :+ EdgeData e) -> PlanarSubdivision s [p] e () r Source #
Constructs a connected planar subdivision.
pre: the segments form a single connected component running time: \(O(n\log n)\)
fromConnectedSegments' :: (Foldable f, Ord r, Num r) => proxy s -> f (LineSegment 2 p r :+ e) -> PlanarGraph s Primal_ (VertexData r [p]) e () Source #
Constructs a planar graph
pre: The segments form a single connected component
running time: \(O(n\log n)\)