plots-0.1.1.1: Diagrams based plotting library.

Copyright(C) 2015 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

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

Axis type

data Axis c 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
RenderOutcome t (Diagram V3) => RenderOutcome t (Axis V3) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type MainOpts t (Axis V3) :: Type

Methods

resultParser :: t -> proxy (Axis V3) -> Parser (MainOpts t (Axis V3))

renderOutcome :: t -> MainOpts t (Axis V3) -> Axis V3 -> IO ()

RenderOutcome t (Diagram V2) => RenderOutcome t (Axis V2) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type MainOpts t (Axis V2) :: Type

Methods

resultParser :: t -> proxy (Axis V2) -> Parser (MainOpts t (Axis V2))

renderOutcome :: t -> MainOpts t (Axis V2) -> Axis V2 -> IO ()

RenderOutcome t (Diagram V2) => RenderOutcome t (Axis Polar) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type MainOpts t (Axis Polar) :: Type

Methods

resultParser :: t -> proxy (Axis Polar) -> Parser (MainOpts t (Axis Polar))

renderOutcome :: t -> MainOpts t (Axis Polar) -> Axis Polar -> IO ()

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

(Applicative f, Traversable c) => HasAxisLine f (Axis c) Source # 
Instance details

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

Methods

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

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

Methods

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

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Types.Scatter

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

Defined in Plots.Types.Scatter

Methods

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

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

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

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

WithOutcome (Axis V3) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type Args (Axis V3) :: Type

type Outcome (Axis V3) :: Type

Methods

argsParser :: proxy (Axis V3) -> Parser (Args (Axis V3))

withOutcome :: (Outcome (Axis V3) -> IO ()) -> Args (Axis V3) -> Axis V3 -> IO ()

WithOutcome (Axis V2) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type Args (Axis V2) :: Type

type Outcome (Axis V2) :: Type

Methods

argsParser :: proxy (Axis V2) -> Parser (Args (Axis V2))

withOutcome :: (Outcome (Axis V2) -> IO ()) -> Args (Axis V2) -> Axis V2 -> IO ()

WithOutcome (Axis Polar) 
Instance details

Defined in Plots.Axis.Render

Associated Types

type Args (Axis Polar) :: Type

type Outcome (Axis Polar) :: Type

Methods

argsParser :: proxy (Axis Polar) -> Parser (Args (Axis Polar))

withOutcome :: (Outcome (Axis Polar) -> IO ()) -> Args (Axis Polar) -> Axis Polar -> IO ()

HasAxisStyle (Axis v) Source # 
Instance details

Defined in Plots.Axis

HasLegend (Axis c) Source # 
Instance details

Defined in Plots.Axis

HasTitle (Axis c) Source # 
Instance details

Defined in Plots.Axis

Methods

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

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

titleStyle :: Lens' (Axis c) (Style (V (Axis c)) Double) Source #

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

titleTextFunction :: Lens' (Axis c) (TextAlignment Double -> String -> Diagram (V (Axis c))) Source #

titleAlignment :: Lens' (Axis c) (TextAlignment Double) Source #

titleGap :: Lens' (Axis c) Double Source #

HasColourBar (Axis v) Source # 
Instance details

Defined in Plots.Axis

type MainOpts t (Axis Polar) 
Instance details

Defined in Plots.Axis.Render

type MainOpts t (Axis Polar) = MainOpts t (Diagram V2)
type MainOpts t (Axis V3) 
Instance details

Defined in Plots.Axis.Render

type MainOpts t (Axis V3) = MainOpts t (Diagram V3)
type MainOpts t (Axis V2) 
Instance details

Defined in Plots.Axis.Render

type MainOpts t (Axis V2) = MainOpts t (Diagram V2)
type Args (Axis V3) 
Instance details

Defined in Plots.Axis.Render

type Args (Axis V3) = ()
type Args (Axis V2) 
Instance details

Defined in Plots.Axis.Render

type Args (Axis V2) = ()
type Args (Axis Polar) 
Instance details

Defined in Plots.Axis.Render

type Args (Axis Polar) = ()
type Outcome (Axis V3) 
Instance details

Defined in Plots.Axis.Render

type Outcome (Axis V3) = Axis V3
type Outcome (Axis V2) 
Instance details

Defined in Plots.Axis.Render

type Outcome (Axis V2) = Axis V2
type Outcome (Axis Polar) 
Instance details

Defined in Plots.Axis.Render

type Outcome (Axis Polar) = Axis Polar
type N (Axis c) Source # 
Instance details

Defined in Plots.Axis

type N (Axis c) = Double
type V (Axis c) Source # 
Instance details

Defined in Plots.Axis

type V (Axis c) = BaseSpace c

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' (Axis c) (c (SingleAxis v))

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

r2Axis :: Axis V2 Source #

The default axis for plots in the V2 coordinate system.

r3Axis :: Axis V3 Source #

The default axis for plots in the V2 coordinate system.

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 # 
Instance details

Defined in Plots.Axis

type BaseSpace V3 Source # 
Instance details

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

Axis plots

addPlot Source #

Arguments

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

the plot

-> m ()

add plot to the Axis

Add a Plotable Plot to an Axis.

addPlotable Source #

Arguments

:: (InSpace (BaseSpace c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c)) 
=> p

the raw plot

-> State (Plot p) ()

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 c) Double p, MonadState (Axis c) m, Plotable p, HasLinearMap (BaseSpace c)) 
=> p

the raw plot

-> m ()

add plot to the Axis

Simple version of AddPlotable without any changes Plot.

Single axis

data SingleAxis v Source #

Render information for a single axis line.

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

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

Defined in Plots.Axis

Default (SingleAxis V3) Source # 
Instance details

Defined in Plots.Axis

Methods

def :: SingleAxis V3 #

Default (SingleAxis V2) Source # 
Instance details

Defined in Plots.Axis

Methods

def :: SingleAxis V2 #

HasVisibility (SingleAxis v) Source # 
Instance details

Defined in Plots.Axis

type N (SingleAxis v) Source # 
Instance details

Defined in Plots.Axis

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

Defined in Plots.Axis

type V (SingleAxis v) = v

Specific axes

x-axis

xAxis :: R1 c => Lens' (Axis c) (SingleAxis (BaseSpace c)) Source #

Lens onto the x-axis of an Axis.

xLabel :: R1 c => Lens' (Axis c) String Source #

The label for the x-axis. Shorthand for xAxis . axisLabelText.

xMin :: R1 c => Lens' (Axis c) (Maybe Double) 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 c) (Maybe Double) 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 c) (SingleAxis (BaseSpace c)) Source #

Lens onto the y-axis of an Axis.

yLabel :: R2 c => Lens' (Axis c) String Source #

The label for the y-axis. Shorthand for yAxis . axisLabelText.

yMin :: R2 c => Lens' (Axis c) (Maybe Double) 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 c) (Maybe Double) 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 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

zAxis :: R3 c => Lens' (Axis c) (SingleAxis (BaseSpace c)) Source #

Lens onto the z-axis of an Axis.

zLabel :: R3 c => Lens' (Axis c) String Source #

The label for the z-axis. Shorthand for zAxis . axisLabelText.

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

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