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

Copyright(c) Tim Docker 2006 2014
LicenseBSD-style (see chart/COPYRIGHT)
Safe HaskellNone
LanguageHaskell98

Graphics.Rendering.Chart.Layout

Contents

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:

Synopsis

Types

data Layout x y Source #

A Layout value is a single plot area, with single x and y axis. The title is at the top and the legend at the bottom. It's parametrized by the types of values to be plotted on the x and y axes.

Constructors

Layout 

Fields

Instances

(PlotValue x, PlotValue y) => Default (Layout x y) Source #

Empty Layout without title and plots. The background is white and the grid is drawn beneath all plots. There will be a legend. The top and right axis will not be visible.

Methods

def :: Layout x y #

(Ord x, Ord y) => ToRenderable (Layout x y) Source # 

Methods

toRenderable :: Layout x y -> Renderable () Source #

data LayoutLR x y1 y2 Source #

A LayoutLR value is a single plot area, with an x axis and independent left and right y axes, with a title at the top; legend at the bottom. It's parametrized by the types of values to be plotted on the x and two y axes.

Constructors

LayoutLR 

Fields

Instances

(PlotValue x, PlotValue y1, PlotValue y2) => Default (LayoutLR x y1 y2) Source #

Empty LayoutLR without title and plots. The background is white and the grid is drawn beneath all plots. There will be a legend. The top axis will not be visible.

Methods

def :: LayoutLR x y1 y2 #

(Ord x, Ord yl, Ord yr) => ToRenderable (LayoutLR x yl yr) Source # 

Methods

toRenderable :: LayoutLR x yl yr -> Renderable () Source #

data LayoutAxis x Source #

Type of axis that is used in Layout and LayoutLR.

To generate the actual axis type (AxisData and AxisT) the _laxis_generate function is called and custom settings are applied with _laxis_override. Note that the AxisVisibility values in Layout and LayoutLR override visibility related settings of the axis.

Constructors

LayoutAxis 

Fields

Instances

data LayoutPick x y1 y2 Source #

Information on what is at a specifc location of a Layout or LayoutLR. This is delivered by the PickFn of a Renderable.

Constructors

LayoutPick_Legend String

A legend entry.

LayoutPick_Title String

The title.

LayoutPick_XTopAxisTitle String

The title of the top x axis.

LayoutPick_XBottomAxisTitle String

The title of the bottom x axis.

LayoutPick_YLeftAxisTitle String

The title of the left y axis.

LayoutPick_YRightAxisTitle String

The title of the right y axis.

LayoutPick_PlotArea x y1 y2

The plot area at the given plot coordinates.

LayoutPick_XTopAxis x

The top x axis at the given plot coordinate.

LayoutPick_XBottomAxis x

The bottom x axis at the given plot coordinate.

LayoutPick_YLeftAxis y1

The left y axis at the given plot coordinate.

LayoutPick_YRightAxis y2

The right y axis at the given plot coordinate.

Instances

(Show y2, Show y1, Show x) => Show (LayoutPick x y1 y2) Source # 

Methods

showsPrec :: Int -> LayoutPick x y1 y2 -> ShowS #

show :: LayoutPick x y1 y2 -> String #

showList :: [LayoutPick x y1 y2] -> ShowS #

data StackedLayouts x Source #

A container for a set of vertically StackedLayouts. The x axis of the different layouts will be aligned.

Constructors

StackedLayouts 

Fields

Instances

Default (StackedLayouts x) Source #

A empty StackedLayout with compressions applied.

Methods

def :: StackedLayouts x #

Ord x => ToRenderable (StackedLayouts x) Source # 

data StackedLayout x Source #

A layout with its y type hidden, so that it can be stacked with other layouts with differing y axis, but the same x axis. See StackedLayouts.

Constructors

Ord y => StackedLayout (Layout x y)

A Layout to stack.

(Ord yl, Ord yr) => StackedLayoutLR (LayoutLR x yl yr)

A LayoutLR to stack.

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.

Rendering

layoutToRenderable :: forall x y. (Ord x, Ord y) => Layout x y -> Renderable (LayoutPick x y y) Source #

Render the given Layout.

layoutToGrid :: forall x y. (Ord x, Ord y) => Layout x y -> Grid (Renderable (LayoutPick x y y)) Source #

layoutLRToRenderable :: forall x yl yr. (Ord x, Ord yl, Ord yr) => LayoutLR x yl yr -> Renderable (LayoutPick x yl yr) Source #

Render the given LayoutLR.

layoutLRToGrid :: forall x yl yr. (Ord x, Ord yl, Ord yr) => LayoutLR x yl yr -> Grid (Renderable (LayoutPick x yl yr)) Source #

renderStackedLayouts :: forall x. 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. See StackedLayouts for further information.

LayoutAxis lenses

Layout lenses

layout_title :: forall x y. Lens' (Layout x y) String Source #

layout_x_axis :: forall x y. Lens' (Layout x y) (LayoutAxis x) Source #

layout_y_axis :: forall x y. Lens' (Layout x y) (LayoutAxis y) Source #

layout_margin :: forall x y. Lens' (Layout x y) Double Source #

layout_plots :: forall x y. Lens' (Layout x y) [Plot x y] Source #

layout_grid_last :: forall x y. Lens' (Layout x y) Bool Source #

layout_axes_styles :: Setter' (Layout x y) AxisStyle Source #

Setter to update all axis styles on a Layout

layout_axes_title_styles :: Setter' (Layout x y) FontStyle Source #

Setter to update all the axes title styles on a Layout

layout_all_font_styles :: Setter' (Layout x y) FontStyle Source #

Setter to update all the font styles on a Layout

layout_foreground :: Setter' (Layout x y) (AlphaColour Double) Source #

Setter to update the foreground color of core chart elements on a Layout

LayoutLR lenses

layoutlr_background :: forall x y1 y2. Lens' (LayoutLR x y1 y2) FillStyle Source #

layoutlr_title :: forall x y1 y2. Lens' (LayoutLR x y1 y2) String Source #

layoutlr_title_style :: forall x y1 y2. Lens' (LayoutLR x y1 y2) FontStyle Source #

layoutlr_x_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis x) Source #

layoutlr_left_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis y1) Source #

layoutlr_right_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis y2) Source #

layoutlr_plots :: forall x y1 y2. Lens' (LayoutLR x y1 y2) [Either (Plot x y1) (Plot x y2)] Source #

layoutlr_legend :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (Maybe LegendStyle) Source #

layoutlr_margin :: forall x y1 y2. Lens' (LayoutLR x y1 y2) Double Source #

layoutlr_grid_last :: forall x y1 y2. Lens' (LayoutLR x y1 y2) Bool Source #

layoutlr_axes_styles :: Setter' (LayoutLR x y1 y2) AxisStyle Source #

Setter to update all axis styles on a LayoutLR

layoutlr_axes_title_styles :: Setter' (LayoutLR x y1 y2) FontStyle Source #

Setter to update all the axes title styles on a LayoutLR

layoutlr_all_font_styles :: Setter' (LayoutLR x y1 y2) FontStyle Source #

Setter to update all the font styles on a LayoutLR

layoutlr_foreground :: Setter' (LayoutLR x y1 y2) (AlphaColour Double) Source #

Setter to update the foreground color of core chart elements on a LayoutLR

StackedLayouts lenses