hgeometry-0.10.0.0: 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 #

Rotating Right - rotate clockwise

data Triangulation p r Source #

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

Instances
(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 :: forall p r. Lens' (Triangulation p r) (Map (Point 2 r) VertexID) Source #

positions :: forall p r p. Lens (Triangulation p r) (Triangulation p r) (Vector ((:+) (Point 2 r) p)) (Vector ((:+) (Point 2 r) p)) Source #

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

showDT :: (Show p, Show r) => Triangulation p r -> IO () Source #

data ST a b c Source #

Constructors

ST 

Fields

type ArcID = Int 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)\).