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

Contents

Description

This module defines the various types for holding plots:

PlotOptions v
Generic options all plots have.
PlotMods v
Includes PlotOptions along with modifications to the PlotStyle.
Plot p
A rawPlot p grouped with a PlotMods.
DynamicPlot v
A wrapped up Plot so it can be stored in an Axis.
StyledPlot v
A DynamicPlot with a concrete PlotStyle, ready to be rendered.

As well as other things like the Plotable class, LegendEntries, HasOrientation and HasVisibility.

Synopsis

Plot options

data PlotOptions v Source #

Data type for holding information all plots must contain.

Instances
HasPlotOptions f (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

(HasBasis v, Foldable v) => Default (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

Methods

def :: PlotOptions v #

Qualifiable (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

Methods

(.>>) :: IsName nm => nm -> PlotOptions v -> PlotOptions v

Additive v => HasOrigin (PlotOptions v) Source #

Move origin by applying to plotTransform.

Instance details

Defined in Plots.Types

Methods

moveOriginTo :: Point (V (PlotOptions v)) (N (PlotOptions v)) -> PlotOptions v -> PlotOptions v

HasLinearMap v => Transformable (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

Methods

transform :: Transformation (V (PlotOptions v)) (N (PlotOptions v)) -> PlotOptions v -> PlotOptions v

HasVisibility (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

type N (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (PlotOptions v) = v

class HasPlotOptions f a where Source #

Class of things that have PlotOptions.

Minimal complete definition

plotOptions

Methods

plotOptions :: LensLike' f a (PlotOptions (V a)) Source #

Lens onto the PlotOptions.

plotName :: Functor f => LensLike' f a Name Source #

The Name applied to the plot. This gives a way to reference a specific plot in a rendered axis.

Default is mempty.

clipPlot :: Functor f => LensLike' f a Bool Source #

Whether the plot should be clipped to the bounds of the axes.

Default is True.

legendEntries :: Functor f => LensLike' f a [LegendEntry (V a)] Source #

The legend entries to be used for the current plot.

Default is mempty.

plotTransform :: Functor f => LensLike' f a (Transformation (V a) Double) Source #

The transform applied to the plot once it's in the axis coordinates.

Default is mempty.

plotVisible :: Functor f => LensLike' f a Bool Source #

Whether or not the plot should be shown. The BoundingBox of the plot will still affect the inferred axis bounds.

Default is True.

Instances
HasPlotOptions f (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

Functor f => HasPlotOptions f (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

Functor f => HasPlotOptions f (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

Functor f => HasPlotOptions f (Plot p) Source # 
Instance details

Defined in Plots.Types

Functor f => HasPlotOptions f (PlotMods v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Axis

key :: (HasPlotOptions Identity a, MonadState a m) => String -> m () Source #

Add a LegendEntry to something with PlotOptions using the String as the legendText and a DefaultLegendPic. Here are some typical examples:

key :: String -> State (Plot (ScatterPlot v)) ()
key :: String -> State (DynamicPlot v) ()
key :: String -> State (PlotMods v) ()

If you only care about the name of the legend, use key.

addLegendEntry :: (HasPlotOptions Identity a, MonadState a m) => LegendEntry (V a) -> m () Source #

Add a LegendEntry to something with PlotOptions. Here are some typical examples:

addLegendEntry :: LegendEntry v -> State (Plot (ScatterPlot v)) ()
addLegendEntry :: LegendEntry v -> State (DynamicPlot v) ()

If you only care about the name of the legend, use key.

Plot modifications

data PlotMods v Source #

A PlotOptions with modifications to a PlotStyle.

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

Defined in Plots.Types

Functor f => HasPlotOptions f (PlotMods v) Source # 
Instance details

Defined in Plots.Types

(HasBasis v, Foldable v) => Default (PlotMods v) Source # 
Instance details

Defined in Plots.Types

Methods

def :: PlotMods v #

HasVisibility (PlotMods v) Source # 
Instance details

Defined in Plots.Types

type N (PlotMods v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (PlotMods v) = v

plotMods :: Lens' (Plot p) (PlotMods (V p)) Source #

The modifications to the PlotOptions and PlotStyle in a Plot.

Plotable class

class (Typeable p, Enveloped p, N p ~ Double) => Plotable p where Source #

Class defining how plots should be rendered.

Minimal complete definition

renderPlotable

Methods

renderPlotable :: InSpace v Double p => AxisSpec v -> PlotStyle v -> p -> Diagram v Source #

Render a plot according to the AxisSpec, using the PlotStyle.

defLegendPic :: InSpace v Double p => PlotStyle v -> p -> Diagram v Source #

The default legend picture when the LegendPic is DefaultLegendPic.

Instances
Plotable HistogramPlot Source # 
Instance details

Defined in Plots.Types.Histogram

Methods

renderPlotable :: InSpace v Double HistogramPlot => AxisSpec v -> PlotStyle v -> HistogramPlot -> Diagram v Source #

defLegendPic :: InSpace v Double HistogramPlot => PlotStyle v -> HistogramPlot -> Diagram v Source #

Plotable BarPlot Source # 
Instance details

Defined in Plots.Types.Bar

Methods

renderPlotable :: InSpace v Double BarPlot => AxisSpec v -> PlotStyle v -> BarPlot -> Diagram v Source #

defLegendPic :: InSpace v Double BarPlot => PlotStyle v -> BarPlot -> Diagram v Source #

(Typeable v, HasLinearMap v) => Plotable (Diagram v) Source # 
Instance details

Defined in Plots.Types

Methods

renderPlotable :: InSpace v0 Double (Diagram v) => AxisSpec v0 -> PlotStyle v0 -> Diagram v -> Diagram v0 Source #

defLegendPic :: InSpace v0 Double (Diagram v) => PlotStyle v0 -> Diagram v -> Diagram v0 Source #

Plotable (ScatterPlot V3) Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

renderPlotable :: InSpace v Double (ScatterPlot V3) => AxisSpec v -> PlotStyle v -> ScatterPlot V3 -> Diagram v Source #

defLegendPic :: InSpace v Double (ScatterPlot V3) => PlotStyle v -> ScatterPlot V3 -> Diagram v Source #

Plotable (ScatterPlot V2) Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

renderPlotable :: InSpace v Double (ScatterPlot V2) => AxisSpec v -> PlotStyle v -> ScatterPlot V2 -> Diagram v Source #

defLegendPic :: InSpace v Double (ScatterPlot V2) => PlotStyle v -> ScatterPlot V2 -> Diagram v Source #

Plotable (HeatMap V3) Source # 
Instance details

Defined in Plots.Types.HeatMap

Methods

renderPlotable :: InSpace v Double (HeatMap V3) => AxisSpec v -> PlotStyle v -> HeatMap V3 -> Diagram v Source #

defLegendPic :: InSpace v Double (HeatMap V3) => PlotStyle v -> HeatMap V3 -> Diagram v Source #

Plotable (HeatMap V2) Source # 
Instance details

Defined in Plots.Types.HeatMap

Methods

renderPlotable :: InSpace v Double (HeatMap V2) => AxisSpec v -> PlotStyle v -> HeatMap V2 -> Diagram v Source #

defLegendPic :: InSpace v Double (HeatMap V2) => PlotStyle v -> HeatMap V2 -> Diagram v Source #

(Typeable v, R1 v, HasLinearMap v) => Plotable (Path v Double) Source # 
Instance details

Defined in Plots.Types

Methods

renderPlotable :: InSpace v0 Double (Path v Double) => AxisSpec v0 -> PlotStyle v0 -> Path v Double -> Diagram v0 Source #

defLegendPic :: InSpace v0 Double (Path v Double) => PlotStyle v0 -> Path v Double -> Diagram v0 Source #

Plot types

Parameterised plot

data Plot p Source #

A parameterised plot, together with a PlotMods. This type has an instance of many classes for modifying specific plots.

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

Defined in Plots.Types

Functor f => HasPlotOptions f (Plot p) Source # 
Instance details

Defined in Plots.Types

HasConnectingLine f p => HasConnectingLine f (Plot p) Source # 
Instance details

Defined in Plots.Types.Scatter

(Functor f, HasHeatMap f a) => HasHeatMap f (Plot a) Source # 
Instance details

Defined in Plots.Types.HeatMap

(Functor f, HasScatterOptions f p a) => HasScatterOptions f (Plot p) a Source # 
Instance details

Defined in Plots.Types.Scatter

Methods

gscatterOptions :: LensLike' f (Plot p) (ScatterOptions (V (Plot p)) a) Source #

scatterTransform :: LensLike' f (Plot p) (a -> Transformation (V (Plot p)) Double) Source #

scatterStyle :: LensLike' f (Plot p) (a -> Style (V (Plot p)) Double) Source #

scatterPosition :: LensLike' f (Plot p) (a -> Point (V (Plot p)) Double) Source #

HasOrientation p => HasOrientation (Plot p) Source # 
Instance details

Defined in Plots.Types

HasVisibility (Plot p) Source # 
Instance details

Defined in Plots.Types

HasHistogramOptions a => HasHistogramOptions (Plot a) Source # 
Instance details

Defined in Plots.Types.Histogram

HasBarLayout a => HasBarLayout (Plot a) Source # 
Instance details

Defined in Plots.Types.Bar

type N (Plot p) Source # 
Instance details

Defined in Plots.Types

type N (Plot p) = Double
type V (Plot p) Source # 
Instance details

Defined in Plots.Types

type V (Plot p) = V p

mkPlot :: (InSpace v Double p, HasBasis v, Foldable v) => p -> Plot p Source #

Make a Plot with Default PlotOptions.

rawPlot :: SameSpace p p' => Lens (Plot p) (Plot p') p p' Source #

Lens onto the raw Plotable inside a Plot.

Dynamic plot

data DynamicPlot v where Source #

A wrapped up Plot, used to store plots in an Axis.

Constructors

DynamicPlot :: (InSpace v Double p, Plotable p) => Plot p -> DynamicPlot v 
Instances
Settable f => HasPlotStyle f (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

Functor f => HasPlotOptions f (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

(Applicative f, Typeable v) => HasConnectingLine f (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

(Applicative f, Typeable v, Typeable a) => HasScatterOptions f (DynamicPlot v) a Source # 
Instance details

Defined in Plots.Types.Scatter

HasVisibility (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

type N (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (DynamicPlot v) = v

dynamicPlot :: forall p. Typeable p => Traversal' (DynamicPlot (V p)) (Plot p) Source #

Traversal over the dynamic plot without the Plotable constraint _DynamicPlot has.

dynamicPlotMods :: Lens' (DynamicPlot v) (PlotMods v) Source #

The modifications to the PlotOptions and PlotStyle in a DynamicPlot.

Styled plot

data StyledPlot v Source #

A DynamicPlot with a concrete style. This is suitable for being rendered with renderStyledPlot and get extract the legend entries with styledPlotLegend.

You can make a StyledPlot with styleDynamic

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

Defined in Plots.Types

Functor f => HasPlotOptions f (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

(Applicative f, Typeable v) => HasConnectingLine f (StyledPlot v) Source # 
Instance details

Defined in Plots.Types.Scatter

HasLinearMap v => Enveloped (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

Methods

getEnvelope :: StyledPlot v -> Envelope (V (StyledPlot v)) (N (StyledPlot v))

boundingBox :: StyledPlot v -> BoundingBox (V (StyledPlot v)) (N (StyledPlot v))

HasVisibility (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

type N (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (StyledPlot v) = v

styledPlot :: forall p. Typeable p => Traversal' (StyledPlot (V p)) p Source #

Traversal over a raw plot of a styled plot. The type of the plot must match for the traversal to be successful.

renderStyledPlot :: HasLinearMap v => AxisSpec v -> StyledPlot v -> Diagram v Source #

Render a StyledPlot given an and AxisSpec.

singleStyledPlotLegend Source #

Arguments

:: StyledPlot v 
-> [(Double, Diagram v, String)]
(z-order, legend pic, legend text)

Get the legend rendered entries from a single styled plot. The resulting entries are in no particular order. See also styledPlotLegends.

styledPlotLegends Source #

Arguments

:: [StyledPlot v] 
-> [(Diagram v, String)]
[(legend pic, legend text)]

Render a list of legend entries, in order.

Miscellaneous

Visibility

class HasVisibility a where Source #

Class of objects that can be hidden.

Minimal complete definition

visible

Methods

visible :: Lens' a Bool Source #

Lens onto whether an object should be visible when rendered.

hidden :: Lens' a Bool Source #

The opposite of visible.

Instances
HasVisibility Legend Source # 
Instance details

Defined in Plots.Legend

HasVisibility ColourBar Source # 
Instance details

Defined in Plots.Axis.ColourBar

HasVisibility (PlotOptions v) Source # 
Instance details

Defined in Plots.Types

HasVisibility (StyledPlot v) Source # 
Instance details

Defined in Plots.Types

HasVisibility (DynamicPlot v) Source # 
Instance details

Defined in Plots.Types

HasVisibility (Plot p) Source # 
Instance details

Defined in Plots.Types

HasVisibility (PlotMods v) Source # 
Instance details

Defined in Plots.Types

HasVisibility (Title v) Source # 
Instance details

Defined in Plots.Axis.Title

HasVisibility (AxisLine v) Source # 
Instance details

Defined in Plots.Axis.Line

HasVisibility (TickLabels v) Source # 
Instance details

Defined in Plots.Axis.Labels

HasVisibility (AxisLabel v) Source # 
Instance details

Defined in Plots.Axis.Labels

HasVisibility (MinorGridLines v) Source #

Hidden by default.

Instance details

Defined in Plots.Axis.Grid

HasVisibility (MajorGridLines v) Source # 
Instance details

Defined in Plots.Axis.Grid

HasVisibility (MinorTicks v) Source # 
Instance details

Defined in Plots.Axis.Ticks

HasVisibility (MajorTicks v) Source # 
Instance details

Defined in Plots.Axis.Ticks

HasVisibility (SingleAxis v) Source # 
Instance details

Defined in Plots.Axis

hide :: (MonadState s m, HasVisibility a) => ASetter' s a -> m () Source #

Set visible to False for the given setter.

hide minorTicks          :: State (Axis v) ()
hide (xAxis . gridLines) :: State (Axis v) ()

display :: (MonadState s m, HasVisibility a) => ASetter' s a -> m () Source #

Set visible to True for the given setter.

display minorGridLines :: State (Axis v) ()
display colourBar      :: State (Axis v) ()

Orientation

orient :: HasOrientation o => o -> a -> a -> a Source #

Pick the first a if the object has Horizontal orientation and the second a if the object has a Vertical orientation.

horizontal :: HasOrientation a => Lens' a Bool Source #

Lens onto whether an object's orientation is horizontal.

vertical :: HasOrientation a => Lens' a Bool Source #

Lens onto whether an object's orientation is vertical.

Legend entries

data LegendEntry v Source #

Data type for holding a legend entry.

Instances
type N (LegendEntry v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (LegendEntry v) = v

data LegendPic v Source #

Type allowing use of the default legend picture (depending on the plot) or a custom legend picture with access to the PlotStyle.

Constructors

DefaultLegendPic 
CustomLegendPic (PlotStyle v -> Diagram v) 
Instances
Default (LegendPic v) Source # 
Instance details

Defined in Plots.Types

Methods

def :: LegendPic v #

mkLegendEntry :: String -> LegendEntry v Source #

Make a legend entry with a default legendPicture and legendPrecedence 0 using the string as the legendText.

legendPicture :: Lens' (LegendEntry v) (LegendPic v) Source #

The picture used in the legend entry.

legendText :: Lens' (LegendEntry v) String Source #

The text used in the legend entry.

legendPrecedence :: Lens' (LegendEntry v) Double Source #

The order in which the legend entries are rendered. If precedences are equal, the entries are put in the order they are added to the axis.

Default is 0.

Axis spec

data AxisSpec v Source #

Information from the Axis necessary to render a Plotable.

Constructors

AxisSpec 

Fields

Instances
type N (AxisSpec v) Source # 
Instance details

Defined in Plots.Types

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

Defined in Plots.Types

type V (AxisSpec v) = v

specTrans :: forall v. Lens' (AxisSpec v) (Transformation v Double) Source #

specBounds :: forall v. Lens' (AxisSpec v) (v (Double, Double)) Source #

specScale :: forall v. Lens' (AxisSpec v) (v LogScale) Source #

scaleNum :: Floating n => (n, n) -> LogScale -> n -> n Source #

Scale a number by log10-ing it and linearly scaling it so it's within the same range.

specPoint :: (Applicative v, Additive v, Foldable v) => AxisSpec v -> Point v Double -> Point v Double Source #

Apply log scaling and the transform to a point.

Positioning

data Placement Source #

A Position is a point on an axis together with an anchor and a direction for the gap.

Constructors

Placement 

Fields

class HasPlacement a where Source #

Minimal complete definition

placement

Methods

placement :: Lens' a Placement Source #

placementAt :: Lens' a (V2 Rational) Source #

The position relative to the axis. V2 0 0 corresponds to the bottom left corner, V2 1 1 is the top right corner.

placementAnchor :: Lens' a (V2 Rational) Source #

The anchor used for the object being positioned. V2 0 0 corresponds to the bottom left corner, V2 1 1 is the top right corner.

gapDirection :: Lens' a (Direction V2 Double) Source #

The direction to extend the gap when positioning.

class HasGap a where Source #

Methods

gap :: Lens' a Double Source #

The value of the gap when rendering.

Instances
HasGap Legend Source # 
Instance details

Defined in Plots.Legend

HasGap ColourBar Source # 
Instance details

Defined in Plots.Axis.ColourBar

HasGap (Title v) Source # 
Instance details

Defined in Plots.Axis.Title

Methods

gap :: Lens' (Title v) Double Source #

HasGap (TickLabels v) Source # 
Instance details

Defined in Plots.Axis.Labels

HasGap (AxisLabel v) Source # 
Instance details

Defined in Plots.Axis.Labels

placeAgainst :: (InSpace V2 n a, SameSpace a b, Enveloped a, Enveloped b, HasOrigin b) => a -> Placement -> n -> b -> b Source #

A tool for aligned one object to another. Positions b around the bounding box of a by translating b.

Common positions

Inside positions

Outside positions