hgeometry-0.8.0.0: Geometric Algorithms, Data structures, and Data types.

Safe HaskellNone
LanguageHaskell2010

Algorithms.Geometry.DelaunayTriangulation.DivideAndConquer

Contents

Synopsis

Divide & Conqueror Delaunay Triangulation

delaunayTriangulation :: (Ord r, Fractional r) => NonEmpty (Point 2 r :+ p) -> Triangulation p r Source #

Computes the delaunay triangulation of a set of points.

Running time: \(O(n \log n)\) (note: We use an IntMap in the implementation. So maybe actually \(O(n \log^2 n)\))

pre: the input is a *SET*, i.e. contains no duplicate points. (If the input does contain duplicate points, the implementation throws them away)

Implementation

firsts :: ConvexPolygon (p :+ VertexID) r -> IntMap VertexID Source #

Mapping that says for each vtx in the convex hull what the first entry in the adj. list should be. The input polygon is given in Clockwise order

fromHull :: Ord r => Mapping p r -> ConvexPolygon (p :+ q) r -> Adj Source #

Given a polygon; construct the adjacency list representation pre: at least two elements

merge Source #

Arguments

:: (Ord r, Fractional r) 
=> Adj 
-> Adj 
-> LineSegment 2 (p :+ VertexID) r

lower tangent

-> LineSegment 2 (p :+ VertexID) r

upper tangent

-> Mapping p r 
-> Firsts 
-> Adj 

Merge the two delaunay triangulations.

running time: \(O(n)\) (although we cheat a bit by using a IntMap)

type Merge p r = StateT Adj (Reader (Mapping p r, Firsts)) Source #

moveUp :: (Ord r, Fractional r) => (VertexID, VertexID) -> VertexID -> VertexID -> Merge p r () Source #

Merges the two delaunay traingulations.

rotateR :: (Ord r, Fractional r) => VertexID -> VertexID -> Vertex -> Merge p r (Vertex, Bool) Source #

'rotates' around r and removes all neighbours of r that violate the delaunay condition. Returns the first vertex (as a Neighbour of r) that should remain in the Delaunay Triangulation, as well as a boolean A that helps deciding if we merge up by rotating left or rotating right (See description in the paper for more info)

rotateR' :: (Ord r, Fractional r) => VertexID -> VertexID -> Vertex -> Vertex -> Merge p r Vertex Source #

The code that does the actual rotating

rotateL :: (Ord r, Fractional r) => VertexID -> VertexID -> Vertex -> Merge p r (Vertex, Bool) Source #

Symmetric to rotateR

rotateL' :: (Ord r, Fractional r) => VertexID -> VertexID -> Vertex -> Vertex -> Merge p r Vertex Source #

The code that does the actual rotating. Symmetric to rotateR'

Primitives used by the Algorithm

qTest :: (Ord r, Fractional r) => VertexID -> VertexID -> Vertex -> Vertex -> Merge p r Bool Source #

returns True if the forth point (vertex) does not lie in the disk defined by the first three points.

insert :: (Num r, Ord r) => VertexID -> VertexID -> Merge p r () Source #

Inserts an edge into the right position.

rotateToFirst :: VertexID -> Firsts -> Merge p r () Source #

make sure that the first vtx in the adj list of v is its predecessor on the CH

insert' :: (Num r, Ord r) => VertexID -> VertexID -> Mapping p r -> Adj -> Adj Source #

Inserts an edge (and makes sure that the vertex is inserted in the correct. pos in the adjacency lists)

delete :: VertexID -> VertexID -> Adj -> Adj Source #

Deletes an edge

isLeftOf :: (Ord r, Num r) => VertexID -> (VertexID, VertexID) -> Merge p r Bool Source #

Lifted version of Convex.IsLeftOf

isRightOf :: (Ord r, Num r) => VertexID -> (VertexID, VertexID) -> Merge p r Bool Source #

Lifted version of Convex.IsRightOf

Some Helper functions

lookup' :: Ord k => Map k a -> k -> a Source #

rotateTo :: Eq a => a -> CList a -> CList a Source #

an unsafe version of rotateTo that assumes the element to rotate to occurs in the list.

pred' :: CList a -> CList a Source #

Adjacency lists are stored in clockwise order, so pred means rotate right

succ' :: CList a -> CList a Source #

Adjacency lists are stored in clockwise order, so pred and succ rotate left

focus' :: CList a -> a Source #

nub' :: Eq a => NonEmpty (a :+ b) -> NonEmpty (a :+ b) Source #

Removes duplicates from a sorted list

withID :: (c :+ e) -> e' -> c :+ (e :+ e') Source #

lookup'' :: Int -> IntMap a -> a Source #