Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- data Axis b c n
- axes :: (v ~ BaseSpace c, v ~ BaseSpace c') => Lens (Axis b c n) (Axis b c' n) (c (SingleAxis b v n)) (c' (SingleAxis b v n))
- axisPlots :: BaseSpace c ~ v => Lens' (Axis b c n) [DynamicPlot b v n]
- currentPlots :: BaseSpace c ~ v => Traversal' (Axis b c n) (DynamicPlot b v n)
- finalPlots :: BaseSpace c ~ v => Setter' (Axis b c n) (StyledPlot b v n)
- plotModifier :: BaseSpace c ~ v => Lens' (Axis b c n) (Endo (StyledPlot b v n))
- axisSize :: (HasLinearMap c, Num n, Ord n) => Lens' (Axis b c n) (SizeSpec c n)
- colourBarRange :: Lens' (Axis b v n) (n, n)
- r2Axis :: (TypeableFloat n, Renderable (Text n) b, Renderable (Path V2 n) b) => Axis b V2 n
- polarAxis :: (TypeableFloat n, Renderable (Text n) b, Renderable (Path V2 n) b) => Axis b Polar n
- type family BaseSpace (c :: Type -> Type) :: Type -> Type
- addPlot :: (InSpace (BaseSpace c) n p, MonadState (Axis b c n) m, Plotable p b) => Plot p b -> m ()
- addPlotable :: (InSpace (BaseSpace c) n p, MonadState (Axis b c n) m, Plotable p b) => p -> State (Plot p b) () -> m ()
- addPlotable' :: (InSpace (BaseSpace v) n p, MonadState (Axis b v n) m, Plotable p b) => p -> m ()
- data SingleAxis b v n
- xAxis :: R1 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n)
- xLabel :: R1 c => Lens' (Axis b c n) String
- xMin :: R1 c => Lens' (Axis b c n) (Maybe n)
- xMax :: R1 c => Lens' (Axis b c n) (Maybe n)
- yAxis :: R2 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n)
- yLabel :: R2 c => Lens' (Axis b c n) String
- yMin :: R2 c => Lens' (Axis b c n) (Maybe n)
- yMax :: R2 c => Lens' (Axis b c n) (Maybe n)
- rAxis :: Radial c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n)
- rLabel :: Radial c => Lens' (Axis b c n) String
- rMax :: Radial c => Lens' (Axis b c n) (Maybe n)
- thetaAxis :: Circle c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n)
- thetaLabel :: Circle c => Lens' (Axis b c n) String
- zAxis :: R3 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n)
- zLabel :: R3 c => Lens' (Axis b c n) String
- zMin :: R3 c => Lens' (Axis b c n) (Maybe n)
- zMax :: R3 c => Lens' (Axis b c n) (Maybe n)
Axis type
Axis is the data type that holds all the necessary information to render
a plot. Common LensLike
s used for the axis (see haddock's
instances for a more comprehensive list):
axisStyle
- customise theAxisStyle
legend
- customise theLegend
colourBar
- customise theColourBar
currentPlots
- current plots in theAxis
finalPlots
- changes to the plots just before renderingaxes
- changes to eachSingleAxis
The following LensLike
s 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 theMinorTicks
tickLabel
- customise theTickLabels
minorTicks
- customise theMinorTicks
majorTicks
- customise theMajorTicks
gridLines
- customise theGridLines
axisLine
- customise theAxisLine
axisScaling
- 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 b c n) (Axis b c' n) (c (SingleAxis b v n)) (c' (SingleAxis b v n)) Source #
Lens onto the separate axes of an axis. Allows changing the
coordinate system as long as the BaseSpace
is the same.
axes
::Lens'
(Axis
b c n) (c (SingleAxis
b v n))
axisPlots :: BaseSpace c ~ v => Lens' (Axis b c n) [DynamicPlot b v n] Source #
The list of plots currently in the axis.
currentPlots :: BaseSpace c ~ v => Traversal' (Axis b c n) (DynamicPlot b v n) Source #
Traversal over the current plots in the axis.
For example, to make all ScatterPlot
s currently in the axis use a
connectingLine
, you can write
finalPlots
.connectingLine
.=True
finalPlots :: BaseSpace c ~ v => Setter' (Axis b c n) (StyledPlot b v n) Source #
Setter over the final plot before the axis is rendered.
For example, to make all ScatterPlot
s 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 b c n) (Endo (StyledPlot b v n)) 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, Num n, Ord n) => Lens' (Axis b c n) (SizeSpec c n) Source #
The size used for the rendered axis.
colourBarRange :: Lens' (Axis b v n) (n, n) Source #
The range used for the colour bar limits. This is automatically set
when using heatMap
or heatMap'
Predefined axes
r2Axis :: (TypeableFloat n, Renderable (Text n) b, Renderable (Path V2 n) b) => Axis b V2 n Source #
The default axis for plots in the V2
coordinate system.
polarAxis :: (TypeableFloat n, Renderable (Text n) b, Renderable (Path V2 n) b) => Axis b Polar n Source #
Base space
type family BaseSpace (c :: Type -> Type) :: Type -> Type 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 V2 Source # | |
Defined in Plots.Axis | |
type BaseSpace V3 Source # | |
Defined in Plots.Axis | |
type BaseSpace Polar Source # | |
Defined in Plots.Axis |
Axis plots
:: (InSpace (BaseSpace v) n p, MonadState (Axis b v n) m, Plotable p b) | |
=> p | the raw plot |
-> m () | add plot to the |
Simple version of AddPlotable
without any changes Plot
.
Single axis
data SingleAxis b v n Source #
Render information for a single axis line.
Instances
Specific axes
x-axis
xAxis :: R1 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n) Source #
Lens onto the x-axis of an Axis
.
xLabel :: R1 c => Lens' (Axis b c n) String Source #
The label for the x-axis. Shorthand for
.xAxis
. axisLabelText
y-axis
yAxis :: R2 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n) Source #
Lens onto the y-axis of an Axis
.
yLabel :: R2 c => Lens' (Axis b c n) String Source #
The label for the y-axis. Shorthand for
.yAxis
. axisLabelText
r-axis
rAxis :: Radial c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n) Source #
Lens onto the radial axis of an Axis
.
rLabel :: Radial c => Lens' (Axis b c n) String Source #
The label for the radial axis. Shorthand for
.rAxis
. axisLabelText
rMax :: Radial c => Lens' (Axis b c n) (Maybe n) 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 b c n) (Maybe n)
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 b c n) (SingleAxis b (BaseSpace c) n) Source #
Lens onto the radial axis of an Axis
.
thetaLabel :: Circle c => Lens' (Axis b c n) String Source #
The label for the radial axis. Shorthand for
.rAxis
. axisLabelText
z-axis
zAxis :: R3 c => Lens' (Axis b c n) (SingleAxis b (BaseSpace c) n) Source #
Lens onto the z-axis of an Axis
.
zLabel :: R3 c => Lens' (Axis b c n) String Source #
The label for the z-axis. Shorthand for
.zAxis
. axisLabelText