hgeometry-0.12.0.1: Geometric Algorithms, Data structures, and Data types.
Copyright(C) Frank Staals
Licensesee the LICENSE file
MaintainerFrank Staals
Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.DelaunayTriangulation.Types

Description

Defines some geometric types used in the delaunay triangulation

Synopsis

Documentation

type VertexID = Int Source #

Vertex identifier.

type Vertex = CList VertexID Source #

Rotating Right - rotate clockwise

type Adj = IntMap (CList VertexID) Source #

Neighbours indexed by VertexID.

data Triangulation p r Source #

Neighbours are stored in clockwise order: i.e. rotating right moves to the next clockwise neighbour.

Instances

Instances details
(Eq r, Eq p) => Eq (Triangulation p r) Source # 
Instance details

Defined in Algorithms.Geometry.DelaunayTriangulation.Types

Methods

(==) :: Triangulation p r -> Triangulation p r -> Bool #

(/=) :: Triangulation p r -> Triangulation p r -> Bool #

(Show r, Show p) => Show (Triangulation p r) Source # 
Instance details

Defined in Algorithms.Geometry.DelaunayTriangulation.Types

type NumType (Triangulation p r) Source # 
Instance details

Defined in Algorithms.Geometry.DelaunayTriangulation.Types

type NumType (Triangulation p r) = r
type Dimension (Triangulation p r) Source # 
Instance details

Defined in Algorithms.Geometry.DelaunayTriangulation.Types

type Dimension (Triangulation p r) = 2

vertexIds :: Lens' (Triangulation p r) (Map (Point 2 r) VertexID) Source #

Mapping between triangulated points and their internal VertexID.

positions :: Lens (Triangulation p1 r) (Triangulation p2 r) (Vector (Point 2 r :+ p1)) (Vector (Point 2 r :+ p2)) Source #

Point positions indexed by VertexID.

neighbours :: Lens' (Triangulation p r) (Vector (CList VertexID)) Source #

Point neighbours indexed by VertexID.

type Mapping p r = (Map (Point 2 r) VertexID, Vector (Point 2 r :+ p)) Source #

Bidirectional mapping between points and VertexIDs.

edgesAsPoints :: Triangulation p r -> [(Point 2 r :+ p, Point 2 r :+ p)] Source #

List add edges as point pairs.

edgesAsVertices :: Triangulation p r -> [(VertexID, VertexID)] Source #

List add edges as VertexID pairs.

toPlanarSubdivision :: (Ord r, Fractional r) => proxy s -> Triangulation p r -> PlanarSubdivision s p () () r 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 type ST' a = ST (SM.Map (VertexID,VertexID) ArcID) ArcID a

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)\).