| Copyright | (C) 2015 Christopher Chalmers |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Christopher Chalmers |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell2010 |
Plots.Axis
Contents
Description
The Axis is the main data type for "plots". It holds all the
necessary infomation to be rendered into a Diagram.
Synopsis
- data Axis c
- axes :: (v ~ BaseSpace c, v ~ BaseSpace c') => Lens (Axis c) (Axis c') (c (SingleAxis v)) (c' (SingleAxis v))
- axisPlots :: BaseSpace c ~ v => Lens' (Axis c) [DynamicPlot v]
- currentPlots :: BaseSpace c ~ v => Traversal' (Axis c) (DynamicPlot v)
- finalPlots :: BaseSpace c ~ v => Setter' (Axis c) (StyledPlot v)
- plotModifier :: BaseSpace c ~ v => Lens' (Axis c) (Endo (StyledPlot v))
- axisSize :: HasLinearMap c => Lens' (Axis c) (SizeSpec c Double)
- colourBarRange :: Lens' (Axis v) (Double, Double)
- r2Axis :: Axis V2
- r3Axis :: Axis V3
- polarAxis :: Axis Polar
- type family BaseSpace (c :: * -> *) :: * -> *
- addPlot :: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p) => Plot p -> m ()
- addPlotable :: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c)) => p -> State (Plot p) () -> m ()
- addPlotable' :: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c)) => p -> m ()
- data SingleAxis v
- xAxis :: R1 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
- xLabel :: R1 c => Lens' (Axis c) String
- xMin :: R1 c => Lens' (Axis c) (Maybe Double)
- xMax :: R1 c => Lens' (Axis c) (Maybe Double)
- yAxis :: R2 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
- yLabel :: R2 c => Lens' (Axis c) String
- yMin :: R2 c => Lens' (Axis c) (Maybe Double)
- yMax :: R2 c => Lens' (Axis c) (Maybe Double)
- rAxis :: Radial c => Lens' (Axis c) (SingleAxis (BaseSpace c))
- rLabel :: Radial c => Lens' (Axis c) String
- rMax :: Radial c => Lens' (Axis c) (Maybe Double)
- thetaAxis :: Circle c => Lens' (Axis c) (SingleAxis (BaseSpace c))
- thetaLabel :: Circle c => Lens' (Axis c) String
- zAxis :: R3 c => Lens' (Axis c) (SingleAxis (BaseSpace c))
- zLabel :: R3 c => Lens' (Axis c) String
- zMin :: R3 c => Lens' (Axis c) (Maybe Double)
- zMax :: R3 c => Lens' (Axis c) (Maybe Double)
Axis type
Axis is the data type that holds all the necessary information to render
a plot. Common LensLikes used for the axis (see haddock's
instances for a more comprehensive list):
axisStyle- customise theAxisStylelegend- customise theLegendcolourBar- customise theColourBarcurrentPlots- current plots in theAxisfinalPlots- changes to the plots just before renderingaxes- changes to eachSingleAxis
The following LensLikes can be used on the on all the axes by
applying it the to Axis or can be used on a SingleAxis by using
it in combination with a specific axis (like xAxis).
axisLabel- customise theMinorTickstickLabel- customise theTickLabelsminorTicks- customise theMinorTicksmajorTicks- customise theMajorTicksgridLines- customise theGridLinesaxisLine- customise theAxisLineaxisScaling- customise theAxisScaling
Plots are usually added to the axis using specific functions for
those plots ('Plots.Types.Line.linePlot, barPlot).
These functions use addPlotable to add the plot to the axis.
Instances
axes :: (v ~ BaseSpace c, v ~ BaseSpace c') => Lens (Axis c) (Axis c') (c (SingleAxis v)) (c' (SingleAxis v)) Source #
Lens onto the separate axes of an axis. Allows changing the
coordinate system as long as the BaseSpace is the same.
axes::Lens'(Axisc) (c (SingleAxisv))
axisPlots :: BaseSpace c ~ v => Lens' (Axis c) [DynamicPlot v] Source #
The list of plots currently in the axis.
currentPlots :: BaseSpace c ~ v => Traversal' (Axis c) (DynamicPlot v) Source #
Traversal over the current plots in the axis.
For example, to make all ScatterPlots currently in the axis use a
connectingLine, you can write
finalPlots.connectingLine.=True
finalPlots :: BaseSpace c ~ v => Setter' (Axis c) (StyledPlot v) Source #
Setter over the final plot before the axis is rendered.
For example, to make all ScatterPlots in the axis use a
connectingLine (both currently in the axis and ones added later),
you can add
finalPlots.connectingLine.=True
plotModifier :: BaseSpace c ~ v => Lens' (Axis c) (Endo (StyledPlot v)) Source #
Lens onto the modifier set by finalPlots. This gets applied to
all plots in the axis, just before they are rendered.
axisSize :: HasLinearMap c => Lens' (Axis c) (SizeSpec c Double) Source #
The size used for the rendered axis.
colourBarRange :: Lens' (Axis v) (Double, Double) Source #
The range used for the colour bar limits. This is automatically set
when using heatMap or heatMap'
Predefined axes
Base space
type family BaseSpace (c :: * -> *) :: * -> * Source #
This family is used so that we can say (Axis Polar) but use V2 for the underlying diagram.
Instances
| type BaseSpace Complex Source # | |
Defined in Plots.Axis | |
| type BaseSpace V3 Source # | |
Defined in Plots.Axis | |
| type BaseSpace V2 Source # | |
Defined in Plots.Axis | |
| type BaseSpace Polar Source # | |
Defined in Plots.Axis | |
Axis plots
Arguments
| :: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c)) | |
| => p | the raw plot |
| -> m () | add plot to the |
Simple version of AddPlotable without any changes Plot.
Single axis
data SingleAxis v Source #
Render information for a single axis line.
Instances
Specific axes
x-axis
xLabel :: R1 c => Lens' (Axis c) String Source #
The label for the x-axis. Shorthand for .xAxis . axisLabelText
y-axis
yLabel :: R2 c => Lens' (Axis c) String Source #
The label for the y-axis. Shorthand for .yAxis . axisLabelText
r-axis
rAxis :: Radial c => Lens' (Axis c) (SingleAxis (BaseSpace c)) Source #
Lens onto the radial axis of an Axis.
rLabel :: Radial c => Lens' (Axis c) String Source #
The label for the radial axis. Shorthand for .rAxis . axisLabelText
rMax :: Radial c => Lens' (Axis c) (Maybe Double) Source #
The minimum z value for the axis. If the value if Nothing (the
Default), the bounds will be infered by the plots in the axis.
rMin :: R3 c => Lens' (Axis c) (Maybe Double)
rMin = zAxis . boundMin
The minimum radial value for the axis. If the value if Nothing
(the Default), the bounds will be infered by the plots in the
axis.
theta-axis
thetaAxis :: Circle c => Lens' (Axis c) (SingleAxis (BaseSpace c)) Source #
Lens onto the radial axis of an Axis.
thetaLabel :: Circle c => Lens' (Axis c) String Source #
The label for the radial axis. Shorthand for .rAxis . axisLabelText
z-axis
zLabel :: R3 c => Lens' (Axis c) String Source #
The label for the z-axis. Shorthand for .zAxis . axisLabelText