diagrams-lib-1.1.0.3: Embedded domain-specific language for declarative graphics

Copyright(c) 2011 diagrams-lib team (see LICENSE)
LicenseBSD-style (see LICENSE)
Maintainerdiagrams-discuss@googlegroups.com
Safe HaskellNone
LanguageHaskell2010

Diagrams.Points

Contents

Description

Points in space. For more tools for working with points and vectors, see Data.AffineSpace and Diagrams.Coordinates.

Synopsis

Points

data Point v :: * -> *

Point is a newtype wrapper around vectors used to represent points, so we don't get them mixed up. The distinction between vectors and points is important: translations affect points, but leave vectors unchanged. Points are instances of the AffineSpace class from Data.AffineSpace.

Instances

Functor Point 
HasZ P3 
HasY P2 
HasY P3 
HasX P2 
HasX P3 
Eq v => Eq (Point v) 
Data v => Data (Point v) 
Ord v => Ord (Point v) 
Read v => Read (Point v) 
Show v => Show (Point v) 
(OrderedField (Scalar v), InnerSpace v) => Enveloped (Point v) 
(Ord (Scalar v), VectorSpace v) => Traced (Point v)

The trace of a single point is the empty trace, i.e. the one which returns no intersection points for every query. Arguably it should return a single finite distance for vectors aimed directly at the given point, but due to floating-point inaccuracy this is problematic. Note that the envelope for a single point is not the empty envelope (see Diagrams.Core.Envelope).

HasLinearMap v => Transformable (Point v) 
VectorSpace v => HasOrigin (Point v) 
AdditiveGroup v => AffineSpace (Point v) 
Coordinates v => Coordinates (Point v) 
(InnerSpace v, OrderedField (Scalar v)) => TrailLike [Point v]

A list of points is trail-like; this instance simply computes the vertices of the trail, using trailVertices.

Deformable (Point v) 
Typeable (* -> *) Point 
type V (Point v) = v 
type Diff (Point v) = v 
type FinalCoord (Point v) = FinalCoord v 
type PrevDim (Point v) = PrevDim v 
type Decomposition (Point v) = Decomposition v 

origin :: AdditiveGroup v => Point v

The origin of the vector space v.

(*.) :: VectorSpace v => Scalar v -> Point v -> Point v

Scale a point by a scalar.

Point-related utilities

centroid :: (VectorSpace v, Fractional (Scalar v)) => [Point v] -> Point v Source

The centroid of a set of n points is their sum divided by n.

pointDiagram :: (Fractional (Scalar v), InnerSpace v) => Point v -> QDiagram b v m

Create a "point diagram", which has no content, no trace, an empty query, and a point envelope.