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_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])
- layout1_margin_ :: Double
- layout1_plots_ :: [Either (Plot x y) (Plot x y)]
- layout1_legend_ :: Maybe LegendStyle
- layout1_grid_last_ :: Bool
- data LayoutAxis x = LayoutAxis {
- laxis_title_style_ :: CairoFontStyle
- laxis_title_ :: String
- laxis_style_ :: AxisStyle
- laxis_visible_ :: [x] -> Bool
- laxis_generate_ :: AxisFn x
- laxis_override_ :: AxisData x -> AxisData x
- laxis_reverse_ :: Bool
- data Layout1Pick x y
- = L1P_Legend String
- | L1P_Title String
- | L1P_AxisTitle String
- | L1P_PlotArea x y y
- | L1P_BottomAxis x
- | L1P_TopAxis x
- | L1P_LeftAxis y
- | L1P_RightAxis y
- type MAxisFn t = [t] -> Maybe (AxisData t)
- defaultLayout1 :: (PlotValue x, PlotValue y) => Layout1 x y
- layout1ToRenderable :: (Ord x, Ord y) => Layout1 x y -> Renderable (Layout1Pick x y)
- linkAxes :: ([a], [a]) -> ([a], [a])
- independentAxes :: (a, b) -> (a, b)
- updateAllAxesStyles :: (AxisStyle -> AxisStyle) -> Layout1 x y -> Layout1 x y
- setLayout1Foreground :: AlphaColour Double -> Layout1 x y -> Layout1 x y
- defaultLayoutAxis :: PlotValue t => LayoutAxis t
- laxis_title_style :: forall x. T (LayoutAxis x) CairoFontStyle
- laxis_title :: forall x. T (LayoutAxis x) String
- laxis_style :: forall x. T (LayoutAxis x) AxisStyle
- laxis_visible :: forall x. T (LayoutAxis x) ([x] -> Bool)
- laxis_generate :: forall x. T (LayoutAxis x) (AxisFn x)
- laxis_override :: forall x. T (LayoutAxis x) (AxisData x -> AxisData x)
- laxis_reverse :: forall x. T (LayoutAxis x) Bool
- layout1_background :: forall x y. T (Layout1 x y) CairoFillStyle
- layout1_plot_background :: forall x y. T (Layout1 x y) (Maybe CairoFillStyle)
- layout1_title :: forall x y. T (Layout1 x y) String
- layout1_title_style :: forall x y. T (Layout1 x y) CairoFontStyle
- layout1_left_axis :: forall x y. T (Layout1 x y) (LayoutAxis y)
- layout1_right_axis :: forall x y. T (Layout1 x y) (LayoutAxis y)
- layout1_top_axis :: forall x y. T (Layout1 x y) (LayoutAxis x)
- layout1_bottom_axis :: forall x y. T (Layout1 x y) (LayoutAxis x)
- layout1_yaxes_control :: forall x y. T (Layout1 x y) (([y], [y]) -> ([y], [y]))
- layout1_margin :: forall x y. T (Layout1 x y) Double
- layout1_plots :: forall x y. T (Layout1 x y) [Either (Plot x y) (Plot x y)]
- layout1_legend :: forall x y. T (Layout1 x y) (Maybe LegendStyle)
- layout1_grid_last :: forall x y. T (Layout1 x y) Bool
- renderLayout1sStacked :: Ord x => [AnyLayout1 x] -> Renderable ()
- data AnyLayout1 x
- withAnyOrdinate :: (Ord x, Ord y) => Layout1 x y -> AnyLayout1 x
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
|
data Layout1Pick x y Source
Constructors
L1P_Legend String | |
L1P_Title String | |
L1P_AxisTitle String | |
L1P_PlotArea x y y | |
L1P_BottomAxis x | |
L1P_TopAxis x | |
L1P_LeftAxis y | |
L1P_RightAxis y |
Instances
(Show x, Show y) => Show (Layout1Pick 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
layout1ToRenderable :: (Ord x, Ord y) => Layout1 x y -> Renderable (Layout1Pick x y)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
laxis_title_style :: forall x. T (LayoutAxis x) CairoFontStyleSource
laxis_title :: forall x. T (LayoutAxis x) StringSource
laxis_style :: forall x. T (LayoutAxis x) AxisStyleSource
laxis_visible :: forall x. T (LayoutAxis x) ([x] -> Bool)Source
laxis_generate :: forall x. T (LayoutAxis x) (AxisFn x)Source
laxis_override :: forall x. T (LayoutAxis x) (AxisData x -> AxisData x)Source
laxis_reverse :: forall x. T (LayoutAxis x) BoolSource
layout1_background :: forall x y. T (Layout1 x y) CairoFillStyleSource
layout1_plot_background :: forall x y. T (Layout1 x y) (Maybe CairoFillStyle)Source
layout1_title :: forall x y. T (Layout1 x y) StringSource
layout1_title_style :: forall x y. T (Layout1 x y) CairoFontStyleSource
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_bottom_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_legend :: forall x y. T (Layout1 x y) (Maybe LegendStyle)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.
withAnyOrdinate :: (Ord x, Ord y) => Layout1 x y -> AnyLayout1 xSource