| Copyright | (c) Sven Panne 2002-2018 | 
|---|---|
| License | BSD3 | 
| Maintainer | Sven Panne <[email protected]> | 
| Stability | stable | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Graphics.Rendering.OpenGL.GLU.Tessellation
Contents
Description
This module corresponds to chapter 5 (Polygon Tessellation) of the GLU specs.
Synopsis
- data AnnotatedVertex v = AnnotatedVertex (Vertex3 GLdouble) v
- newtype ComplexContour v = ComplexContour [AnnotatedVertex v]
- newtype ComplexPolygon v = ComplexPolygon [ComplexContour v]
- data WeightedProperties v = WeightedProperties (GLfloat, v) (GLfloat, v) (GLfloat, v) (GLfloat, v)
- type Combiner v = Vertex3 GLdouble -> WeightedProperties v -> v
- data TessWinding
- type Tolerance = GLdouble
- type Tessellator p v = TessWinding -> Tolerance -> Normal3 GLdouble -> Combiner v -> ComplexPolygon v -> IO (p v)
- newtype SimpleContour v = SimpleContour [AnnotatedVertex v]
- newtype PolygonContours v = PolygonContours [SimpleContour v]
- extractContours :: Storable v => Tessellator PolygonContours v
- type TriangleVertex v = AnnotatedVertex (v, EdgeFlag)
- data Triangle v = Triangle (TriangleVertex v) (TriangleVertex v) (TriangleVertex v)
- newtype Triangulation v = Triangulation [Triangle v]
- triangulate :: Storable v => Tessellator Triangulation v
- data Primitive v = Primitive PrimitiveMode [AnnotatedVertex v]
- newtype SimplePolygon v = SimplePolygon [Primitive v]
- tessellate :: Storable v => Tessellator SimplePolygon v
Polygon description
data AnnotatedVertex v Source #
The basic building block in tessellation is a 3D vertex with an associated property, e.g. color, texture coordinates, etc.
Constructors
| AnnotatedVertex (Vertex3 GLdouble) v | 
Instances
newtype ComplexContour v Source #
A complex contour, which can be self-intersecting and/or concave.
Constructors
| ComplexContour [AnnotatedVertex v] | 
Instances
| Eq v => Eq (ComplexContour v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: ComplexContour v -> ComplexContour v -> Bool # (/=) :: ComplexContour v -> ComplexContour v -> Bool # | |
| Ord v => Ord (ComplexContour v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: ComplexContour v -> ComplexContour v -> Ordering # (<) :: ComplexContour v -> ComplexContour v -> Bool # (<=) :: ComplexContour v -> ComplexContour v -> Bool # (>) :: ComplexContour v -> ComplexContour v -> Bool # (>=) :: ComplexContour v -> ComplexContour v -> Bool # max :: ComplexContour v -> ComplexContour v -> ComplexContour v # min :: ComplexContour v -> ComplexContour v -> ComplexContour v # | |
newtype ComplexPolygon v Source #
A complex (possibly concave) polygon, represented by one or more complex and possibly intersecting contours.
Constructors
| ComplexPolygon [ComplexContour v] | 
Instances
| Eq v => Eq (ComplexPolygon v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: ComplexPolygon v -> ComplexPolygon v -> Bool # (/=) :: ComplexPolygon v -> ComplexPolygon v -> Bool # | |
| Ord v => Ord (ComplexPolygon v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: ComplexPolygon v -> ComplexPolygon v -> Ordering # (<) :: ComplexPolygon v -> ComplexPolygon v -> Bool # (<=) :: ComplexPolygon v -> ComplexPolygon v -> Bool # (>) :: ComplexPolygon v -> ComplexPolygon v -> Bool # (>=) :: ComplexPolygon v -> ComplexPolygon v -> Bool # max :: ComplexPolygon v -> ComplexPolygon v -> ComplexPolygon v # min :: ComplexPolygon v -> ComplexPolygon v -> ComplexPolygon v # | |
Combining vertices
data WeightedProperties v Source #
Four vertex properties (cf. AnnotatedVertex) with associated weigths
 summing up to 1.0.
Constructors
| WeightedProperties (GLfloat, v) (GLfloat, v) (GLfloat, v) (GLfloat, v) | 
Instances
| Eq v => Eq (WeightedProperties v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: WeightedProperties v -> WeightedProperties v -> Bool # (/=) :: WeightedProperties v -> WeightedProperties v -> Bool # | |
| Ord v => Ord (WeightedProperties v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: WeightedProperties v -> WeightedProperties v -> Ordering # (<) :: WeightedProperties v -> WeightedProperties v -> Bool # (<=) :: WeightedProperties v -> WeightedProperties v -> Bool # (>) :: WeightedProperties v -> WeightedProperties v -> Bool # (>=) :: WeightedProperties v -> WeightedProperties v -> Bool # max :: WeightedProperties v -> WeightedProperties v -> WeightedProperties v # min :: WeightedProperties v -> WeightedProperties v -> WeightedProperties v # | |
type Combiner v = Vertex3 GLdouble -> WeightedProperties v -> v Source #
A function combining given vertex properties into a property for a newly generated vertex
Tessellation parameters
data TessWinding Source #
Constructors
| TessWindingOdd | |
| TessWindingNonzero | |
| TessWindingPositive | |
| TessWindingNegative | |
| TessWindingAbsGeqTwo | 
Instances
| Eq TessWinding Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation | |
| Ord TessWinding Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: TessWinding -> TessWinding -> Ordering # (<) :: TessWinding -> TessWinding -> Bool # (<=) :: TessWinding -> TessWinding -> Bool # (>) :: TessWinding -> TessWinding -> Bool # (>=) :: TessWinding -> TessWinding -> Bool # max :: TessWinding -> TessWinding -> TessWinding # min :: TessWinding -> TessWinding -> TessWinding # | |
| Show TessWinding Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods showsPrec :: Int -> TessWinding -> ShowS # show :: TessWinding -> String # showList :: [TessWinding] -> ShowS # | |
type Tolerance = GLdouble Source #
The relative tolerance under which two vertices can be combined (see
 Combiner). Multiplication with the largest coordinate magnitude of all
 polygon vertices yields the maximum distance between two mergeable vertices.
Note that merging is optional and the tolerance is only a hint.
Tessellator type
type Tessellator p v = TessWinding -> Tolerance -> Normal3 GLdouble -> Combiner v -> ComplexPolygon v -> IO (p v) Source #
A general tessellator type.
Before tessellation of a complex polygon, all its vertices are projected into
 a plane perpendicular to the given normal. If the given normal is
 Normal3 0 0 0, a fitting plane of all vertices is used.
Contour extraction
newtype SimpleContour v Source #
A simple, non-self-intersecting contour
Constructors
| SimpleContour [AnnotatedVertex v] | 
Instances
| Eq v => Eq (SimpleContour v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: SimpleContour v -> SimpleContour v -> Bool # (/=) :: SimpleContour v -> SimpleContour v -> Bool # | |
| Ord v => Ord (SimpleContour v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: SimpleContour v -> SimpleContour v -> Ordering # (<) :: SimpleContour v -> SimpleContour v -> Bool # (<=) :: SimpleContour v -> SimpleContour v -> Bool # (>) :: SimpleContour v -> SimpleContour v -> Bool # (>=) :: SimpleContour v -> SimpleContour v -> Bool # max :: SimpleContour v -> SimpleContour v -> SimpleContour v # min :: SimpleContour v -> SimpleContour v -> SimpleContour v # | |
newtype PolygonContours v Source #
The contours of a complex polygon, represented by one or more non-intersecting simple contours
Constructors
| PolygonContours [SimpleContour v] | 
Instances
| Eq v => Eq (PolygonContours v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: PolygonContours v -> PolygonContours v -> Bool # (/=) :: PolygonContours v -> PolygonContours v -> Bool # | |
| Ord v => Ord (PolygonContours v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: PolygonContours v -> PolygonContours v -> Ordering # (<) :: PolygonContours v -> PolygonContours v -> Bool # (<=) :: PolygonContours v -> PolygonContours v -> Bool # (>) :: PolygonContours v -> PolygonContours v -> Bool # (>=) :: PolygonContours v -> PolygonContours v -> Bool # max :: PolygonContours v -> PolygonContours v -> PolygonContours v # min :: PolygonContours v -> PolygonContours v -> PolygonContours v # | |
extractContours :: Storable v => Tessellator PolygonContours v Source #
Triangulation
type TriangleVertex v = AnnotatedVertex (v, EdgeFlag) Source #
A triangle vertex with additional information about the edge it begins
A triangle, represented by three triangle vertices
Constructors
| Triangle (TriangleVertex v) (TriangleVertex v) (TriangleVertex v) | 
Instances
| Eq v => Eq (Triangle v) Source # | |
| Ord v => Ord (Triangle v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation | |
newtype Triangulation v Source #
A triangulation of a complex polygon
Constructors
| Triangulation [Triangle v] | 
Instances
| Eq v => Eq (Triangulation v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: Triangulation v -> Triangulation v -> Bool # (/=) :: Triangulation v -> Triangulation v -> Bool # | |
| Ord v => Ord (Triangulation v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: Triangulation v -> Triangulation v -> Ordering # (<) :: Triangulation v -> Triangulation v -> Bool # (<=) :: Triangulation v -> Triangulation v -> Bool # (>) :: Triangulation v -> Triangulation v -> Bool # (>=) :: Triangulation v -> Triangulation v -> Bool # max :: Triangulation v -> Triangulation v -> Triangulation v # min :: Triangulation v -> Triangulation v -> Triangulation v # | |
triangulate :: Storable v => Tessellator Triangulation v Source #
Tessellation into primitives
Constructors
| Primitive PrimitiveMode [AnnotatedVertex v] | 
Instances
| Eq v => Eq (Primitive v) Source # | |
| Ord v => Ord (Primitive v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation | |
newtype SimplePolygon v Source #
Constructors
| SimplePolygon [Primitive v] | 
Instances
| Eq v => Eq (SimplePolygon v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods (==) :: SimplePolygon v -> SimplePolygon v -> Bool # (/=) :: SimplePolygon v -> SimplePolygon v -> Bool # | |
| Ord v => Ord (SimplePolygon v) Source # | |
| Defined in Graphics.Rendering.OpenGL.GLU.Tessellation Methods compare :: SimplePolygon v -> SimplePolygon v -> Ordering # (<) :: SimplePolygon v -> SimplePolygon v -> Bool # (<=) :: SimplePolygon v -> SimplePolygon v -> Bool # (>) :: SimplePolygon v -> SimplePolygon v -> Bool # (>=) :: SimplePolygon v -> SimplePolygon v -> Bool # max :: SimplePolygon v -> SimplePolygon v -> SimplePolygon v # min :: SimplePolygon v -> SimplePolygon v -> SimplePolygon v # | |
tessellate :: Storable v => Tessellator SimplePolygon v Source #