Copyright | (C) 2016 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 AxisStyle b v n
- class HasAxisStyle a b | a -> b where
- axisStyle :: Lens' a (AxisStyle b (V a) (N a))
- axisColourMap :: Lens' a ColourMap
- axisStyles :: IndexedTraversal' Int a (PlotStyle b (V a) (N a))
- fadedColours :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n
- vividColours :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n
- blackAndWhite :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n
- data PlotStyle b v n
- class HasPlotStyle f a b | a -> b where
- plotStyle :: LensLike' f a (PlotStyle b (V a) (N a))
- plotColour :: Functor f => LensLike' f a (Colour Double)
- plotColor :: Functor f => LensLike' f a (Colour Double)
- lineStyle :: Settable f => LensLike' f a (Style (V a) (N a))
- lineStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a))
- markerStyle :: Settable f => LensLike' f a (Style (V a) (N a))
- markerStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a))
- areaStyle :: Settable f => LensLike' f a (Style (V a) (N a))
- areaStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a))
- textStyle :: Settable f => LensLike' f a (Style (V a) (N a))
- textStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a))
- plotMarker :: Functor f => LensLike' f a (QDiagram b (V a) (N a) Any)
- plotStyles :: Settable f => LensLike' f a (Style (V a) (N a))
- plotStyleFunctions :: Applicative f => LensLike' f a (Colour Double -> Style (V a) (N a))
- applyLineStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t
- applyMarkerStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t
- applyAreaStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t
- applyTextStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t
- colours1 :: OrderedField n => [Colour n]
- colours2 :: OrderedField n => [Colour n]
- asterisk :: OrderedField n => Int -> n -> Path V2 n
- diamond :: (InSpace V2 n t, TrailLike t) => n -> t
- crossShape :: (InSpace V2 n t, TrailLike t) => n -> t
- star' :: (InSpace V2 n t, TrailLike t) => n -> t
- plus :: (InSpace V2 n t, TrailLike t) => n -> t
- lineMarkers :: OrderedField n => [Path V2 n]
- data ColourMap
- ixColour :: Double -> Lens' ColourMap (Colour Double)
- ixColourR :: Rational -> Lens' ColourMap (Colour Double)
- cmTraverse :: IndexedTraversal' Rational ColourMap (Colour Double)
- colourMap :: [(Rational, Colour Double)] -> ColourMap
- colourList :: ColourMap -> [(Rational, Colour Double)]
- toStops :: Fractional n => ColourMap -> [GradientStop n]
- data NanColours
- class HasNanColours a where
- nanColours :: Lens' a NanColours
- nanColour :: Lens' a (Colour Double)
- infColour :: Lens' a (Colour Double)
- negInfColour :: Lens' a (Colour Double)
- viridis :: ColourMap
- magma :: ColourMap
- inferno :: ColourMap
- plasma :: ColourMap
- greys :: ColourMap
The axis style
The AxisStyle
determines the Style
s of the plots in an axis.
There are various predefined styles to change the look of the plot.
Instances
class HasAxisStyle a b | a -> b where Source #
Class of things that have an AxisStyle
.
axisStyle :: Lens' a (AxisStyle b (V a) (N a)) Source #
Lens onto the AxisStyle
.
axisColourMap :: Lens' a ColourMap Source #
axisStyles :: IndexedTraversal' Int a (PlotStyle b (V a) (N a)) Source #
Instances
HasAxisStyle (Axis b v n) b Source # | |
HasAxisStyle (AxisStyle b v n) b Source # | |
Defined in Plots.Style |
Predefined styles
fadedColours :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n Source #
Theme using funColours
with faded fills and thick lines.
vividColours :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n Source #
Theme using funColours
with no lines on 'areaStyle.
blackAndWhite :: (TypeableFloat n, Renderable (Path V2 n) b) => AxisStyle b V2 n Source #
Theme without any colours, useful for black and white documents.
Plot Style
Plot styles are used to style each plot in an axis. Every Axis
comes with a list of plots styles (contained in the AxisStyle
)
which get applied the plots upon rendering.
You can either change the list of plot styles used with
axisStyle
:
stylishAxis = r2Axis &~ do axisStyle .= vividColours linePlot [(1,2) (3,4)] $ key "line 1" linePlot [(1,1) (4,2)] $ key "line 2"
change the style for individual plots when changing the plot state.
stylishAxis2 = r2Axis &~ do linePlot [(1,2) (3,4)] $ do key "line 1" plotColour .= green linePlot [(1,1) (4,2)] $ do key "line 2" plotColour .= orange
A plot style is made up of separate styles (lineStyle
,
markerStyle
, areaStyle
and textStyle
) a plotColour
and a
plotMarker
. When rendering a plot, the PlotStyle
s in an
AxisStyle
are used to style each plot. The lenses can be used to
customise each style when adding the plot.
plotColour
- the underlying colour of the plotlineStyle
- style used for lines (linePlot
,connectingLine
in ascatterPlot
)areaStyle
- style used for any area (barPlot
,piePlot
,histogramPlot
)markerStyle
- style used for markers inscatterPlot
plotMarker
- marker used inscatterPlot
Instances
class HasPlotStyle f a b | a -> b where Source #
Class for objects that contain a PlotStyle
.
plotStyle :: LensLike' f a (PlotStyle b (V a) (N a)) Source #
Lens onto the PlotStyle
.
plotColour :: Functor f => LensLike' f a (Colour Double) Source #
The plotColour
is the overall colour of the plot. This is passed
to the other styles (lineStyle
, markerStyle
etc.) to give an
overall colour for the plot.
plotColor :: Functor f => LensLike' f a (Colour Double) Source #
Alias for plotColour
.
lineStyle :: Settable f => LensLike' f a (Style (V a) (N a)) Source #
This style is applied to any plots made up of lines only (like
Path
plots). This is a less general version of
lineStyleFunction
.
lineStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a)) Source #
A version lineStyle
with access to the current plotColour
when applyLineStyle
is used.
markerStyle :: Settable f => LensLike' f a (Style (V a) (N a)) Source #
This style is applied to any markers in the plot (usually the
plotMarker
). This is a less general version of
markerStyleFunction
.
markerStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a)) Source #
A version lineStyle
with access to the current plotColour
when
applyMarkerStyle
is used.
areaStyle :: Settable f => LensLike' f a (Style (V a) (N a)) Source #
This style is applied to any filled areas in a plot (like
Bar
or Ribbon
). This is a less
general version of areaStyleFunction
.
areaStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a)) Source #
A version areaStyle
with access to the current plotColour
when
applyAreaStyle
is used.
textStyle :: Settable f => LensLike' f a (Style (V a) (N a)) Source #
This style is applied to text plots. This is a less general
version of textStyleFunction
.
textStyleFunction :: Functor f => LensLike' f a (Colour Double -> Style (V a) (N a)) Source #
A version textStyle
with access to the current plotColour
when
applyAreaStyle
is used.
plotMarker :: Functor f => LensLike' f a (QDiagram b (V a) (N a) Any) Source #
This diagram is used as any markers in a plot (like
Scatter
). The markerStyle
will be applied to this
marker when the plot gets rendered.
plotStyles :: Settable f => LensLike' f a (Style (V a) (N a)) Source #
A traversal over all the styles (lineStyle
, markerStyle
,
areaStyle
and textStyle
) of a PlotStyle
. This is a less
general version of plotStyleFunctions
.
plotStyleFunctions :: Applicative f => LensLike' f a (Colour Double -> Style (V a) (N a)) Source #
A version of plotStyles
with access to the plotColour
.
Instances
Applying Plot styles
applyLineStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t Source #
applyMarkerStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t Source #
Apply the markerStyle
from a PlotStyle
.
applyMarkerStyle :: (InSpace v n t, HasStyle t) => PlotStyle b v n -> t -> t
applyAreaStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t Source #
Apply the 'areaStyle from a PlotStyle
.
applyLineStyle :: (InSpace v n t, HasStyle t) => PlotStyle b v n -> t -> t
applyTextStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t Source #
Colour schemes
colours1 :: OrderedField n => [Colour n] Source #
A colourful colour set used for fadedColours
.
colours2 :: OrderedField n => [Colour n] Source #
Another colour set, used for vividColours
.
Marker shapes
asterisk :: OrderedField n => Int -> n -> Path V2 n Source #
Make an asterisk with n
spokes, each of length l
.
lineMarkers :: OrderedField n => [Path V2 n] Source #
asterisk
markers with varying numbers of prongs.
Colour maps
A map from a number (usually between 0 and 1) to a colour. Colour
maps are part of the AxisStyle
, which is used for plots like
HeatMap
.
Instances
Show ColourMap Source # | |
Transformable ColourMap Source # | |
Defined in Plots.Style | |
At ColourMap Source # | |
Ixed ColourMap Source # | |
Defined in Plots.Style | |
HasNanColours ColourMap Source # | |
Each ColourMap ColourMap (Colour Double) (Colour Double) Source # | |
type N ColourMap Source # | |
Defined in Plots.Style | |
type V ColourMap Source # | |
Defined in Plots.Style | |
type Index ColourMap Source # | |
Defined in Plots.Style | |
type IxValue ColourMap Source # | |
Defined in Plots.Style |
cmTraverse :: IndexedTraversal' Rational ColourMap (Colour Double) Source #
Indexed traversal over the colours indexed and ordered by their position in the map.
colourList :: ColourMap -> [(Rational, Colour Double)] Source #
Return the list of colours in the [0,1] range in order. This always includes colours 0 and 1.
toStops :: Fractional n => ColourMap -> [GradientStop n] Source #
data NanColours Source #
Colours to use when representing NaN
, Infinity
and -Infinity
.
Instances
Show NanColours Source # | |
Defined in Plots.Style showsPrec :: Int -> NanColours -> ShowS # show :: NanColours -> String # showList :: [NanColours] -> ShowS # | |
Default NanColours Source # | |
Defined in Plots.Style def :: NanColours # | |
HasNanColours NanColours Source # | |
Defined in Plots.Style |
class HasNanColours a where Source #
nanColours :: Lens' a NanColours Source #
Colours to use when displaying NaN
, Infinity
and -Infinity
.
nanColour :: Lens' a (Colour Double) Source #
Colour to use when displaying NaN
.
Default is 'white.
infColour :: Lens' a (Colour Double) Source #
Colour to use when displaying Infinity
.
Default is lime
.
negInfColour :: Lens' a (Colour Double) Source #
Colour to use when displaying -Infinity
.
Default is magenta
.
Instances
HasNanColours ColourMap Source # | |
HasNanColours NanColours Source # | |
Defined in Plots.Style |
Sample maps
The viridis colour map taken from https://bids.github.io/colormap/. This is the default colour map.
The magma colour map taken from https://bids.github.io/colormap/.
The inferno colour map taken from https://bids.github.io/colormap/.
The plasma colour map taken from https://bids.github.io/colormap/.