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

Plots.Axis

Description

The Axis is the main data type for "plots". It holds all the necessary infomation to be rendered into a Diagram.

Synopsis

Axis type

data Axis b c n Source #

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):

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).

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

Instances details
(Applicative f, Traversable c) => HasGridLines f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

gridLines :: LensLike' f (Axis b c n) (GridLines (V (Axis b c n)) (N (Axis b c n))) Source #

(Applicative f, Traversable c) => HasMajorGridLines f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

majorGridLines :: LensLike' f (Axis b c n) (MajorGridLines (V (Axis b c n)) (N (Axis b c n))) Source #

majorGridLinesFunction :: LensLike' f (Axis b c n) (GridLineFunction (N (Axis b c n))) Source #

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

(Applicative f, Traversable c) => HasMinorGridLines f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

minorGridLines :: LensLike' f (Axis b c n) (MinorGridLines (V (Axis b c n)) (N (Axis b c n))) Source #

minorGridLinesFunction :: LensLike' f (Axis b c n) (GridLineFunction (N (Axis b c n))) Source #

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

(Applicative f, Traversable c) => HasAxisScaling f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

axisScaling :: LensLike' f (Axis b c n) (AxisScaling (N (Axis b c n))) Source #

scaleAspectRatio :: LensLike' f (Axis b c n) (Maybe (N (Axis b c n))) Source #

scaleMode :: LensLike' f (Axis b c n) ScaleMode Source #

logScale :: LensLike' f (Axis b c n) LogScale Source #

axisExtend :: LensLike' f (Axis b c n) (Extending (N (Axis b c n))) Source #

boundMin :: LensLike' f (Axis b c n) (Maybe (N (Axis b c n))) Source #

boundMax :: LensLike' f (Axis b c n) (Maybe (N (Axis b c n))) Source #

renderSize :: LensLike' f (Axis b c n) (Maybe (N (Axis b c n))) Source #

(Applicative f, Traversable c) => HasMajorTicks f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

majorTicks :: LensLike' f (Axis b c n) (MajorTicks (V (Axis b c n)) (N (Axis b c n))) Source #

majorTicksFunction :: LensLike' f (Axis b c n) ((N (Axis b c n), N (Axis b c n)) -> [N (Axis b c n)]) Source #

majorTicksAlignment :: LensLike' f (Axis b c n) TicksAlignment Source #

majorTicksLength :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

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

(Applicative f, Traversable c) => HasMinorTicks f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

minorTicks :: LensLike' f (Axis b c n) (MinorTicks (V (Axis b c n)) (N (Axis b c n))) Source #

minorTicksFunction :: LensLike' f (Axis b c n) ([N (Axis b c n)] -> (N (Axis b c n), N (Axis b c n)) -> [N (Axis b c n)]) Source #

minorTicksAlignment :: LensLike' f (Axis b c n) TicksAlignment Source #

minorTicksLength :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

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

(Applicative f, Traversable c) => HasTicks f (Axis b c n) Source # 
Instance details

Defined in Plots.Axis

Methods

bothTicks :: LensLike' f (Axis b c n) (Ticks (V (Axis b c n)) (N (Axis b c n))) Source #

(BaseSpace c ~ V2, Settable f, Typeable n) => HasWedge f (Axis b c n) Source # 
Instance details

Defined in Plots.Types.Pie

Methods

pieWedge :: LensLike' f (Axis b c n) (Wedge (N (Axis b c n))) Source #

wedgeOuterRadius :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeInnerRadius :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeOffset :: LensLike' f (Axis b c n) (N (Axis b c n)) Source #

wedgeWidth :: LensLike' f (Axis b c n) (Angle (N (Axis b c n))) Source #

wedgeDirection :: LensLike' f (Axis b c n) (Direction V2 (N (Axis b c n))) Source #

(Settable f, Typeable (BaseSpace c), Typeable n) => HasConnectingLine f (Axis b c n) Source # 
Instance details

Defined in Plots.Types.Scatter

(Applicative f, Traversable c) => HasAxisLabel f (Axis b c n) b Source # 
Instance details

Defined in Plots.Axis

(Applicative f, Traversable c) => HasTickLabels f (Axis b c n) b Source # 
Instance details

Defined in Plots.Axis

Methods

tickLabel :: LensLike' f (Axis b c n) (TickLabels b (V (Axis b c n)) (N (Axis b c n))) Source #

tickLabelTextFunction :: LensLike' f (Axis b c n) (TextFunction b (V (Axis b c n)) (N (Axis b c n))) Source #

tickLabelFunction :: LensLike' f (Axis b c n) ([N (Axis b c n)] -> (N (Axis b c n), N (Axis b c n)) -> [(N (Axis b c n), String)]) Source #

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

tickLabelGap :: LensLike' f (Axis b c n) (N (Axis b c n)) 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 #

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

Defined in Plots.Axis

Methods

plotOptions :: LensLike' f (Axis b c n) (PlotOptions b (V (Axis b c n)) (N (Axis b c n))) Source #

plotName :: LensLike' f (Axis b c n) Name Source #

clipPlot :: LensLike' f (Axis b c n) Bool Source #

legendEntries :: LensLike' f (Axis b c n) [LegendEntry b (V (Axis b c n)) (N (Axis b c n))] Source #

plotTransform :: LensLike' f (Axis b c n) (Transformation (V (Axis b c n)) (N (Axis b c n))) Source #

plotVisible :: LensLike' f (Axis b c n) Bool Source #

(Applicative f, Typeable b, Typeable (BaseSpace c), Typeable n, Typeable a) => HasScatterOptions f (Axis b c n) a Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

gscatterOptions :: LensLike' f (Axis b c n) (ScatterOptions (V (Axis b c n)) (N (Axis b c n)) a) Source #

scatterTransform :: LensLike' f (Axis b c n) (a -> Transformation (V (Axis b c n)) (N (Axis b c n))) Source #

scatterStyle :: LensLike' f (Axis b c n) (a -> Style (V (Axis b c n)) (N (Axis b c n))) Source #

scatterPosition :: LensLike' f (Axis b c n) (a -> Point (V (Axis b c n)) (N (Axis b c n))) Source #

(TypeableFloat n, Renderable (Path V2 n) b, Mainable (QDiagram b V2 n Any)) => Mainable (Axis b V2 n) Source # 
Instance details

Defined in Plots.Axis.Render

Associated Types

type MainOpts (Axis b V2 n) #

Methods

mainArgs :: Parseable (MainOpts (Axis b V2 n)) => proxy (Axis b V2 n) -> IO (MainOpts (Axis b V2 n)) #

mainRender :: MainOpts (Axis b V2 n) -> Axis b V2 n -> IO () #

mainWith :: Axis b V2 n -> IO () #

(TypeableFloat n, Renderable (Path V2 n) b, Mainable (QDiagram b V2 n Any)) => Mainable (Axis b Polar n) Source # 
Instance details

Defined in Plots.Axis.Render

Associated Types

type MainOpts (Axis b Polar n) #

Methods

mainArgs :: Parseable (MainOpts (Axis b Polar n)) => proxy (Axis b Polar n) -> IO (MainOpts (Axis b Polar n)) #

mainRender :: MainOpts (Axis b Polar n) -> Axis b Polar n -> IO () #

mainWith :: Axis b Polar n -> IO () #

ToResult (Axis b v n) Source # 
Instance details

Defined in Plots.Axis.Render

Associated Types

type Args (Axis b v n) #

type ResultOf (Axis b v n) #

Methods

toResult :: Axis b v n -> Args (Axis b v n) -> ResultOf (Axis b v n) #

HasColourBar (Axis b v n) b Source # 
Instance details

Defined in Plots.Axis

Methods

colourBar :: Lens' (Axis b v n) (ColourBar b (N (Axis b v n))) Source #

colourBarDraw :: Lens' (Axis b v n) (ColourMap -> QDiagram b V2 (N (Axis b v n)) Any) Source #

colourBarWidth :: Lens' (Axis b v n) (N (Axis b v n)) Source #

colourBarLengthFunction :: Lens' (Axis b v n) (N (Axis b v n) -> N (Axis b v n)) Source #

colourBarGap :: Lens' (Axis b v n) (N (Axis b v n)) Source #

colourBarStyle :: Lens' (Axis b v n) (Style V2 (N (Axis b v n))) Source #

HasTitle (Axis b c n) b Source # 
Instance details

Defined in Plots.Axis

Methods

title :: Lens' (Axis b c n) (Title b (V (Axis b c n)) (N (Axis b c n))) Source #

titleText :: Lens' (Axis b c n) String Source #

titleStyle :: Lens' (Axis b c n) (Style (V (Axis b c n)) (N (Axis b c n))) Source #

titlePlacement :: Lens' (Axis b c n) Placement Source #

titleTextFunction :: Lens' (Axis b c n) (TextAlignment (N (Axis b c n)) -> String -> QDiagram b (V (Axis b c n)) (N (Axis b c n)) Any) Source #

titleAlignment :: Lens' (Axis b c n) (TextAlignment (N (Axis b c n))) Source #

titleGap :: Lens' (Axis b c n) (N (Axis b c n)) Source #

HasLegend (Axis b c n) b Source # 
Instance details

Defined in Plots.Axis

Methods

legend :: Lens' (Axis b c n) (Legend b (N (Axis b c n))) Source #

legendPlacement :: Lens' (Axis b c n) Placement Source #

legendGap :: Lens' (Axis b c n) (N (Axis b c n)) Source #

legendStyle :: Lens' (Axis b c n) (Style V2 (N (Axis b c n))) Source #

legendSpacing :: Lens' (Axis b c n) (N (Axis b c n)) Source #

legendTextWidth :: Lens' (Axis b c n) (N (Axis b c n)) Source #

legendTextFunction :: Lens' (Axis b c n) (String -> QDiagram b V2 (N (Axis b c n)) Any) Source #

legendTextStyle :: Lens' (Axis b c n) (Style V2 (N (Axis b c n))) Source #

legendOrientation :: Lens' (Axis b c n) Orientation Source #

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 #

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

Defined in Plots.Axis

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

Defined in Plots.Axis

type V (Axis b v n) = BaseSpace v
type Args (Axis b v n) Source # 
Instance details

Defined in Plots.Axis.Render

type Args (Axis b v n) = ()
type MainOpts (Axis b V2 n) Source # 
Instance details

Defined in Plots.Axis.Render

type MainOpts (Axis b V2 n) = MainOpts (QDiagram b V2 n Any)
type MainOpts (Axis b Polar n) Source # 
Instance details

Defined in Plots.Axis.Render

type ResultOf (Axis b v n) Source # 
Instance details

Defined in Plots.Axis.Render

type ResultOf (Axis b v n) = Axis b v 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)) 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 ScatterPlots 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 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 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.

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

Instances details
type BaseSpace Complex Source # 
Instance details

Defined in Plots.Axis

type BaseSpace V2 Source # 
Instance details

Defined in Plots.Axis

type BaseSpace V2 = V2
type BaseSpace V3 Source # 
Instance details

Defined in Plots.Axis

type BaseSpace V3 = V3
type BaseSpace Polar Source # 
Instance details

Defined in Plots.Axis

Axis plots

addPlot Source #

Arguments

:: (InSpace (BaseSpace c) n p, MonadState (Axis b c n) m, Plotable p b) 
=> Plot p b

the plot

-> m ()

add plot to the Axis

Add a Plotable Plot to an Axis.

addPlotable Source #

Arguments

:: (InSpace (BaseSpace c) n p, MonadState (Axis b c n) m, Plotable p b) 
=> p

the raw plot

-> State (Plot p b) ()

changes to the plot

-> m ()

add plot to the Axis

Add something Plotable to the Axis with a stateful modification of the Plot.

addPlotable' Source #

Arguments

:: (InSpace (BaseSpace v) n p, MonadState (Axis b v n) m, Plotable p b) 
=> p

the raw plot

-> m ()

add plot to the Axis

Simple version of AddPlotable without any changes Plot.

Single axis

data SingleAxis b v n Source #

Render information for a single axis line.

Instances

Instances details
Functor f => HasGridLines f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Methods

gridLines :: LensLike' f (SingleAxis b v n) (GridLines (V (SingleAxis b v n)) (N (SingleAxis b v n))) Source #

Functor f => HasMajorGridLines f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasMinorGridLines f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasAxisLine f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasAxisScaling f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasMajorTicks f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasMinorTicks f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Functor f => HasTicks f (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

Methods

bothTicks :: LensLike' f (SingleAxis b v n) (Ticks (V (SingleAxis b v n)) (N (SingleAxis b v n))) Source #

Functor f => HasAxisLabel f (SingleAxis b v n) b Source # 
Instance details

Defined in Plots.Axis

Functor f => HasTickLabels f (SingleAxis b v n) b Source # 
Instance details

Defined in Plots.Axis

Methods

tickLabel :: LensLike' f (SingleAxis b v n) (TickLabels b (V (SingleAxis b v n)) (N (SingleAxis b v n))) Source #

tickLabelTextFunction :: LensLike' f (SingleAxis b v n) (TextFunction b (V (SingleAxis b v n)) (N (SingleAxis b v n))) Source #

tickLabelFunction :: LensLike' f (SingleAxis b v n) ([N (SingleAxis b v n)] -> (N (SingleAxis b v n), N (SingleAxis b v n)) -> [(N (SingleAxis b v n), String)]) Source #

tickLabelStyle :: LensLike' f (SingleAxis b v n) (Style (V (SingleAxis b v n)) (N (SingleAxis b v n))) Source #

tickLabelGap :: LensLike' f (SingleAxis b v n) (N (SingleAxis b v n)) Source #

(TypeableFloat n, Renderable (Text n) b) => Default (SingleAxis b V2 n) Source # 
Instance details

Defined in Plots.Axis

Methods

def :: SingleAxis b V2 n #

HasVisibility (SingleAxis b v n) Source # 
Instance details

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

type V (SingleAxis b v n) = v

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.

xMin :: R1 c => Lens' (Axis b c n) (Maybe n) Source #

The minimum x value for the axis. If the value if Nothing (the Default), the bounds will be infered by the plots in the axis.

xMax :: R1 c => Lens' (Axis b c n) (Maybe n) Source #

The minimum x value for the axis. If the value if Nothing (the Default), the bounds will be infered by the plots in the axis.

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.

yMin :: R2 c => Lens' (Axis b c n) (Maybe n) Source #

The minimum y value for the axis. If the value if Nothing (the Default), the bounds will be infered by the plots in the axis.

yMax :: R2 c => Lens' (Axis b c n) (Maybe n) Source #

The minimum y value for the axis. If the value if Nothing (the Default), the bounds will be infered by the plots in the axis.

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.

zMin :: R3 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.

zMax :: R3 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.