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

CopyrightMarco Zocca 2017
LicenseBSD3
MaintainerMarco Zocca <zocca marco gmail>
Safe HaskellNone
LanguageHaskell2010

Graphics.Rendering.Plot.Light

Contents

Description

`plot-light` provides functionality for rendering vector graphics in SVG format. It is geared in particular towards scientific plotting, and it is termed "light" because it only requires a few common Haskell dependencies and no external libraries.

Usage

To use this project you just need import Graphics.Rendering.Plot.Light. If GHC complains of name clashes you can import the module in "qualified" form.

If you wish to try out the examples in this page, you will need to have these additional import statements:

import Text.Blaze.Svg.Renderer.String (renderSvg)
import qualified Data.Colour.Names as C

Synopsis

Graphical elements

rectCentered Source #

Arguments

:: (Show a, RealFrac a) 
=> Point a

Center coordinates

-> a

Width

-> a

Height

-> Maybe (Colour Double)

Stroke colour

-> Maybe (Colour Double)

Fill colour

-> Svg 

A rectangle, defined by its center coordinates and side lengths

> putStrLn $ renderSvg $ rectCentered (Point 20 30) 15 30 (Just C.blue) (Just C.red)
<g transform="translate(12.5 15.0)"><rect width="15.0" height="30.0" fill="#ff0000" stroke="#0000ff" /></g>

circle Source #

Arguments

:: (Real a1, Real a) 
=> Point a1

Center

-> a

Radius

-> Maybe (Colour Double)

Stroke colour

-> Maybe (Colour Double)

Fill colour

-> Svg 

A circle

> putStrLn $ renderSvg $ circle (Point 20 30) 15 (Just C.blue) (Just C.red)
<circle cx="20.0" cy="30.0" r="15.0" fill="#ff0000" stroke="#0000ff" />

line Source #

Arguments

:: (Show a, RealFrac a) 
=> Point a

First point

-> Point a

Second point

-> a

Stroke width

-> LineStroke_ a

Stroke type

-> Colour Double

Stroke colour

-> Svg 

Line segment between two Points

> putStrLn $ renderSvg $ line (Point 0 0) (Point 1 1) 0.1 Continuous C.blueviolet
<line x1="0.0" y1="0.0" x2="1.0" y2="1.0" stroke="#8a2be2" stroke-width="0.1" />
> putStrLn $ renderSvg (line (Point 0 0) (Point 1 1) 0.1 (Dashed [0.2, 0.3]) C.blueviolet)
<line x1="0.0" y1="0.0" x2="1.0" y2="1.0" stroke="#8a2be2" stroke-width="0.1" stroke-dasharray="0.2, 0.3" />

axis Source #

Arguments

:: (Functor t, Foldable t, Show a, RealFrac a) 
=> Point a

Origin coordinates

-> Axis

Axis (i.e. either X or Y)

-> a

Length of the axis

-> a

Stroke width

-> Colour Double

Stroke colour

-> a

The tick length is a fraction of the axis length

-> LineStroke_ a

Stroke type

-> Int

Label font size

-> a

Label rotation angle

-> TextAnchor_

How to anchor a text label to the axis

-> (l -> Text)

How to render the tick label

-> V2 a

Offset the label

-> t (LabeledPoint l a)

Tick center coordinates

-> Svg 

text Source #

Arguments

:: (Show a, Real a) 
=> a

Rotation angle of the frame

-> Int

Font size

-> Colour Double

Font colour

-> TextAnchor_

How to anchor a text label to the axis

-> Text

Text

-> V2 a

Displacement w.r.t. rotated frame

-> Point a

Reference frame origin of the text box

-> Svg 

text renders text onto the SVG canvas

Conventions

The Point argument p refers to the lower-left corner of the text box.

After the text is rendered, its text box can be rotated by rot degrees around p and then optionally anchored.

The user can supply an additional V2 displacement which will be applied after rotation and anchoring and refers to the rotated text box frame.

> putStrLn $ renderSvg $ text (-45) C.green TAEnd "blah" (V2 (- 10) 0) (Point 250 0)
<text x="-10.0" y="0.0" transform="translate(250.0 0.0)rotate(-45.0)" fill="#008000" text-anchor="end">blah</text>

polyline Source #

Arguments

:: (Foldable t, Show a1, Show a, RealFrac a, RealFrac a1) 
=> t (Point a)

Data

-> a1

Stroke width

-> LineStroke_ a

Stroke type

-> StrokeLineJoin_

Stroke join type

-> Colour Double

Stroke colour

-> Svg 

Polyline (piecewise straight line)

> putStrLn $ renderSvg (polyline [Point 100 50, Point 120 20, Point 230 50] 4 (Dashed [3, 5]) Round C.blueviolet)
<polyline points="100.0,50.0 120.0,20.0 230.0,50.0" fill="none" stroke="#8a2be2" stroke-width="4.0" stroke-linejoin="round" stroke-dasharray="3.0, 5.0" />

Element attributes

data LineStroke_ a Source #

Specify a continuous or dashed stroke

Constructors

Continuous 
Dashed [a] 

Instances

data TextAnchor_ Source #

Specify at which end should the text be anchored to its current point

Constructors

TAStart 
TAMiddle 
TAEnd 

SVG utilities

svgHeader :: Real a => Frame a -> Svg -> Svg Source #

Create the SVG header from a Frame

Types

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 #

data Point a Source #

A Point defines a point in R2

Constructors

Point 

Fields

Instances

Eq a => Eq (Point a) Source # 

Methods

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

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

Show a => Show (Point a) Source # 

Methods

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

show :: Point a -> String #

showList :: [Point a] -> ShowS #

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 # 

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 #

Geometry

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 => 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

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

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 from a Point p (i.e. assuming the V2 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

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

Operations on vectors

frameToFrame Source #

Arguments

:: (Fractional a, LinearMap m (V2 a)) 
=> Frame a

Initial frame

-> Frame a

Final frame

-> m

Optional rescaling in [0,1] x [0,1]

-> V2 a

Optional shift

-> V2 a

Initial vector

-> V2 a 

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

  1. map v into a unit square vector v01 with an affine transformation
  2. (optional) map v01 into another point in the unit square via a linear rescaling
  3. map v01' onto F2 with a second affine transformation

NB: we do not check that v is actually contained within the F1. This has to be supplied correctly by the user.

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