diagrams-lib-1.3.0.7: 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 Linear.Affine.

Synopsis

Points

newtype Point f a :: (* -> *) -> * -> *

A handy wrapper to help distinguish points from vectors at the type level

Constructors

P (f a) 

Instances

Monad f => Monad (Point f) 
Functor f => Functor (Point f) 
Applicative f => Applicative (Point f) 
Foldable f => Foldable (Point f) 
Traversable f => Traversable (Point f) 
Generic1 (Point f) 
Apply f => Apply (Point f) 
Distributive f => Distributive (Point f) 
Representable f => Representable (Point f) 
Serial1 f => Serial1 (Point f) 
Additive f => Additive (Point f) 
Additive f => Affine (Point f) 
R4 f => R4 (Point f) 
R3 f => R3 (Point f) 
R2 f => R2 (Point f) 
R1 f => R1 (Point f) 
Metric f => Metric (Point f) 
Bind f => Bind (Point f) 
Eq1 f => Eq1 (Point f) 
Ord1 f => Ord1 (Point f) 
Read1 f => Read1 (Point f) 
Show1 f => Show1 (Point f) 
HasPhi v => HasPhi (Point v) Source 
HasTheta v => HasTheta (Point v) Source 
HasR v => HasR (Point v) Source 
(Metric v, OrderedField n) => TrailLike [Point v n] Source

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

Eq (f a) => Eq (Point f a) 
Fractional (f a) => Fractional (Point f a) 
(Data (f a), Typeable (* -> *) f, Typeable * a) => Data (Point f a) 
Num (f a) => Num (Point f a) 
Ord (f a) => Ord (Point f a) 
Read (f a) => Read (Point f a) 
Show (f a) => Show (Point f a) 
Ix (f a) => Ix (Point f a) 
Generic (Point f a) 
Storable (f a) => Storable (Point f a) 
Binary (f a) => Binary (Point f a) 
Serial (f a) => Serial (Point f a) 
Serialize (f a) => Serialize (Point f a) 
NFData (f a) => NFData (Point f a) 
(OrderedField n, Metric v) => Enveloped (Point v n) 
(Additive v, Ord n) => Traced (Point v n)

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

(Additive v, Num n) => Transformable (Point v n) 
(Additive v, Num n) => HasOrigin (Point v n) 
Hashable (f a) => Hashable (Point f a) 
Ixed (f a) => Ixed (Point f a) 
Wrapped (Point f a) 
Epsilon (f a) => Epsilon (Point f a) 
Coordinates (v n) => Coordinates (Point v n) Source 
(~) * t (Point g b) => Rewrapped (Point f a) t 
(~) * r (Point u n) => Deformable (Point v n) r Source 
(Additive v, Foldable v, Num n, (~) * r (Point u n)) => AffineMappable (Point v n) r Source 
LinearMappable (Point v n) (Point u m) Source 
Traversable f => Each (Point f a) (Point f b) a b 
Each (FixedSegment v n) (FixedSegment v' n') (Point v n) (Point v' n') 
(Additive v', Foldable v', Ord n') => Each (BoundingBox v n) (BoundingBox v' n') (Point v n) (Point v' n')

Only valid if the second point is not smaller than the first.

type Rep1 (Point f) = D1 D1Point (C1 C1_0Point (S1 NoSelector (Rec1 f))) 
type Rep (Point f) = Rep f 
type Diff (Point f) = f 
type Rep (Point f a) = D1 D1Point (C1 C1_0Point (S1 NoSelector (Rec0 (f a)))) 
type V (Point v n) = v 
type N (Point v n) = n 
type Index (Point f a) = Index (f a) 
type IxValue (Point f a) = IxValue (f a) 
type Unwrapped (Point f a) = f a 
type FinalCoord (Point v n) = FinalCoord (v n) Source 
type PrevDim (Point v n) = PrevDim (v n) Source 
type Decomposition (Point v n) = Decomposition (v n) Source 

origin :: (Additive f, Num a) => Point f a

Vector spaces have origins.

(*.) :: (Functor v, Num n) => n -> Point v n -> Point v n

Scale a point by a scalar. Specialized version of '(*^)'.

Point-related utilities

centroid :: (Additive v, Fractional n) => [Point v n] -> Point v n Source

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

pointDiagram :: (Metric v, Fractional n) => Point v n -> QDiagram b v n m

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

_Point :: (Profunctor p, Functor f) => p (f a) (f (f a)) -> p (Point f a) (f (Point f a))

lensP :: Functor f => (g a -> f (g a)) -> Point g a -> f (Point g a)