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

Plots.Axis.Labels

Description

There are two kinds of labels this module deals with: The AxisLabel labels are placed next to an axis line. The TickLabels are the numbers (usually) next to each major tick on an axis line.

Synopsis

Axis line labels

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

Minimal complete definition

axisLabel

Methods

axisLabel :: LensLike' f a (AxisLabel b (V a) (N a)) Source #

The options for the label of the axis. This can be used on various levels of the axis:

axisLabel :: Traversal' (Axis b c n)       (AxisLabel (BaseSpace c) n)
axisLabel :: Lens'      (SingleAxis b v n) (AxisLabel v n)
axisLabel :: Lens'      (AxisLabel v n)    (AxisLabel v n)

axisLabelText :: Functor f => LensLike' f a String Source #

The text to use when labeling the axis.

axisLabelTextFunction :: Functor f => LensLike' f a (TextFunction b (V a) (N a)) Source #

The TextFunction to render the text of the axis label.

axisLabelGap :: Functor f => LensLike' f a (N a) Source #

The gap between the axis and the labels, in the direction corresponding to the axisLabelPosition.

axisLabelStyle :: Functor f => LensLike' f a (Style (V a) (N a)) Source #

The Style to use on the rendered text.

axisLabelPosition :: Functor f => LensLike' f a AxisLabelPosition Source #

The position the label will be placed parallel to the axis.

axisLabelPlacement :: Functor f => LensLike' f a AxisLabelPosition Source #

Whether the axis label should be placed inside or outside the axis.

Instances

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

Defined in Plots.Axis

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

Defined in Plots.Axis

HasAxisLabel f (AxisLabel b v n) b Source # 
Instance details

Defined in Plots.Axis.Labels

data AxisLabel b v n Source #

AxisLabel describes the label next to each axis line. They are normally set with the xLabel and yLabel helper function:

myAxis = r2Axis &~ do
  xLabel .= "time (s)"
  yLabel .= "height (m)"

See HasAxisLabel for more advanced settings.

Instances

Instances details
HasAxisLabel f (AxisLabel b v n) b Source # 
Instance details

Defined in Plots.Axis.Labels

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

Defined in Plots.Axis.Labels

Methods

def :: AxisLabel b V2 n #

Typeable n => HasStyle (AxisLabel b v n) Source # 
Instance details

Defined in Plots.Axis.Labels

Methods

applyStyle :: Style (V (AxisLabel b v n)) (N (AxisLabel b v n)) -> AxisLabel b v n -> AxisLabel b v n #

HasGap (AxisLabel b v n) Source # 
Instance details

Defined in Plots.Axis.Labels

Methods

gap :: Lens' (AxisLabel b v n) (N (AxisLabel b v n)) Source #

HasVisibility (AxisLabel b v n) Source # 
Instance details

Defined in Plots.Axis.Labels

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

Defined in Plots.Axis.Labels

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

Defined in Plots.Axis.Labels

type V (AxisLabel b v n) = v

data AxisLabelPosition Source #

The position of the AxisLabel along the axis.

data AxisLabelPlacement Source #

Whether the AxisLabel should be inside or outside the axis.

Axis tick labels

data TickLabels b v n Source #

TickLabels describes how to draw the labels next to ticks. See HasTickLabels for more options.

Instances

Instances details
HasTickLabels f (TickLabels b v n) b Source # 
Instance details

Defined in Plots.Axis.Labels

Methods

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

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

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

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

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

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

Defined in Plots.Axis.Labels

Methods

def :: TickLabels b V2 n #

HasGap (TickLabels b v n) Source # 
Instance details

Defined in Plots.Axis.Labels

Methods

gap :: Lens' (TickLabels b v n) (N (TickLabels b v n)) Source #

HasVisibility (TickLabels b v n) Source # 
Instance details

Defined in Plots.Axis.Labels

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

Defined in Plots.Axis.Labels

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

Defined in Plots.Axis.Labels

type V (TickLabels b v n) = v

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

Minimal complete definition

tickLabel

Methods

tickLabel :: LensLike' f a (TickLabels b (V a) (N a)) Source #

The options for the label of ticks. This can be used on various levels of the axis:

tickLabel :: Traversal' (Tick b c n)       (TickLabels (BaseSpace c) n)
tickLabel :: Lens'      (SingleAxis b v n) (TickLabels v n)
tickLabel :: Lens'      (TickLabel v n)    (TickLabels v n)

tickLabelTextFunction :: Functor f => LensLike' f a (TextFunction b (V a) (N a)) Source #

The TextFunction to render the text.

Default is mkText.

tickLabelFunction :: Functor f => LensLike' f a ([N a] -> (N a, N a) -> [(N a, String)]) Source #

Tick labels functions are used to draw the tick labels. They have access to the major ticks and the current bounds. Returns the position of the tick and label to use at that position.

Default is atMajorTicks floatShow

tickLabelStyle :: Functor f => LensLike' f a (Style (V a) (N a)) Source #

The Style to use on the rendered text.

Default is fontSize (output 11).

tickLabelGap :: Functor f => LensLike' f a (N a) Source #

The gap between the axis and the tick labels.

Default is 12.

Instances

Instances details
Functor f => HasTickLabels f (ColourBar b n) b Source # 
Instance details

Defined in Plots.Axis.ColourBar

(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 #

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 #

HasTickLabels f (TickLabels b v n) b Source # 
Instance details

Defined in Plots.Axis.Labels

Methods

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

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

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

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

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

tickLabelPositions :: (HasTickLabels f a b, Settable f) => LensLike' f a [(N a, String)] Source #

Setter over the final positions the major ticks. This is not as general as tickLabelFunction because you don't have access to the bounds but it can be useful when you know exactly what ticks you want to add or modify existing tick positions or to add an extra value:

xAxis . tickLabelPositions .= [(1, "apples"), (2, "oranges"), (3, "bananas"]
yAxis . tickLabelPositions <>= [(1.5, "critial mass")]

If you want to change or add normal ticks see majorTicksFunction.

atMajorTicks :: (n -> String) -> [n] -> (n, n) -> [(n, String)] Source #

Make a TickLabelFunction by specifying how to draw a single label from a position on the axis.

Misc

type TextFunction b v n = TextAlignment n -> String -> QDiagram b v n Any Source #

Function to render the axis label from a string. This is very basic now and will be replace by a more sophisticated system.