plot-light-0.4.3: A lightweight plotting library, exporting to SVG

Safe HaskellSafe
LanguageHaskell2010

Graphics.Rendering.Plot.Light.Internal.Geometry

Contents

Description

This module provides functionality for working with affine transformations (i.e. in the unit square)

Synopsis

Geometry

Point

data Point a Source #

A Point object defines a point in the plane

Constructors

Point 

Fields

Instances

Eq a => Eq (Point a) Source # 

Methods

(==) :: Point a -> Point a -> Bool #

(/=) :: Point a -> Point a -> Bool #

Ord a => Ord (Point a) Source # 

Methods

compare :: Point a -> Point a -> Ordering #

(<) :: Point a -> Point a -> Bool #

(<=) :: Point a -> Point a -> Bool #

(>) :: Point a -> Point a -> Bool #

(>=) :: Point a -> Point a -> Bool #

max :: Point a -> Point a -> Point a #

min :: Point a -> Point a -> Point a #

Show a => Show (Point a) Source # 

Methods

showsPrec :: Int -> Point a -> ShowS #

show :: Point a -> String #

showList :: [Point a] -> ShowS #

Generic (Point a) Source # 

Associated Types

type Rep (Point a) :: * -> * #

Methods

from :: Point a -> Rep (Point a) x #

to :: Rep (Point a) x -> Point a #

type Rep (Point a) Source # 
type Rep (Point a) = D1 * (MetaData "Point" "Graphics.Rendering.Plot.Light.Internal.Geometry" "plot-light-0.4.3-INdR6yt9R8U3A2rTrNIf1r" False) (C1 * (MetaCons "Point" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_px") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) (S1 * (MetaSel (Just Symbol "_py") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

mkPoint :: a -> a -> Point a Source #

setPointX :: a -> Point a -> Point a Source #

setPointY :: a -> Point a -> Point a Source #

LabeledPoint

data LabeledPoint l a Source #

A LabeledPoint carries a "label" (i.e. any additional information such as a text tag, or any other data structure), in addition to position information. Data points on a plot are LabeledPoints.

Constructors

LabeledPoint 

Fields

Instances

(Eq l, Eq a) => Eq (LabeledPoint l a) Source # 

Methods

(==) :: LabeledPoint l a -> LabeledPoint l a -> Bool #

(/=) :: LabeledPoint l a -> LabeledPoint l a -> Bool #

(Show l, Show a) => Show (LabeledPoint l a) Source # 

labelPoint :: (Point a -> l) -> Point a -> LabeledPoint l a Source #

Given a labelling function and a Point p, returned a LabeledPoint containing p and the computed label

mapLabel :: (l1 -> l2) -> LabeledPoint l1 a -> LabeledPoint l2 a Source #

Apply a function to the label

Frame

data Frame a Source #

A frame, i.e. a bounding box for objects

Constructors

Frame 

Fields

Instances

Eq a => Eq (Frame a) Source # 

Methods

(==) :: Frame a -> Frame a -> Bool #

(/=) :: Frame a -> Frame a -> Bool #

Show a => Show (Frame a) Source # 

Methods

showsPrec :: Int -> Frame a -> ShowS #

show :: Frame a -> String #

showList :: [Frame a] -> ShowS #

Generic (Frame a) Source # 

Associated Types

type Rep (Frame a) :: * -> * #

Methods

from :: Frame a -> Rep (Frame a) x #

to :: Rep (Frame a) x -> Frame a #

Ord a => Semigroup (Frame a) Source #

The semigroup operation (mappend) applied on two Frames results in a new Frame that bounds both.

Methods

(<>) :: Frame a -> Frame a -> Frame a #

sconcat :: NonEmpty (Frame a) -> Frame a #

stimes :: Integral b => b -> Frame a -> Frame a #

(Ord a, Num a) => Monoid (Frame a) Source # 

Methods

mempty :: Frame a #

mappend :: Frame a -> Frame a -> Frame a #

mconcat :: [Frame a] -> Frame a #

type Rep (Frame a) Source # 
type Rep (Frame a) = D1 * (MetaData "Frame" "Graphics.Rendering.Plot.Light.Internal.Geometry" "plot-light-0.4.3-INdR6yt9R8U3A2rTrNIf1r" False) (C1 * (MetaCons "Frame" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "_fpmin") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Point a))) (S1 * (MetaSel (Just Symbol "_fpmax") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Point a)))))

mkFrame :: Point a -> Point a -> Frame a Source #

unitFrame :: Num a => Frame a Source #

The unit square (0, 0) - (1, 1)

frameFromPoints :: (Ord a, Foldable t, Functor t) => t (Point a) -> Frame a Source #

Create a Frame from a container of Points P, i.e. construct two points p1 and p2 such that :

p1 := inf(x,y) P

p2 := sup(x,y) P

mkFrameOrigin :: Num a => a -> a -> Frame a Source #

Build a frame rooted at the origin (0, 0)

height :: Num a => Frame a -> a Source #

The width is the extent in the x direction and height is the extent in the y direction

width :: Num a => Frame a -> a Source #

The width is the extent in the x direction and height is the extent in the y direction

xmin :: Frame a -> a Source #

Frame corner coordinates

xmax :: Frame a -> a Source #

Frame corner coordinates

ymin :: Frame a -> a Source #

Frame corner coordinates

ymax :: Frame a -> a Source #

Frame corner coordinates

Axis

data Axis Source #

Constructors

X 
Y 

Instances

Eq Axis Source # 

Methods

(==) :: Axis -> Axis -> Bool #

(/=) :: Axis -> Axis -> Bool #

Show Axis Source # 

Methods

showsPrec :: Int -> Axis -> ShowS #

show :: Axis -> String #

showList :: [Axis] -> ShowS #

Vectors

data V2 a Source #

V2 is a vector in R^2

Constructors

V2 a a 

Instances

Eq a => Eq (V2 a) Source # 

Methods

(==) :: V2 a -> V2 a -> Bool #

(/=) :: V2 a -> V2 a -> Bool #

Show a => Show (V2 a) Source # 

Methods

showsPrec :: Int -> V2 a -> ShowS #

show :: V2 a -> String #

showList :: [V2 a] -> ShowS #

Num a => Semigroup (V2 a) Source # 

Methods

(<>) :: V2 a -> V2 a -> V2 a #

sconcat :: NonEmpty (V2 a) -> V2 a #

stimes :: Integral b => b -> V2 a -> V2 a #

Num a => Monoid (V2 a) Source #

Vectors form a monoid w.r.t. vector addition

Methods

mempty :: V2 a #

mappend :: V2 a -> V2 a -> V2 a #

mconcat :: [V2 a] -> V2 a #

Eps (V2 Double) Source # 

Methods

(~=) :: V2 Double -> V2 Double -> Bool Source #

Eps (V2 Float) Source # 

Methods

(~=) :: V2 Float -> V2 Float -> Bool Source #

Num a => Hermitian (V2 a) Source # 

Associated Types

type InnerProduct (V2 a) :: * Source #

Methods

(<.>) :: V2 a -> V2 a -> InnerProduct (V2 a) Source #

Num a => VectorSpace (V2 a) Source # 

Associated Types

type Scalar (V2 a) :: * Source #

Methods

(.*) :: Scalar (V2 a) -> V2 a -> V2 a Source #

Num a => AdditiveGroup (V2 a) Source #

Vectors form an additive group

Methods

zero :: V2 a Source #

(^+^) :: V2 a -> V2 a -> V2 a Source #

(^-^) :: V2 a -> V2 a -> V2 a Source #

Fractional a => MatrixGroup (DiagMat2 a) (V2 a) Source #

Diagonal matrices can always be inverted

Methods

(<\>) :: DiagMat2 a -> V2 a -> V2 a Source #

Num a => LinearMap (DiagMat2 a) (V2 a) Source # 

Methods

(#>) :: DiagMat2 a -> V2 a -> V2 a Source #

Num a => LinearMap (Mat2 a) (V2 a) Source # 

Methods

(#>) :: Mat2 a -> V2 a -> V2 a Source #

type InnerProduct (V2 a) Source # 
type InnerProduct (V2 a) = a
type Scalar (V2 a) Source # 
type Scalar (V2 a) = a

pointFromV2 :: V2 a -> Point a Source #

Build a Point p from a V2 v (i.e. assuming v points from the origin (0,0) to p)

Matrices

data Mat2 a Source #

A Mat2 can be seen as a linear operator that acts on points in the plane

Constructors

Mat2 a a a a 

Instances

Eq a => Eq (Mat2 a) Source # 

Methods

(==) :: Mat2 a -> Mat2 a -> Bool #

(/=) :: Mat2 a -> Mat2 a -> Bool #

Show a => Show (Mat2 a) Source # 

Methods

showsPrec :: Int -> Mat2 a -> ShowS #

show :: Mat2 a -> String #

showList :: [Mat2 a] -> ShowS #

Num a => Semigroup (Mat2 a) Source # 

Methods

(<>) :: Mat2 a -> Mat2 a -> Mat2 a #

sconcat :: NonEmpty (Mat2 a) -> Mat2 a #

stimes :: Integral b => b -> Mat2 a -> Mat2 a #

Num a => Monoid (Mat2 a) Source #

Matrices form a monoid w.r.t. matrix multiplication and have the identity matrix as neutral element

Methods

mempty :: Mat2 a #

mappend :: Mat2 a -> Mat2 a -> Mat2 a #

mconcat :: [Mat2 a] -> Mat2 a #

Num a => MultiplicativeSemigroup (Mat2 a) Source # 

Methods

(##) :: Mat2 a -> Mat2 a -> Mat2 a Source #

Num a => LinearMap (Mat2 a) (V2 a) Source # 

Methods

(#>) :: Mat2 a -> V2 a -> V2 a Source #

data DiagMat2 a Source #

Diagonal matrices in R2 behave as scaling transformations

Constructors

DMat2 a a 

Instances

Eq a => Eq (DiagMat2 a) Source # 

Methods

(==) :: DiagMat2 a -> DiagMat2 a -> Bool #

(/=) :: DiagMat2 a -> DiagMat2 a -> Bool #

Show a => Show (DiagMat2 a) Source # 

Methods

showsPrec :: Int -> DiagMat2 a -> ShowS #

show :: DiagMat2 a -> String #

showList :: [DiagMat2 a] -> ShowS #

Num a => Semigroup (DiagMat2 a) Source # 

Methods

(<>) :: DiagMat2 a -> DiagMat2 a -> DiagMat2 a #

sconcat :: NonEmpty (DiagMat2 a) -> DiagMat2 a #

stimes :: Integral b => b -> DiagMat2 a -> DiagMat2 a #

Num a => Monoid (DiagMat2 a) Source #

Diagonal matrices form a monoid w.r.t. matrix multiplication and have the identity matrix as neutral element

Methods

mempty :: DiagMat2 a #

mappend :: DiagMat2 a -> DiagMat2 a -> DiagMat2 a #

mconcat :: [DiagMat2 a] -> DiagMat2 a #

Num a => MultiplicativeSemigroup (DiagMat2 a) Source # 

Methods

(##) :: DiagMat2 a -> DiagMat2 a -> DiagMat2 a Source #

Fractional a => MatrixGroup (DiagMat2 a) (V2 a) Source #

Diagonal matrices can always be inverted

Methods

(<\>) :: DiagMat2 a -> V2 a -> V2 a Source #

Num a => LinearMap (DiagMat2 a) (V2 a) Source # 

Methods

(#>) :: DiagMat2 a -> V2 a -> V2 a Source #

diagMat2 :: Num a => a -> a -> DiagMat2 a Source #

Create a diagonal matrix

Primitive elements

origin :: Num a => Point a Source #

The origin of the axes, point (0, 0)

oneOne :: Num a => Point a Source #

The (1, 1) point

e1 :: Num a => V2 a Source #

X-aligned unit vector

e2 :: Num a => V2 a Source #

Y-aligned unit vector

Vector norm operations

norm2 :: (Hermitian v, Floating n, n ~ InnerProduct v) => v -> n Source #

Euclidean (L^2) norm

normalize2 :: (InnerProduct v ~ Scalar v, Floating (Scalar v), Hermitian v) => v -> v Source #

Normalize a V2 w.r.t. its Euclidean norm

Vector construction

v2fromEndpoints :: Num a => Point a -> Point a -> V2 a Source #

Create a V2 v from two endpoints p1, p2. That is v can be seen as pointing from p1 to p2

v2fromPoint :: Num a => Point a -> V2 a Source #

Build a V2 v from a Point p (i.e. assuming v points from the origin (0,0) to p)

Operations on points

movePoint :: Num a => V2 a -> Point a -> Point a Source #

Move a point along a vector

moveLabeledPointV2 :: Num a => V2 a -> LabeledPoint l a -> LabeledPoint l a Source #

Move a LabeledPoint along a vector

moveLabeledPointBwFrames Source #

Arguments

:: Fractional a 
=> Frame a

Initial frame

-> Frame a

Final frame

-> Bool

Flip L-R in [0,1] x [0,1]

-> Bool

Flip U-D in [0,1] x [0,1]

-> LabeledPoint l a

Initial LabeledPoint

-> LabeledPoint l a 

(-.) :: Num a => Point a -> Point a -> V2 a Source #

Create a V2 v from two endpoints p1, p2. That is v can be seen as pointing from p1 to p2

pointRange :: (Fractional a, Integral n) => n -> Point a -> Point a -> [Point a] Source #

`pointRange n p q` returns a list of equi-spaced Points between p and q.

Operations on vectors

frameToFrame Source #

Arguments

:: Fractional a 
=> Frame a

Initial frame

-> Frame a

Final frame

-> Bool

Flip L-R in [0,1] x [0,1]

-> Bool

Flip U-D in [0,1] x [0,1]

-> V2 a

Initial vector

-> V2 a 

Given two frames F1 and F2, returns a function f that maps an arbitrary vector v contained within F1 onto one contained within F2.

This function is composed of three affine maps :

  1. map v into a vector v01 that points within the unit square,
  2. map v01 onto v01'. This transformation serves to e.g. flip the dataset along the y axis (since the origin of the SVG canvas is the top-left corner of the screen). If this is not needed one can just supply the identity matrix and the zero vector,
  3. map v01' onto the target frame F2.

NB: we do not check that v is actually contained within the F1, nor that v01' is still contained within [0,1] x [0, 1]. This has to be supplied correctly by the user.

frameToFrameValue Source #

Arguments

:: Fractional t 
=> Frame t

Initial frame

-> Frame t

Final frame

-> t

Initial value

-> t 

Map function values across frames

Typeclasses

class AdditiveGroup v where Source #

Additive group :

v ^+^ zero == zero ^+^ v == v
v ^-^ v == zero

Minimal complete definition

zero, (^+^), (^-^)

Methods

zero :: v Source #

Identity element

(^+^) :: v -> v -> v Source #

Group action ("sum")

(^-^) :: v -> v -> v Source #

Inverse group action ("subtraction")

Instances

Num a => AdditiveGroup (V2 a) Source #

Vectors form an additive group

Methods

zero :: V2 a Source #

(^+^) :: V2 a -> V2 a -> V2 a Source #

(^-^) :: V2 a -> V2 a -> V2 a Source #

class AdditiveGroup v => VectorSpace v where Source #

Vector space : multiplication by a scalar quantity

Minimal complete definition

(.*)

Associated Types

type Scalar v :: * Source #

Methods

(.*) :: Scalar v -> v -> v Source #

Scalar multiplication

Instances

Num a => VectorSpace (V2 a) Source # 

Associated Types

type Scalar (V2 a) :: * Source #

Methods

(.*) :: Scalar (V2 a) -> V2 a -> V2 a Source #

class VectorSpace v => Hermitian v where Source #

Hermitian space : inner product

Minimal complete definition

(<.>)

Associated Types

type InnerProduct v :: * Source #

Methods

(<.>) :: v -> v -> InnerProduct v Source #

Inner product

Instances

Num a => Hermitian (V2 a) Source # 

Associated Types

type InnerProduct (V2 a) :: * Source #

Methods

(<.>) :: V2 a -> V2 a -> InnerProduct (V2 a) Source #

class Hermitian v => LinearMap m v where Source #

Linear maps, i.e. linear transformations of vectors

Minimal complete definition

(#>)

Methods

(#>) :: m -> v -> v Source #

Matrix action, i.e. linear transformation of a vector

Instances

Num a => LinearMap (DiagMat2 a) (V2 a) Source # 

Methods

(#>) :: DiagMat2 a -> V2 a -> V2 a Source #

Num a => LinearMap (Mat2 a) (V2 a) Source # 

Methods

(#>) :: Mat2 a -> V2 a -> V2 a Source #

class MultiplicativeSemigroup m where Source #

Multiplicative matrix semigroup ("multiplying" two matrices together)

Minimal complete definition

(##)

Methods

(##) :: m -> m -> m Source #

Matrix product

Instances

class LinearMap m v => MatrixGroup m v where Source #

The class of invertible linear transformations

Minimal complete definition

(<\>)

Methods

(<\>) :: m -> v -> v Source #

Inverse matrix action on a vector

Instances

Fractional a => MatrixGroup (DiagMat2 a) (V2 a) Source #

Diagonal matrices can always be inverted

Methods

(<\>) :: DiagMat2 a -> V2 a -> V2 a Source #

class Eps a where Source #

Numerical equality

Minimal complete definition

(~=)

Methods

(~=) :: a -> a -> Bool Source #

Comparison within numerical precision

Instances

Utilities

meshGrid Source #

Arguments

:: (Enum a, RealFrac a) 
=> Frame a 
-> Int

Number of points along x axis

-> Int

" y axis

-> [Point a] 

A list of nx by ny points in the plane arranged on the vertices of a rectangular mesh.

NB: Only the minimum x, y coordinate point is included in the output mesh. This is intentional, since the output from this can be used as an input to functions that use a corner rather than the center point as refernce (e.g. rect)

subdivSegment :: (Real a, Enum b, RealFrac b) => a -> a -> Int -> [b] Source #

interpolateBilinear :: (Ord p, Fractional p, Show p) => Frame p -> (Point p -> p) -> Point p -> p Source #

Interpolation

Safe