Copyright | (C) Frank Staals |
---|---|
License | see the LICENSE file |
Maintainer | Frank Staals |
Safe Haskell | None |
Language | Haskell2010 |
Defines some geometric types used in the delaunay triangulation
Synopsis
- type VertexID = Int
- type Vertex = CList VertexID
- type Adj = IntMap (CList VertexID)
- data Triangulation p r = Triangulation {
- _vertexIds :: Map (Point 2 r) VertexID
- _positions :: Vector (Point 2 r :+ p)
- _neighbours :: Vector (CList VertexID)
- vertexIds :: forall p r. Lens' (Triangulation p r) (Map (Point 2 r) VertexID)
- positions :: forall p r p. Lens (Triangulation p r) (Triangulation p r) (Vector ((:+) (Point 2 r) p)) (Vector ((:+) (Point 2 r) p))
- neighbours :: forall p r. Lens' (Triangulation p r) (Vector (CList VertexID))
- type Mapping p r = (Map (Point 2 r) VertexID, Vector (Point 2 r :+ p))
- showDT :: (Show p, Show r) => Triangulation p r -> IO ()
- triangulationEdges :: Triangulation p r -> [(Point 2 r :+ p, Point 2 r :+ p)]
- tEdges :: Triangulation p r -> [(VertexID, VertexID)]
- data ST a b c = ST {}
- type ArcID = Int
- type ST' a = ST (Map (VertexID, VertexID) ArcID) ArcID a
- toPlanarSubdivision :: (Ord r, Fractional r) => proxy s -> Triangulation p r -> PlanarSubdivision s p () () r
- toPlaneGraph :: forall proxy s p r. proxy s -> Triangulation p r -> PlaneGraph s p () () r
Documentation
data Triangulation p r Source #
Neighbours are stored in clockwise order: i.e. rotating right moves to the next clockwise neighbour.
Triangulation | |
|
Instances
(Eq r, Eq p) => Eq (Triangulation p r) Source # | |
Defined in Algorithms.Geometry.DelaunayTriangulation.Types (==) :: Triangulation p r -> Triangulation p r -> Bool # (/=) :: Triangulation p r -> Triangulation p r -> Bool # | |
(Show r, Show p) => Show (Triangulation p r) Source # | |
Defined in Algorithms.Geometry.DelaunayTriangulation.Types showsPrec :: Int -> Triangulation p r -> ShowS # show :: Triangulation p r -> String # showList :: [Triangulation p r] -> ShowS # | |
type NumType (Triangulation p r) Source # | |
type Dimension (Triangulation p r) Source # | |
positions :: forall p r p. Lens (Triangulation p r) (Triangulation p r) (Vector ((:+) (Point 2 r) p)) (Vector ((:+) (Point 2 r) p)) Source #
neighbours :: forall p r. Lens' (Triangulation p r) (Vector (CList VertexID)) Source #
triangulationEdges :: Triangulation p r -> [(Point 2 r :+ p, Point 2 r :+ p)] Source #
type ST' a = ST (Map (VertexID, VertexID) ArcID) ArcID a Source #
ST' is a strict triple (m,a,x) containing:
- m: a Map, mapping edges, represented by a pair of vertexId's (u,v) with u < v, to arcId's.
- a: the next available unused arcID
- x: the data value we are interested in computing
toPlanarSubdivision :: (Ord r, Fractional r) => proxy s -> Triangulation p r -> PlanarSubdivision s p () () r Source #
convert the triangulation into a planarsubdivision
running time: \(O(n)\).
toPlaneGraph :: forall proxy s p r. proxy s -> Triangulation p r -> PlaneGraph s p () () r Source #
convert the triangulation into a plane graph
running time: \(O(n)\).