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

Graphics.Rendering.Chart.Layout

Description

This module glues together axes and plots to actually create a renderable for a 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

Documentation

data Layout1 x y Source

A Layout1 value is a single plot area, with optional: axes on each of the 4 sides; title at the top; legend at the bottom. It's parameterised by the types of values to be plotted on the horizonal and vertical axes.

Constructors

Layout1 

Fields

layout1_background_ :: CairoFillStyle
 
layout1_plot_background_ :: Maybe CairoFillStyle
 
layout1_title_ :: String
 
layout1_title_style_ :: CairoFontStyle
 
layout1_bottom_axis_ :: LayoutAxis x
 
layout1_top_axis_ :: LayoutAxis x
 
layout1_left_axis_ :: LayoutAxis y
 
layout1_right_axis_ :: LayoutAxis y
 
layout1_yaxes_control_ :: ([y], [y]) -> ([y], [y])

Function to map points from the left/right plot to the left/right axes. The default value is id.

layout1_margin_ :: Double
 
layout1_plots_ :: [Either (Plot x y) (Plot x y)]
 
layout1_legend_ :: Maybe LegendStyle
 
layout1_grid_last_ :: Bool

True if the grid is to be rendered on top of the Plots.

Instances

(Ord x, Ord y) => ToRenderable (Layout1 x y) 

data LayoutAxis x Source

Constructors

LayoutAxis 

Fields

laxis_title_style_ :: CairoFontStyle
 
laxis_title_ :: String
 
laxis_style_ :: AxisStyle
 
laxis_visible_ :: [x] -> Bool

Function that determines whether an axis should be visible, based upon the points plotted on this axis. The default value is 'not.null'.

laxis_generate_ :: AxisFn x

Function that generates the axis data, based upon the points plotted. The default value is autoAxis.

laxis_override_ :: AxisData x -> AxisData x

Function that can be used to override the generated axis data. The default value is id.

laxis_reverse_ :: Bool

True if left to right (bottom to top) is to show descending values.

type MAxisFn t = [t] -> Maybe (AxisData t)Source

A MAxisFn is a function that generates an (optional) axis given the points plotted against that axis.

linkAxes :: ([a], [a]) -> ([a], [a])Source

independentAxes :: (a, b) -> (a, b)Source

updateAllAxesStyles :: (AxisStyle -> AxisStyle) -> Layout1 x y -> Layout1 x ySource

Helper to update all axis styles on a Layout1 simultaneously.

setLayout1Foreground :: AlphaColour Double -> Layout1 x y -> Layout1 x ySource

Helper to set the forground color uniformly on a Layout1.

laxis_visible :: forall x. T (LayoutAxis x) ([x] -> Bool)Source

layout1_title :: forall x y. T (Layout1 x y) StringSource

layout1_left_axis :: forall x y. T (Layout1 x y) (LayoutAxis y)Source

layout1_right_axis :: forall x y. T (Layout1 x y) (LayoutAxis y)Source

layout1_top_axis :: forall x y. T (Layout1 x y) (LayoutAxis x)Source

layout1_yaxes_control :: forall x y. T (Layout1 x y) (([y], [y]) -> ([y], [y]))Source

layout1_margin :: forall x y. T (Layout1 x y) DoubleSource

layout1_plots :: forall x y. T (Layout1 x y) [Either (Plot x y) (Plot x y)]Source

layout1_grid_last :: forall x y. T (Layout1 x y) BoolSource

renderLayout1sStacked :: Ord x => [AnyLayout1 x] -> Renderable ()Source

Render several layouts with the same abscissa type stacked so that their origins and axis titles are aligned horizontally with respect to each other. The exterior margins and background are taken from the first element.

data AnyLayout1 x Source

Encapsulates a Layout1 with a fixed abscissa type but arbitrary ordinate type.