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

Graphics.Rendering.Chart.Plot

Contents

Description

Definitions of various types of Plots we can put on a 2D Chart.

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

Plot

data Plot x y Source

Interface to control plotting on a 2D area.

Constructors

Plot 

Fields

plot_render_ :: PointMapFn x y -> CRender ()

Given the mapping between model space coordinates and device coordinates, render this plot into a chart.

plot_legend_ :: [(String, Rect -> CRender ())]

Details for how to show this plot in a legend. For each item the string is the text to show, and the function renders a graphical sample of the plot.

plot_all_points_ :: ([x], [y])

All of the model space coordinates to be plotted. These are used to autoscale the axes where necessary.

joinPlot :: Plot x y -> Plot x y -> Plot x ySource

Join any two plots together (they will share a legend).

Typeclass for casting to plot

class ToPlot a whereSource

A type class abstracting the conversion of a value to a Plot.

Methods

toPlot :: a x y -> Plot x ySource

Point plots

data PlotPoints x y Source

Value defining a series of datapoints, and a style in which to render them.

Instances

Lines plot

data PlotLines x y Source

Value defining a series of (possibly disjointed) lines, and a style in which to render them.

Instances

hlinePlot :: String -> CairoLineStyle -> b -> Plot a bSource

Helper function to plot a single horizontal line.

vlinePlot :: String -> CairoLineStyle -> a -> Plot a bSource

Helper function to plot a single vertical line.

Plot with error bars

data PlotErrBars x y Source

Value defining a series of error intervals, and a style in which to render them.

Instances

data ErrPoint x y Source

Constructors

ErrPoint 

Fields

ep_x :: ErrValue x
 
ep_y :: ErrValue y
 

Instances

(Show x, Show y) => Show (ErrPoint x y) 

data ErrValue x Source

Value for holding a point with associated error bounds for each axis.

Constructors

ErrValue 

Fields

ev_low :: x
 
ev_best :: x
 
ev_high :: x
 

Instances

Show x => Show (ErrValue x) 

symErrPoint :: (Num a, Num b) => a -> b -> a -> b -> ErrPoint a bSource

When the error is symmetric, we can simply pass in dx for the error.

Plot with filled area

data PlotFillBetween x y Source

Value specifying a plot filling the area between two sets of Y coordinates, given common X coordinates.

Bar plots

data PlotBars x y Source

Value describing how to plot a set of bars. Note that the input data is typed [(x,[y])], ie for each x value we plot several y values. Typically the size of each [y] list would be the same.

Constructors

PlotBars 

Fields

plot_bars_style_ :: PlotBarsStyle

This value specifies whether each value from [y] should be shown beside or above the previous value.

plot_bars_item_styles_ :: [(CairoFillStyle, Maybe CairoLineStyle)]

The style in which to draw each element of [y]. A fill style is required, and if a linestyle is given, each bar will be outlined.

plot_bars_titles_ :: [String]

The title of each element of [y]. These will be shown in the legend.

plot_bars_spacing_ :: PlotBarsSpacing

This value controls how the widths of the bars are calculated. Either the widths of the bars, or the gaps between them can be fixed.

plot_bars_alignment_ :: PlotBarsAlignment

This value controls how bars for a fixed x are aligned with respect to the device coordinate corresponding to x.

plot_bars_reference_ :: y

The starting level for the chart (normally 0).

plot_bars_singleton_width_ :: Double
 
plot_bars_values_ :: [(x, [y])]

The actual points to be plotted.

data PlotBarsStyle Source

Constructors

BarsStacked

Bars for a fixed x are stacked vertically on top of each other.

BarsClustered

Bars for a fixed x are put horizontally beside each other.

Instances

data PlotBarsSpacing Source

Constructors

BarsFixWidth Double

All bars have the same width in pixels.

BarsFixGap Double Double

(BarsFixGap g mw) means make the gaps between the bars equal to g, but with a minimum bar width of mw

data PlotBarsAlignment Source

How bars for a given (x,[y]) are aligned with respect to screen coordinate corresponding to x (deviceX).

Constructors

BarsLeft

The left edge of bars is at deviceX

BarsCentered

The right edge of bars is at deviceX

BarsRight

Bars are centered around deviceX

Invisible plot

data PlotHidden x y Source

Value defining some hidden x and y values. The values don't get displayed, but still affect axis scaling.

Constructors

PlotHidden 

Instances

data PlotAnnotation x y Source

Value for describing a series of text annotations to be placed at arbitrary points on the graph. Annotations can be rotated and styled. Rotation angle is given in degrees, rotation is performend around the anchor point.

Accessors

These accessors are generated by template haskell

plot_lines_title :: forall x[awUc] y[awUd]. T (PlotLines x[awUc] y[awUd]) StringSource

plot_lines_style :: forall x[awUc] y[awUd]. T (PlotLines x[awUc] y[awUd]) CairoLineStyleSource

plot_lines_values :: forall x[awUc] y[awUd]. T (PlotLines x[awUc] y[awUd]) ([] ([] ((,) x[awUc] y[awUd])))Source

plot_lines_limit_values :: forall x[awUc] y[awUd]. T (PlotLines x[awUc] y[awUd]) ([] ([] ((,) (Limit x[awUc]) (Limit y[awUd]))))Source

plot_render :: forall x[awUh] y[awUi]. T (Plot x[awUh] y[awUi]) (PointMapFn x[awUh] y[awUi] -> CRender ())Source

plot_legend :: forall x[awUh] y[awUi]. T (Plot x[awUh] y[awUi]) ([] ((,) String (Rect -> CRender ())))Source

plot_all_points :: forall x[awUh] y[awUi]. T (Plot x[awUh] y[awUi]) ((,) ([] x[awUh]) ([] y[awUi]))Source

plot_points_title :: forall x[awUa] y[awUb]. T (PlotPoints x[awUa] y[awUb]) StringSource

plot_points_style :: forall x[awUa] y[awUb]. T (PlotPoints x[awUa] y[awUb]) CairoPointStyleSource

plot_points_values :: forall x[awUa] y[awUb]. T (PlotPoints x[awUa] y[awUb]) ([] ((,) x[awUa] y[awUb]))Source

plot_fillbetween_title :: forall x[awU8] y[awU9]. T (PlotFillBetween x[awU8] y[awU9]) StringSource

plot_fillbetween_style :: forall x[awU8] y[awU9]. T (PlotFillBetween x[awU8] y[awU9]) CairoFillStyleSource

plot_fillbetween_values :: forall x[awU8] y[awU9]. T (PlotFillBetween x[awU8] y[awU9]) ([] ((,) x[awU8] ((,) y[awU9] y[awU9])))Source

plot_errbars_title :: forall x[awU3] y[awU4]. T (PlotErrBars x[awU3] y[awU4]) StringSource

plot_errbars_line_style :: forall x[awU3] y[awU4]. T (PlotErrBars x[awU3] y[awU4]) CairoLineStyleSource

plot_errbars_tick_length :: forall x[awU3] y[awU4]. T (PlotErrBars x[awU3] y[awU4]) DoubleSource

plot_errbars_overhang :: forall x[awU3] y[awU4]. T (PlotErrBars x[awU3] y[awU4]) DoubleSource

plot_errbars_values :: forall x[awU3] y[awU4]. T (PlotErrBars x[awU3] y[awU4]) ([] (ErrPoint x[awU3] y[awU4]))Source

plot_bars_style :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) PlotBarsStyleSource

plot_bars_item_styles :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) ([] ((,) CairoFillStyle (Maybe CairoLineStyle)))Source

plot_bars_titles :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) ([] String)Source

plot_bars_spacing :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) PlotBarsSpacingSource

plot_bars_alignment :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) PlotBarsAlignmentSource

plot_bars_reference :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) y[awU1]Source

plot_bars_singleton_width :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) DoubleSource

plot_bars_values :: forall x[awU0] y[awU1]. T (PlotBars x[awU0] y[awU1]) ([] ((,) x[awU0] ([] y[awU1])))Source

plot_annotation_hanchor :: forall x[awTW] y[awTX]. T (PlotAnnotation x[awTW] y[awTX]) HTextAnchorSource

plot_annotation_vanchor :: forall x[awTW] y[awTX]. T (PlotAnnotation x[awTW] y[awTX]) VTextAnchorSource

plot_annotation_angle :: forall x[awTW] y[awTX]. T (PlotAnnotation x[awTW] y[awTX]) DoubleSource

plot_annotation_style :: forall x[awTW] y[awTX]. T (PlotAnnotation x[awTW] y[awTX]) CairoFontStyleSource

plot_annotation_values :: forall x[awTW] y[awTX]. T (PlotAnnotation x[awTW] y[awTX]) ([] ((,,) x[awTW] y[awTX] String))Source