Copyright | (c) Tim Docker 2006, 2014 |
---|---|
License | BSD-style (see chart/COPYRIGHT) |
Safe Haskell | None |
Language | Haskell98 |
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:
- data Layout x y = Layout {
- _layout_background :: FillStyle
- _layout_plot_background :: Maybe FillStyle
- _layout_title :: String
- _layout_title_style :: FontStyle
- _layout_x_axis :: LayoutAxis x
- _layout_top_axis_visibility :: AxisVisibility
- _layout_bottom_axis_visibility :: AxisVisibility
- _layout_y_axis :: LayoutAxis y
- _layout_left_axis_visibility :: AxisVisibility
- _layout_right_axis_visibility :: AxisVisibility
- _layout_plots :: [Plot x y]
- _layout_legend :: Maybe LegendStyle
- _layout_margin :: Double
- _layout_grid_last :: Bool
- data LayoutLR x y1 y2 = LayoutLR {
- _layoutlr_background :: FillStyle
- _layoutlr_plot_background :: Maybe FillStyle
- _layoutlr_title :: String
- _layoutlr_title_style :: FontStyle
- _layoutlr_x_axis :: LayoutAxis x
- _layoutlr_top_axis_visibility :: AxisVisibility
- _layoutlr_bottom_axis_visibility :: AxisVisibility
- _layoutlr_left_axis :: LayoutAxis y1
- _layoutlr_left_axis_visibility :: AxisVisibility
- _layoutlr_right_axis :: LayoutAxis y2
- _layoutlr_right_axis_visibility :: AxisVisibility
- _layoutlr_plots :: [Either (Plot x y1) (Plot x y2)]
- _layoutlr_legend :: Maybe LegendStyle
- _layoutlr_margin :: Double
- _layoutlr_grid_last :: Bool
- data LayoutAxis x = LayoutAxis {
- _laxis_title_style :: FontStyle
- _laxis_title :: String
- _laxis_style :: AxisStyle
- _laxis_generate :: AxisFn x
- _laxis_override :: AxisData x -> AxisData x
- _laxis_reverse :: Bool
- data LayoutPick x y1 y2
- = LayoutPick_Legend String
- | LayoutPick_Title String
- | LayoutPick_XTopAxisTitle String
- | LayoutPick_XBottomAxisTitle String
- | LayoutPick_YLeftAxisTitle String
- | LayoutPick_YRightAxisTitle String
- | LayoutPick_PlotArea x y1 y2
- | LayoutPick_XTopAxis x
- | LayoutPick_XBottomAxis x
- | LayoutPick_YLeftAxis y1
- | LayoutPick_YRightAxis y2
- data StackedLayouts x = StackedLayouts {}
- data StackedLayout x
- = forall y . Ord y => StackedLayout (Layout x y)
- | forall yl yr . (Ord yl, Ord yr) => StackedLayoutLR (LayoutLR x yl yr)
- type MAxisFn t = [t] -> Maybe (AxisData t)
- layoutToRenderable :: forall x y. (Ord x, Ord y) => Layout x y -> Renderable (LayoutPick x y y)
- layoutLRToRenderable :: forall x yl yr. (Ord x, Ord yl, Ord yr) => LayoutLR x yl yr -> Renderable (LayoutPick x yl yr)
- renderStackedLayouts :: forall x. Ord x => StackedLayouts x -> Renderable ()
- laxis_title_style :: forall x. Lens' (LayoutAxis x) FontStyle
- laxis_title :: forall x. Lens' (LayoutAxis x) String
- laxis_style :: forall x. Lens' (LayoutAxis x) AxisStyle
- laxis_generate :: forall x. Lens' (LayoutAxis x) (AxisFn x)
- laxis_override :: forall x. Lens' (LayoutAxis x) (AxisData x -> AxisData x)
- laxis_reverse :: forall x. Lens' (LayoutAxis x) Bool
- layout_background :: forall x y. Lens' (Layout x y) FillStyle
- layout_plot_background :: forall x y. Lens' (Layout x y) (Maybe FillStyle)
- layout_title :: forall x y. Lens' (Layout x y) String
- layout_title_style :: forall x y. Lens' (Layout x y) FontStyle
- layout_x_axis :: forall x y. Lens' (Layout x y) (LayoutAxis x)
- layout_top_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility
- layout_bottom_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility
- layout_y_axis :: forall x y. Lens' (Layout x y) (LayoutAxis y)
- layout_left_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility
- layout_right_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility
- layout_margin :: forall x y. Lens' (Layout x y) Double
- layout_plots :: forall x y. Lens' (Layout x y) [Plot x y]
- layout_legend :: forall x y. Lens' (Layout x y) (Maybe LegendStyle)
- layout_grid_last :: forall x y. Lens' (Layout x y) Bool
- layout_axes_styles :: Setter' (Layout x y) AxisStyle
- layout_axes_title_styles :: Setter' (Layout x y) FontStyle
- layout_all_font_styles :: Setter' (Layout x y) FontStyle
- layout_foreground :: Setter' (Layout x y) (AlphaColour Double)
- layoutlr_background :: forall x y1 y2. Lens' (LayoutLR x y1 y2) FillStyle
- layoutlr_plot_background :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (Maybe FillStyle)
- layoutlr_title :: forall x y1 y2. Lens' (LayoutLR x y1 y2) String
- layoutlr_title_style :: forall x y1 y2. Lens' (LayoutLR x y1 y2) FontStyle
- layoutlr_x_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis x)
- layoutlr_top_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
- layoutlr_bottom_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
- layoutlr_left_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis y1)
- layoutlr_right_axis :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (LayoutAxis y2)
- layoutlr_left_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
- layoutlr_right_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility
- layoutlr_plots :: forall x y1 y2. Lens' (LayoutLR x y1 y2) [Either (Plot x y1) (Plot x y2)]
- layoutlr_legend :: forall x y1 y2. Lens' (LayoutLR x y1 y2) (Maybe LegendStyle)
- layoutlr_margin :: forall x y1 y2. Lens' (LayoutLR x y1 y2) Double
- layoutlr_grid_last :: forall x y1 y2. Lens' (LayoutLR x y1 y2) Bool
- layoutlr_axes_styles :: Setter' (LayoutLR x y1 y2) AxisStyle
- layoutlr_axes_title_styles :: Setter' (LayoutLR x y1 y2) FontStyle
- layoutlr_all_font_styles :: Setter' (LayoutLR x y1 y2) FontStyle
- layoutlr_foreground :: Setter' (LayoutLR x y1 y2) (AlphaColour Double)
- slayouts_layouts :: forall x x. Lens (StackedLayouts x) (StackedLayouts x) [StackedLayout x] [StackedLayout x]
- slayouts_compress_legend :: forall x. Lens' (StackedLayouts x) Bool
Types
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.
Layout | |
|
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.
LayoutLR | |
|
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.
LayoutAxis | |
|
PlotValue t => Default (LayoutAxis t) |
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
.
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. |
(Show x, Show y1, Show y2) => Show (LayoutPick x y1 y2) |
data StackedLayouts x Source
A container for a set of vertically StackedLayout
s.
The x axis of the different layouts will be aligned.
StackedLayouts | |
|
Default (StackedLayouts x) | A empty |
Ord x => ToRenderable (StackedLayouts x) |
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
.
forall y . Ord y => StackedLayout (Layout x y) | A |
forall yl yr . (Ord yl, Ord yr) => StackedLayoutLR (LayoutLR x yl yr) | A |
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
.
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
.
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
laxis_title_style :: forall x. Lens' (LayoutAxis x) FontStyle Source
laxis_title :: forall x. Lens' (LayoutAxis x) String Source
laxis_style :: forall x. Lens' (LayoutAxis x) AxisStyle Source
laxis_generate :: forall x. Lens' (LayoutAxis x) (AxisFn x) Source
laxis_override :: forall x. Lens' (LayoutAxis x) (AxisData x -> AxisData x) Source
laxis_reverse :: forall x. Lens' (LayoutAxis x) Bool Source
Layout lenses
layout_background :: forall x y. Lens' (Layout x y) FillStyle Source
layout_title :: forall x y. Lens' (Layout x y) String Source
layout_title_style :: forall x y. Lens' (Layout x y) FontStyle Source
layout_x_axis :: forall x y. Lens' (Layout x y) (LayoutAxis x) Source
layout_top_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility Source
layout_bottom_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility Source
layout_y_axis :: forall x y. Lens' (Layout x y) (LayoutAxis y) Source
layout_left_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility Source
layout_right_axis_visibility :: forall x y. Lens' (Layout x y) AxisVisibility 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_legend :: forall x y. Lens' (Layout x y) (Maybe LegendStyle) 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_top_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility Source
layoutlr_bottom_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility 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_left_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility Source
layoutlr_right_axis_visibility :: forall x y1 y2. Lens' (LayoutLR x y1 y2) AxisVisibility 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
slayouts_layouts :: forall x x. Lens (StackedLayouts x) (StackedLayouts x) [StackedLayout x] [StackedLayout x] Source
slayouts_compress_legend :: forall x. Lens' (StackedLayouts x) Bool Source