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
- data Layout1 x y = Layout1 {
- layout1_background_ :: 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_margin_ :: Double
- layout1_plots_ :: [(String, Either (Plot x y) (Plot x y))]
- layout1_legend_ :: Maybe LegendStyle
- layout1_grid_last_ :: Bool
- data LayoutAxis x = LayoutAxis {}
- type MAxisFn t = [t] -> Maybe (AxisData t)
- defaultLayout1 :: (PlotValue x, PlotValue y) => Layout1 x y
- mAxis :: PlotValue t => AxisFn t -> MAxisFn t
- noAxis :: PlotValue t => LayoutAxis t
- updateAllAxesStyles :: (AxisStyle -> AxisStyle) -> Layout1 x y -> Layout1 x y
- updateXAxesData :: (MAxisFn x -> MAxisFn x) -> Layout1 x y -> Layout1 x y
- updateYAxesData :: (MAxisFn y -> MAxisFn y) -> Layout1 x y -> Layout1 x y
- setForeground :: Color -> Layout1 x y -> Layout1 x y
- laxis_title_style :: forall x[ayyK]. T (LayoutAxis x[ayyK]) CairoFontStyle
- laxis_title :: forall x[ayyK]. T (LayoutAxis x[ayyK]) String
- laxis_style :: forall x[ayyK]. T (LayoutAxis x[ayyK]) AxisStyle
- laxis_data :: forall x[ayyK]. T (LayoutAxis x[ayyK]) (MAxisFn x[ayyK])
- laxis_reverse :: forall x[ayyK]. T (LayoutAxis x[ayyK]) Bool
- layout1_background :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) CairoFillStyle
- layout1_title :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) String
- layout1_title_style :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) CairoFontStyle
- layout1_left_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis y[ayyJ])
- layout1_right_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis y[ayyJ])
- layout1_top_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis x[ayyI])
- layout1_bottom_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis x[ayyI])
- layout1_margin :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) Double
- layout1_plots :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) ([] ((,) String (Either (Plot x[ayyI] y[ayyJ]) (Plot x[ayyI] y[ayyJ]))))
- layout1_legend :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (Maybe LegendStyle)
- layout1_grid_last :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) Bool
Documentation
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
|
Instances
(Ord x, Ord y) => ToRenderable (Layout1 x y) |
data LayoutAxis x Source
Constructors
LayoutAxis | |
Fields
|
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
mAxis :: PlotValue t => AxisFn t -> MAxisFn tSource
Create an axis when there are points to be plotted against it.
noAxis :: PlotValue t => LayoutAxis tSource
Never create an axis
updateAllAxesStyles :: (AxisStyle -> AxisStyle) -> Layout1 x y -> Layout1 x ySource
Helper to update all axis styles on a Layout1 simultaneously
updateXAxesData :: (MAxisFn x -> MAxisFn x) -> Layout1 x y -> Layout1 x ySource
Helper to update data member of both horizontal axes in a Layout1
updateYAxesData :: (MAxisFn y -> MAxisFn y) -> Layout1 x y -> Layout1 x ySource
Helper to update data member of both vertical axes in a Layout1
setForeground :: Color -> Layout1 x y -> Layout1 x ySource
Helper to set the forground color uniformly on a Layout1
laxis_title_style :: forall x[ayyK]. T (LayoutAxis x[ayyK]) CairoFontStyleSource
laxis_title :: forall x[ayyK]. T (LayoutAxis x[ayyK]) StringSource
laxis_style :: forall x[ayyK]. T (LayoutAxis x[ayyK]) AxisStyleSource
laxis_data :: forall x[ayyK]. T (LayoutAxis x[ayyK]) (MAxisFn x[ayyK])Source
laxis_reverse :: forall x[ayyK]. T (LayoutAxis x[ayyK]) BoolSource
layout1_background :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) CairoFillStyleSource
layout1_title :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) StringSource
layout1_title_style :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) CairoFontStyleSource
layout1_left_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis y[ayyJ])Source
layout1_right_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis y[ayyJ])Source
layout1_top_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis x[ayyI])Source
layout1_bottom_axis :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (LayoutAxis x[ayyI])Source
layout1_margin :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) DoubleSource
layout1_plots :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) ([] ((,) String (Either (Plot x[ayyI] y[ayyJ]) (Plot x[ayyI] y[ayyJ]))))Source
layout1_legend :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) (Maybe LegendStyle)Source
layout1_grid_last :: forall x[ayyI] y[ayyJ]. T (Layout1 x[ayyI] y[ayyJ]) BoolSource