plots-0.1.1.3: Diagrams based plotting library
Copyright(C) 2016 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Plots.Style

Description

This module defines the AxisStyle type along with different colour schemes. AxisStyles are used to provide default colours and shapes for the plots of an axis.

Synopsis

The axis style

data AxisStyle b v n Source #

The AxisStyle determines the Styles of the plots in an axis. There are various predefined styles to change the look of the plot.

Instances

Instances details
Applicative f => HasPlotStyle f (AxisStyle b v n) b Source # 
Instance details

Defined in Plots.Style

Methods

plotStyle :: LensLike' f (AxisStyle b v n) (PlotStyle b (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotColour :: LensLike' f (AxisStyle b v n) (Colour Double) Source #

plotColor :: LensLike' f (AxisStyle b v n) (Colour Double) Source #

lineStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

lineStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

markerStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

markerStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

areaStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

areaStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

textStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

textStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotMarker :: LensLike' f (AxisStyle b v n) (QDiagram b (V (AxisStyle b v n)) (N (AxisStyle b v n)) Any) Source #

plotStyles :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotStyleFunctions :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

HasAxisStyle (AxisStyle b v n) b Source # 
Instance details

Defined in Plots.Style

type N (AxisStyle b v n) Source # 
Instance details

Defined in Plots.Style

type N (AxisStyle b v n) = n
type V (AxisStyle b v n) Source # 
Instance details

Defined in Plots.Style

type V (AxisStyle b v n) = v

class HasAxisStyle a b | a -> b where Source #

Class of things that have an AxisStyle.

Minimal complete definition

axisStyle

Methods

axisStyle :: Lens' a (AxisStyle b (V a) (N a)) Source #

Lens onto the AxisStyle.

axisColourMap :: Lens' a ColourMap Source #

The ColourMap is used to draw the ColourBar and render plots like HeatMap.

axisStyles :: IndexedTraversal' Int a (PlotStyle b (V a) (N a)) Source #

Traversal over the PlotStyles in an AxisStyle. There are always an infinite number of PlotStyles in an AxisStyle.

Instances

Instances details
HasAxisStyle (Axis b v n) b Source # 
Instance details

Defined in Plots.Axis

Methods

axisStyle :: Lens' (Axis b v n) (AxisStyle b (V (Axis b v n)) (N (Axis b v n))) Source #

axisColourMap :: Lens' (Axis b v n) ColourMap Source #

axisStyles :: IndexedTraversal' Int (Axis b v n) (PlotStyle b (V (Axis b v n)) (N (Axis b v n))) Source #

HasAxisStyle (AxisStyle b v n) b Source # 
Instance details

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

data PlotStyle b v n Source #

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 PlotStyles 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 plot
  • lineStyle - style used for lines (linePlot, connectingLine in a scatterPlot)
  • areaStyle - style used for any area (barPlot, piePlot, histogramPlot)
  • markerStyle - style used for markers in scatterPlot
  • plotMarker - marker used in scatterPlot

Instances

Instances details
HasPlotStyle f (PlotStyle b v n) b Source # 
Instance details

Defined in Plots.Style

Methods

plotStyle :: LensLike' f (PlotStyle b v n) (PlotStyle b (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotColour :: LensLike' f (PlotStyle b v n) (Colour Double) Source #

plotColor :: LensLike' f (PlotStyle b v n) (Colour Double) Source #

lineStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

lineStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

markerStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

markerStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

areaStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

areaStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

textStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

textStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotMarker :: LensLike' f (PlotStyle b v n) (QDiagram b (V (PlotStyle b v n)) (N (PlotStyle b v n)) Any) Source #

plotStyles :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotStyleFunctions :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

(Metric v, Traversable v, OrderedField n) => Transformable (PlotStyle b v n) Source # 
Instance details

Defined in Plots.Style

Methods

transform :: Transformation (V (PlotStyle b v n)) (N (PlotStyle b v n)) -> PlotStyle b v n -> PlotStyle b v n #

type N (PlotStyle b v n) Source # 
Instance details

Defined in Plots.Style

type N (PlotStyle b v n) = n
type V (PlotStyle b v n) Source # 
Instance details

Defined in Plots.Style

type V (PlotStyle b v n) = v

class HasPlotStyle f a b | a -> b where Source #

Class for objects that contain a PlotStyle.

Minimal complete definition

plotStyle

Methods

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

Instances details
Settable f => HasPlotStyle f (Plot p b) b Source # 
Instance details

Defined in Plots.Types

Methods

plotStyle :: LensLike' f (Plot p b) (PlotStyle b (V (Plot p b)) (N (Plot p b))) Source #

plotColour :: LensLike' f (Plot p b) (Colour Double) Source #

plotColor :: LensLike' f (Plot p b) (Colour Double) Source #

lineStyle :: LensLike' f (Plot p b) (Style (V (Plot p b)) (N (Plot p b))) Source #

lineStyleFunction :: LensLike' f (Plot p b) (Colour Double -> Style (V (Plot p b)) (N (Plot p b))) Source #

markerStyle :: LensLike' f (Plot p b) (Style (V (Plot p b)) (N (Plot p b))) Source #

markerStyleFunction :: LensLike' f (Plot p b) (Colour Double -> Style (V (Plot p b)) (N (Plot p b))) Source #

areaStyle :: LensLike' f (Plot p b) (Style (V (Plot p b)) (N (Plot p b))) Source #

areaStyleFunction :: LensLike' f (Plot p b) (Colour Double -> Style (V (Plot p b)) (N (Plot p b))) Source #

textStyle :: LensLike' f (Plot p b) (Style (V (Plot p b)) (N (Plot p b))) Source #

textStyleFunction :: LensLike' f (Plot p b) (Colour Double -> Style (V (Plot p b)) (N (Plot p b))) Source #

plotMarker :: LensLike' f (Plot p b) (QDiagram b (V (Plot p b)) (N (Plot p b)) Any) Source #

plotStyles :: LensLike' f (Plot p b) (Style (V (Plot p b)) (N (Plot p b))) Source #

plotStyleFunctions :: LensLike' f (Plot p b) (Colour Double -> Style (V (Plot p b)) (N (Plot p b))) Source #

Settable f => HasPlotStyle f (Axis b c n) b Source # 
Instance details

Defined in Plots.Axis

Methods

plotStyle :: LensLike' f (Axis b c n) (PlotStyle b (V (Axis b c n)) (N (Axis b c n))) Source #

plotColour :: LensLike' f (Axis b c n) (Colour Double) Source #

plotColor :: LensLike' f (Axis b c n) (Colour Double) Source #

lineStyle :: LensLike' f (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

lineStyleFunction :: LensLike' f (Axis b c n) (Colour Double -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

markerStyle :: LensLike' f (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

markerStyleFunction :: LensLike' f (Axis b c n) (Colour Double -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

areaStyle :: LensLike' f (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

areaStyleFunction :: LensLike' f (Axis b c n) (Colour Double -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

textStyle :: LensLike' f (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

textStyleFunction :: LensLike' f (Axis b c n) (Colour Double -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

plotMarker :: LensLike' f (Axis b c n) (QDiagram b (V (Axis b c n)) (N (Axis b c n)) Any) Source #

plotStyles :: LensLike' f (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

plotStyleFunctions :: LensLike' f (Axis b c n) (Colour Double -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

Applicative f => HasPlotStyle f (AxisStyle b v n) b Source # 
Instance details

Defined in Plots.Style

Methods

plotStyle :: LensLike' f (AxisStyle b v n) (PlotStyle b (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotColour :: LensLike' f (AxisStyle b v n) (Colour Double) Source #

plotColor :: LensLike' f (AxisStyle b v n) (Colour Double) Source #

lineStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

lineStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

markerStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

markerStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

areaStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

areaStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

textStyle :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

textStyleFunction :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotMarker :: LensLike' f (AxisStyle b v n) (QDiagram b (V (AxisStyle b v n)) (N (AxisStyle b v n)) Any) Source #

plotStyles :: LensLike' f (AxisStyle b v n) (Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

plotStyleFunctions :: LensLike' f (AxisStyle b v n) (Colour Double -> Style (V (AxisStyle b v n)) (N (AxisStyle b v n))) Source #

HasPlotStyle f (PlotStyle b v n) b Source # 
Instance details

Defined in Plots.Style

Methods

plotStyle :: LensLike' f (PlotStyle b v n) (PlotStyle b (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotColour :: LensLike' f (PlotStyle b v n) (Colour Double) Source #

plotColor :: LensLike' f (PlotStyle b v n) (Colour Double) Source #

lineStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

lineStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

markerStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

markerStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

areaStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

areaStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

textStyle :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

textStyleFunction :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotMarker :: LensLike' f (PlotStyle b v n) (QDiagram b (V (PlotStyle b v n)) (N (PlotStyle b v n)) Any) Source #

plotStyles :: LensLike' f (PlotStyle b v n) (Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

plotStyleFunctions :: LensLike' f (PlotStyle b v n) (Colour Double -> Style (V (PlotStyle b v n)) (N (PlotStyle b v n))) Source #

Settable f => HasPlotStyle f (DynamicPlot b v n) b Source # 
Instance details

Defined in Plots.Types

Methods

plotStyle :: LensLike' f (DynamicPlot b v n) (PlotStyle b (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

plotColour :: LensLike' f (DynamicPlot b v n) (Colour Double) Source #

plotColor :: LensLike' f (DynamicPlot b v n) (Colour Double) Source #

lineStyle :: LensLike' f (DynamicPlot b v n) (Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

lineStyleFunction :: LensLike' f (DynamicPlot b v n) (Colour Double -> Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

markerStyle :: LensLike' f (DynamicPlot b v n) (Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

markerStyleFunction :: LensLike' f (DynamicPlot b v n) (Colour Double -> Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

areaStyle :: LensLike' f (DynamicPlot b v n) (Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

areaStyleFunction :: LensLike' f (DynamicPlot b v n) (Colour Double -> Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

textStyle :: LensLike' f (DynamicPlot b v n) (Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

textStyleFunction :: LensLike' f (DynamicPlot b v n) (Colour Double -> Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

plotMarker :: LensLike' f (DynamicPlot b v n) (QDiagram b (V (DynamicPlot b v n)) (N (DynamicPlot b v n)) Any) Source #

plotStyles :: LensLike' f (DynamicPlot b v n) (Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

plotStyleFunctions :: LensLike' f (DynamicPlot b v n) (Colour Double -> Style (V (DynamicPlot b v n)) (N (DynamicPlot b v n))) Source #

Settable f => HasPlotStyle f (PlotMods b v n) b Source # 
Instance details

Defined in Plots.Types

Methods

plotStyle :: LensLike' f (PlotMods b v n) (PlotStyle b (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

plotColour :: LensLike' f (PlotMods b v n) (Colour Double) Source #

plotColor :: LensLike' f (PlotMods b v n) (Colour Double) Source #

lineStyle :: LensLike' f (PlotMods b v n) (Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

lineStyleFunction :: LensLike' f (PlotMods b v n) (Colour Double -> Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

markerStyle :: LensLike' f (PlotMods b v n) (Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

markerStyleFunction :: LensLike' f (PlotMods b v n) (Colour Double -> Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

areaStyle :: LensLike' f (PlotMods b v n) (Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

areaStyleFunction :: LensLike' f (PlotMods b v n) (Colour Double -> Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

textStyle :: LensLike' f (PlotMods b v n) (Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

textStyleFunction :: LensLike' f (PlotMods b v n) (Colour Double -> Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

plotMarker :: LensLike' f (PlotMods b v n) (QDiagram b (V (PlotMods b v n)) (N (PlotMods b v n)) Any) Source #

plotStyles :: LensLike' f (PlotMods b v n) (Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

plotStyleFunctions :: LensLike' f (PlotMods b v n) (Colour Double -> Style (V (PlotMods b v n)) (N (PlotMods b v n))) Source #

Functor f => HasPlotStyle f (StyledPlot b v n) b Source # 
Instance details

Defined in Plots.Types

Methods

plotStyle :: LensLike' f (StyledPlot b v n) (PlotStyle b (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

plotColour :: LensLike' f (StyledPlot b v n) (Colour Double) Source #

plotColor :: LensLike' f (StyledPlot b v n) (Colour Double) Source #

lineStyle :: LensLike' f (StyledPlot b v n) (Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

lineStyleFunction :: LensLike' f (StyledPlot b v n) (Colour Double -> Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

markerStyle :: LensLike' f (StyledPlot b v n) (Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

markerStyleFunction :: LensLike' f (StyledPlot b v n) (Colour Double -> Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

areaStyle :: LensLike' f (StyledPlot b v n) (Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

areaStyleFunction :: LensLike' f (StyledPlot b v n) (Colour Double -> Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

textStyle :: LensLike' f (StyledPlot b v n) (Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

textStyleFunction :: LensLike' f (StyledPlot b v n) (Colour Double -> Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

plotMarker :: LensLike' f (StyledPlot b v n) (QDiagram b (V (StyledPlot b v n)) (N (StyledPlot b v n)) Any) Source #

plotStyles :: LensLike' f (StyledPlot b v n) (Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

plotStyleFunctions :: LensLike' f (StyledPlot b v n) (Colour Double -> Style (V (StyledPlot b v n)) (N (StyledPlot b v n))) Source #

Applying Plot styles

applyLineStyle :: (SameSpace a t, HasPlotStyle (Const (PlotStyle b (V a) (N a))) a b, HasStyle t) => a -> t -> t Source #

Apply the lineStyle from a PlotStyle.

applyLineStyle :: (InSpace v n t, HasStyle t) => PlotStyle b v n -> t -> t

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 #

Apply the textStyle from a PlotStyle.

applyTextStyle :: (InSpace v n t, HasStyle t) => PlotStyle b v n -> t -> t

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.

diamond :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A rotated square.

crossShape :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A rotated plus.

star' :: (InSpace V2 n t, TrailLike t) => n -> t Source #

A filled in five sided start of size x.

plus :: (InSpace V2 n t, TrailLike t) => n -> t Source #

Filled in + symbol.

lineMarkers :: OrderedField n => [Path V2 n] Source #

asterisk markers with varying numbers of prongs.

Colour maps

data ColourMap Source #

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

Instances details
Show ColourMap Source # 
Instance details

Defined in Plots.Style

Transformable ColourMap Source # 
Instance details

Defined in Plots.Style

At ColourMap Source #

Nothing == transparent

Instance details

Defined in Plots.Style

Ixed ColourMap Source # 
Instance details

Defined in Plots.Style

HasNanColours ColourMap Source # 
Instance details

Defined in Plots.Style

Each ColourMap ColourMap (Colour Double) (Colour Double) Source # 
Instance details

Defined in Plots.Style

type N ColourMap Source # 
Instance details

Defined in Plots.Style

type V ColourMap Source # 
Instance details

Defined in Plots.Style

type V ColourMap = V1
type Index ColourMap Source # 
Instance details

Defined in Plots.Style

type IxValue ColourMap Source # 
Instance details

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.

data NanColours Source #

Colours to use when representing NaN, Infinity and -Infinity.

class HasNanColours a where Source #

Minimal complete definition

nanColours

Methods

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.

Sample maps

viridis :: ColourMap Source #

The viridis colour map taken from https://bids.github.io/colormap/. This is the default colour map.

magma :: ColourMap Source #

The magma colour map taken from https://bids.github.io/colormap/.

inferno :: ColourMap Source #

The inferno colour map taken from https://bids.github.io/colormap/.

plasma :: ColourMap Source #

The plasma colour map taken from https://bids.github.io/colormap/.

greys :: ColourMap Source #

A colour map from black to white.