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

Safe HaskellNone

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 Lens) 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 :: Control.Lens.Lens' 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 :: FillStyle
 
_layout1_plot_background :: Maybe FillStyle
 
_layout1_title :: String
 
_layout1_title_style :: FontStyle
 
_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

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

data LayoutAxis x Source

Constructors

LayoutAxis 

Fields

_laxis_title_style :: FontStyle
 
_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.

Instances

data StackedLayouts x Source

A container for a set of vertically stacked layouts

Instances

data StackedLayout x Source

A layout with its y type hidden, so that it can be stacked with other layouts (with differing y types)

Constructors

forall y . Ord y => StackedLayout (Layout1 x y) 

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.

defaultLayout1 :: (PlotValue x, PlotValue y) => Layout1 x ySource

Deprecated: Use the according Data.Default instance!

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.

defaultLayoutAxis :: PlotValue t => LayoutAxis tSource

Deprecated: Use the according Data.Default instance!

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

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

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

defaultStackedLayouts :: StackedLayouts xSource

Deprecated: Use the according Data.Default instance!

renderStackedLayouts :: Ord x => StackedLayouts x -> Renderable ()Source

Render several layouts with the same x-axis type and range, vertically stacked so that their origins and x-values are aligned.

The legends from all the charts may be optionally combined, and shown once on the bottom chart. The x labels may be optionally removed so that they are only shown once.