Chart-0.15: A library for generating 2D Charts and Plots

Graphics.Rendering.Chart.Types

Description

This module contains basic types and functions used for drawing.

Note that template haskell is used to derive accessor functions (see Data.Accessor) for each field of the following data types:

These accessors are not shown in this API documentation. They have the same name as the field, but with the trailing underscore dropped. Hence for data field f_::F in type D, they have type

   f :: Data.Accessor.Accessor D F

Synopsis

Documentation

data Rect Source

A rectangle is defined by two points.

Constructors

Rect Point Point 

Instances

data Point Source

A point in two dimensions.

Constructors

Point 

Fields

p_x :: Double
 
p_y :: Double
 

Instances

data Vector Source

Constructors

Vector 

Fields

v_x :: Double
 
v_y :: Double
 

Instances

mkrect :: Point -> Point -> Point -> Point -> RectSource

Create a rectangle based upon the coordinates of 4 points.

pvadd :: Point -> Vector -> PointSource

Add a point and a vector.

pvsub :: Point -> Vector -> PointSource

Subtract a vector from a point.

psub :: Point -> Point -> VectorSource

Subtract two points.

vscale :: Double -> Vector -> VectorSource

Scale a vector by a constant.

within :: Point -> Rect -> BoolSource

Test if a point is within a rectangle.

data Limit a Source

Constructors

LMin 
LValue a 
LMax 

Instances

Show a => Show (Limit a) 

type PointMapFn x y = (Limit x, Limit y) -> PointSource

A function mapping between points.

preserveCState :: CRender a -> CRender aSource

Execute a rendering action in a saved context (ie bracketed between C.save and C.restore).

rectPath :: Rect -> [Point]Source

Make a path from a rectangle.

strokePath :: [Point] -> CRender ()Source

Draw lines between the specified points.

The points will be corrected by the cenv_point_alignfn, so that when drawing bitmaps, 1 pixel wide lines will be centred on the pixels.

fillPath :: [Point] -> CRender ()Source

Fill the region with the given corners.

The points will be corrected by the cenv_coord_alignfn, so that when drawing bitmaps, the edges of the region will fall between pixels.

maybeM :: Monad m => b -> (a -> m b) -> Maybe a -> m bSource

data CairoLineStyle Source

Data type for the style of a line.

solidLineSource

Arguments

:: Double

Width of line.

-> AlphaColour Double 
-> CairoLineStyle 

dashedLineSource

Arguments

:: Double

Width of line.

-> [Double]

The dash pattern in device coordinates.

-> AlphaColour Double 
-> CairoLineStyle 

newtype CairoFillStyle Source

Abstract data type for a fill style.

The contained Cairo action sets the required fill style in the Cairo rendering state.

Constructors

CairoFillStyle (CRender ()) 

newtype CairoPointStyle Source

Abstract data type for the style of a plotted point.

The contained Cairo action draws a point in the desired style, at the supplied device coordinates.

Constructors

CairoPointStyle (Point -> CRender ()) 

filledPolygonSource

Arguments

:: Double

Radius of circle.

-> Int

Number of vertices.

-> Bool

Is right-side-up?

-> AlphaColour Double 
-> CairoPointStyle 

hollowPolygonSource

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> Int

Number of vertices.

-> Bool

Is right-side-up?

-> AlphaColour Double 
-> CairoPointStyle 

filledCirclesSource

Arguments

:: Double

Radius of circle.

-> AlphaColour Double

Colour.

-> CairoPointStyle 

hollowCirclesSource

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double 
-> CairoPointStyle 

plussesSource

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double 
-> CairoPointStyle 

exesSource

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double 
-> CairoPointStyle 

starsSource

Arguments

:: Double

Radius of circle.

-> Double

Thickness of line.

-> AlphaColour Double 
-> CairoPointStyle 

drawText :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender ()Source

Function to draw a textual label anchored by one of its corners or edges.

drawTextR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()Source

Function to draw a textual label anchored by one of its corners or edges, with rotation. Rotation angle is given in degrees, rotation is performed around anchor point.

drawTextsR :: HTextAnchor -> VTextAnchor -> Double -> Point -> String -> CRender ()Source

Function to draw a multi-line textual label anchored by one of its corners or edges, with rotation. Rotation angle is given in degrees, rotation is performed around anchor point.

textSize :: String -> CRender RectSizeSource

Return the bounding rectangle for a text string rendered in the current context.

textDrawRect :: HTextAnchor -> VTextAnchor -> Point -> String -> CRender RectSource

Recturn the bounding rectangle for a text string positioned where it would be drawn by drawText

newtype CRender a Source

The reader monad containing context information to control the rendering process.

Constructors

DR (ReaderT CEnv Render a) 

data CEnv Source

The environment present in the CRender Monad.

Constructors

CEnv 

Fields

cenv_point_alignfn :: Point -> Point

An adjustment applied immediately prior to points being displayed in device coordinates.

When device coordinates correspond to pixels, a cleaner image is created if this transform rounds to the nearest pixel. With higher-resolution output, this transform can just be the identity function.

cenv_coord_alignfn :: Point -> Point

A adjustment applied immediately prior to coordinates being transformed.