plot-light-0.1.0.5: 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 few native Haskell dependencies.

It builds upon `blaze-svg` by adding type-safe combinators, geometry primitives and related functions.

Usage

To use this project you just need to import this module qualified (to avoid name clashes with any other modules you might have loaded on the side), for example as follows :

import Graphics.Rendering.Plot.Light as P

If you wish to try out the examples in this page, you will need to have renderSvg in scope as well:

import Text.Blaze.Svg.Renderer.String (renderSvg)

Synopsis

Graphical elements

rectCentered Source #

Arguments

:: Point Double

Center coordinates

-> Double

Width

-> Double

Height

-> Colour Double

Colour

-> Svg 

A filled rectangle

line Source #

Arguments

:: Point Double

First point

-> Point Double

Second point

-> Double

Stroke width

-> Colour Double

Stroke colour

-> Svg 

Line segment between two Points

> putStrLn $ renderSvg (line 0 0 1 1 0.1 C.blueviolet)
<line x1="0.0" y1="0.0" x2="1.0" y2="1.0" stroke="#8a2be2" stroke-width="0.1" />

axis Source #

Arguments

:: (Functor t, Foldable t) 
=> Axis

Axis (i.e. either X or Y)

-> Double

Length

-> Double

Stroke width

-> Colour Double

Stroke colour

-> Double

Tick length fraction (w.r.t axis length)

-> Point Double

Axis center coordinate

-> t (Point Double)

Tick center coordinates

-> Svg 

An axis with tickmarks

> putStrLn $ renderSvg $ axis X 200 2 C.red 0.05 (Point 150 10) [Point 50 1, Point 60 1, Point 70 1]
<line x1="50.0" y1="10.0" x2="250.0" y2="10.0" stroke="#ff0000" stroke-width="2.0" /><line x1="50.0" y1="5.0" x2="50.0" y2="15.0" stroke="#ff0000" stroke-width="2.0" /><line x1="60.0" y1="5.0" x2="60.0" y2="15.0" stroke="#ff0000" stroke-width="2.0" /><line x1="70.0" y1="5.0" x2="70.0" y2="15.0" stroke="#ff0000" stroke-width="2.0" />

text Source #

Arguments

:: (Show a, Show a1, ToValue a2) 
=> a1

Rotation angle

-> Colour Double

Font colour

-> Text

Text

-> V2 a2

Displacement

-> Point a

Initial center position of the text box

-> Svg 

text renders text onto the SVG canvas. It is also possible to rotate and move the text, however the order of these modifiers matters.

NB1: The Point parameter p determines the initial position of the bottom-left corner of the text box. If a nonzero rotation is applied, the whole text box will move on a circle of radius || x^2 + y^2 || centered at p.

NB2: the rotate and translate attributes apply to the center of the visible text instead.

> putStrLn $ renderSvg $ text (-45) C.red "hullo!" (V2 (-30) 0) (Point 0 20)
<text x="-30" y="0" transform="translate(0 20)rotate(-45)" fill="#ff0000">hullo!</text>

polyline Source #

Arguments

:: (Show a1, Show a) 
=> [(a1, a)]

Data

-> Double

Stroke width

-> Colour Double

Stroke colour

-> Svg 

Polyline (piecewise straight line)

> putStrLn $ renderSvg (polyline [(1,1), (2,1), (2,2), (3,4)] 0.1 C.red)
<polyline points="1,1 2,1 2,2 3,4" fill="none" stroke="#ff0000" stroke-width="0.1" />

Types

data FigureData a Source #

Constructors

FigData 

Fields

Instances

Eq a => Eq (FigureData a) Source # 

Methods

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

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

Show a => Show (FigureData a) Source # 

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

Enum Axis Source # 

Methods

succ :: Axis -> Axis #

pred :: Axis -> Axis #

toEnum :: Int -> Axis #

fromEnum :: Axis -> Int #

enumFrom :: Axis -> [Axis] #

enumFromThen :: Axis -> Axis -> [Axis] #

enumFromTo :: Axis -> Axis -> [Axis] #

enumFromThenTo :: Axis -> Axis -> Axis -> [Axis] #

Eq Axis Source # 

Methods

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

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

Show Axis Source # 

Methods

showsPrec :: Int -> Axis -> ShowS #

show :: Axis -> String #

showList :: [Axis] -> ShowS #

mkFigureData :: Num a => Point a -> a -> a -> FigureData a Source #

Create a FigureData structure from the top-left corner point and its side lengths

svgHeader :: FigureData Int -> Svg -> Svg Source #

Create the SVG header from FigureData

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 #

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

mkV2fromEndpoints :: 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

fromUnitSquare :: Num a => Frame a -> Point a -> Point a Source #

The vector translation from a Point p contained in the unit square onto a Frame

NB: we do not check that p is actually contained in [0,1] x [0,1], This has to be supplied correctly by the user

toUnitSquare :: (Fractional a, MatrixGroup (Mat2 a) (V2 a)) => Frame a -> Point a -> Point a Source #

The vector translation from a Point contained in a Frame onto the unit square

NB: we do not check that p is actually contained within the frame. 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 #