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

Description

Ticks for being placed on an axis or a ColourBar.

Synopsis

Major ticks

data MajorTicks v n Source #

The big ticks on the axis line.

Instances

Instances details
HasMajorTicks f (MajorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

TypeableFloat n => Default (MajorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

Methods

def :: MajorTicks v n #

HasVisibility (MajorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

type N (MajorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

type V (MajorTicks v n) = v

class HasMajorTicks f a where Source #

Class of things that have a MajorTicks.

Minimal complete definition

majorTicks

Methods

majorTicks :: LensLike' f a (MajorTicks (V a) (N a)) Source #

Lens onto the MajorTicks of something.

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

The function used to place ticks for this axis, given the bounds of the axis. The result of these major ticks are also used as guides for MinorTicks, MajorGridLines and MinorGridLines.

Default is linearMinorTicks 5.

majorTicksAlignment :: Functor f => LensLike' f a TicksAlignment Source #

Alignment of the major ticks. Choose between autoTicks (default), centreTicks, insideTicks or outsideTicks.

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

The total length the major ticks.

Default is 7.

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

The style used to render the major ticks.

Default is lwO 0.6 mempty (subject to change).

Instances

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

Defined in Plots.Axis.ColourBar

HasMajorTicks f (MajorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

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

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

Defined in Plots.Axis

majorTicksHelper Source #

Arguments

:: (RealFrac n, Floating n) 
=> [n]

Allowed numbers (up to powers of 10)

-> n

desired number of ticks

-> (n, n)

bounds

-> [n]

tick positions

Choose ticks whose step size is a multiple of 10 of the allowed numbers and tries to match the number of desired ticks.

Note that the resulting tick positions may go out of the range of the bounds. This is so the minor ticks can be chosen correctly if a tick doesn't end exactly on a bound. When we render, we ignore all ticks outside the bounds.

logMajorTicks :: (RealFrac n, Floating n) => n -> (n, n) -> [n] Source #

Place n ticks at powers of 10 on the axis.

Minor ticks

data MinorTicks v n Source #

The small ticks on the axis line.

Instances

Instances details
HasMinorTicks f (MinorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

TypeableFloat n => Default (MinorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

Methods

def :: MinorTicks v n #

HasVisibility (MinorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

type N (MinorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

type V (MinorTicks v n) = v

class HasMinorTicks f a where Source #

Class of things that have a single MinorTicks.

Minimal complete definition

minorTicks

Methods

minorTicks :: LensLike' f a (MinorTicks (V a) (N a)) Source #

Lens onto the MinorTicks of something.

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

The function used to place ticks for this axis, given the result of majorTicksFunction and the bounds of the axis.

Default is linearMinorTicks 3.

minorTicksAlignment :: Functor f => LensLike' f a TicksAlignment Source #

Alignment of the minor ticks. Choose between autoTicks (default), centreTicks, insideTicks or outsideTicks.

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

The total length the minor ticks.

Default is 3.

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

The style used to render the minor ticks.

Default is lwO 0.4 mempty (subject to change).

Instances

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

Defined in Plots.Axis.ColourBar

HasMinorTicks f (MinorTicks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

Methods

minorTicks :: LensLike' f (Ticks v n) (MinorTicks (V (Ticks v n)) (N (Ticks v n))) Source #

minorTicksFunction :: LensLike' f (Ticks v n) ([N (Ticks v n)] -> (N (Ticks v n), N (Ticks v n)) -> [N (Ticks v n)]) Source #

minorTicksAlignment :: LensLike' f (Ticks v n) TicksAlignment Source #

minorTicksLength :: LensLike' f (Ticks v n) (N (Ticks v n)) Source #

minorTicksStyle :: LensLike' f (Ticks v n) (Style (V (Ticks v n)) (N (Ticks v 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 #

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

Defined in Plots.Axis

minorTicksHelper Source #

Arguments

:: Fractional n 
=> Int

Number of minor ticks between each major tick

-> [n]

Positions of major ticks

-> (n, n)

Bounds

-> [n]

Minor tick positions

Place n linear spaced ticks between each major tick.

Both major and minor ticks

data Ticks v n Source #

Both MajorTicks and MinorTicks together.

Instances

Instances details
Functor f => HasMajorTicks f (Ticks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

Methods

minorTicks :: LensLike' f (Ticks v n) (MinorTicks (V (Ticks v n)) (N (Ticks v n))) Source #

minorTicksFunction :: LensLike' f (Ticks v n) ([N (Ticks v n)] -> (N (Ticks v n), N (Ticks v n)) -> [N (Ticks v n)]) Source #

minorTicksAlignment :: LensLike' f (Ticks v n) TicksAlignment Source #

minorTicksLength :: LensLike' f (Ticks v n) (N (Ticks v n)) Source #

minorTicksStyle :: LensLike' f (Ticks v n) (Style (V (Ticks v n)) (N (Ticks v n))) Source #

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

Defined in Plots.Axis.Ticks

Methods

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

TypeableFloat n => Default (Ticks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

Methods

def :: Ticks v n #

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

Defined in Plots.Axis.Ticks

Methods

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

type N (Ticks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

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

Defined in Plots.Axis.Ticks

type V (Ticks v n) = v

class (HasMinorTicks f a, HasMajorTicks f a) => HasTicks f a where Source #

Class of things with both MajorTicks and MinorTicks.

Methods

bothTicks :: LensLike' f a (Ticks (V a) (N a)) Source #

Instances

Instances details
Functor f => HasTicks f (Ticks v n) Source # 
Instance details

Defined in Plots.Axis.Ticks

Methods

bothTicks :: LensLike' f (Ticks v n) (Ticks (V (Ticks v n)) (N (Ticks v 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 #

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 #

ticksAlign :: (HasTicks f a, Applicative f) => LensLike' f a TicksAlignment Source #

Traversal over both major and minor tick alignment.

ticksStyle :: (HasTicks f a, Applicative f) => LensLike' f a (Style (V a) (N a)) Source #

Traversal over both major and minor tick styles.

ticksVisible :: (HasTicks f a, Applicative f) => LensLike' f a Bool Source #

Traversal over the visibility of both major and minor ticks.

Tick alignment

data TicksAlignment Source #

Set the portion of the tick above and below the axis.

Instances

Instances details
Show TicksAlignment Source # 
Instance details

Defined in Plots.Axis.Ticks

Eq TicksAlignment Source # 
Instance details

Defined in Plots.Axis.Ticks

autoTicks :: TicksAlignment Source #

Set the tick type depending on the axis line position. centreTick for middleAxis, insideTick for everything else.

centreTicks :: TicksAlignment Source #

Set the tick to be in the centre of the axis with total length of the corresponding tick length.

insideTicks :: TicksAlignment Source #

Align the ticks to be inside a box axis.

outsideTicks :: TicksAlignment Source #

Align the ticks to be outside a box axis.

Helper functions

hideTicks :: HasTicks Identity a => a -> a Source #

Hides the Minor ticks when trying to render something. This can be used on multiple types:

hideTicks :: Axis b c n       -> Axis b c n
hideTicks :: SingleAxis b v n -> SingleAxis b v n
hideTicks :: Ticks v n        -> Ticks v n
hideTicks :: MinorTicks v n   -> MinorTicks v n

majorTickPositions :: (HasMajorTicks f a, Settable f) => LensLike' f a [N a] Source #

Setter over the final positions the major ticks. This is not as general as majorTicksFunction 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.

minorTickPositions :: (HasMinorTicks f a, Settable f) => LensLike' f a [N a] Source #

Setter over the final positions the major ticks. This is not as general as minorTicksFunction 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.

linearMajorTicks :: (RealFrac n, Floating n) => n -> (n, n) -> [n] Source #

Ticks whose value ends in 1, 0.5, 0.25, 0.2 (*10^n).