Copyright | (C) 2015 Christopher Chalmers |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Christopher Chalmers |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Lines that go along the axis. Supports major and minor grid lines separately for each axis.
Synopsis
- data GridLines v
- class (HasMinorGridLines f a, HasMajorGridLines f a) => HasGridLines f a where
- data MajorGridLines v
- class HasMajorGridLines f a where
- majorGridLines :: LensLike' f a (MajorGridLines (V a))
- majorGridLinesFunction :: Functor f => LensLike' f a (GridLineFunction Double)
- majorGridLinesStyle :: Functor f => LensLike' f a (Style (V a) Double)
- data MinorGridLines v
- class HasMinorGridLines f a where
- minorGridLines :: LensLike' f a (MinorGridLines (V a))
- minorGridLinesFunction :: Functor f => LensLike' f a (GridLineFunction Double)
- minorGridLinesStyle :: Functor f => LensLike' f a (Style (V a) Double)
- gridLinesStyle :: (HasGridLines f a, Applicative f) => LensLike' f a (Style (V a) Double)
- gridLinesVisible :: (HasGridLines f a, Applicative f) => LensLike' f a Bool
- hideGridLines :: (HasGridLines Identity a, MonadState a m) => m ()
- showGridLines :: (HasGridLines Identity a, MonadState a m) => m ()
- type GridLineFunction n = [n] -> (n, n) -> [n]
- onTicksGridLineFunction :: GridLineFunction n
- emptyGridLineFunction :: GridLineFunction n
Grid lines
Type holding information about both major and minor grid lines.
Instances
class (HasMinorGridLines f a, HasMajorGridLines f a) => HasGridLines f a where Source #
Instances
Functor f => HasGridLines f (GridLines v) Source # | |
(Applicative f, Traversable c) => HasGridLines f (Axis c) Source # | |
Functor f => HasGridLines f (SingleAxis v) Source # | |
Defined in Plots.Axis gridLines :: LensLike' f (SingleAxis v) (GridLines (V (SingleAxis v))) Source # |
data MajorGridLines v Source #
Instances
HasMajorGridLines f (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid majorGridLines :: LensLike' f (MajorGridLines v) (MajorGridLines (V (MajorGridLines v))) Source # majorGridLinesFunction :: LensLike' f (MajorGridLines v) (GridLineFunction Double) Source # majorGridLinesStyle :: LensLike' f (MajorGridLines v) (Style (V (MajorGridLines v)) Double) Source # | |
Default (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid def :: MajorGridLines v # | |
ApplyStyle (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid applyStyle :: Style (V (MajorGridLines v)) (N (MajorGridLines v)) -> MajorGridLines v -> MajorGridLines v | |
HasStyle (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid style :: Lens' (MajorGridLines v) (Style (V (MajorGridLines v)) (N (MajorGridLines v))) | |
HasVisibility (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid | |
type N (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid | |
type V (MajorGridLines v) Source # | |
Defined in Plots.Axis.Grid type V (MajorGridLines v) = v |
class HasMajorGridLines f a where Source #
majorGridLines :: LensLike' f a (MajorGridLines (V a)) Source #
The options for how to draw the grid lines. This can be used on various levels of the axis:
majorGridLines
::Traversal'
(Axis
b c n) (GridLines
(BaseSpace
c) n)majorGridLines
::Lens'
(SingleAxis
b v n) (GridLines
v n)majorGridLines
::Lens'
(GridLines
v n) (GridLines
v n)
majorGridLinesFunction :: Functor f => LensLike' f a (GridLineFunction Double) Source #
The function to calculate location of the major grid lines given location of the major ticks and bounds.
majorGridLinesStyle :: Functor f => LensLike' f a (Style (V a) Double) Source #
The style applied to the major grid lines.
Instances
data MinorGridLines v Source #
Instances
class HasMinorGridLines f a where Source #
minorGridLines :: LensLike' f a (MinorGridLines (V a)) Source #
The options for how to draw the grid lines. This can be used on various levels of the axis:
minorGridLines
::Traversal'
(Axis
b c n) (GridLines
(BaseSpace
c) n)minorGridLines
::Lens'
(SingleAxis
b v n) (GridLines
v n)minorGridLines
::Lens'
(GridLines
v n) (GridLines
v n)
minorGridLinesFunction :: Functor f => LensLike' f a (GridLineFunction Double) Source #
The function to calculate location of the minor grid lines given location of the minor ticks and bounds.
minorGridLinesStyle :: Functor f => LensLike' f a (Style (V a) Double) Source #
The style applied to the minor grid lines.
Instances
Extra traversals
gridLinesStyle :: (HasGridLines f a, Applicative f) => LensLike' f a (Style (V a) Double) Source #
Traversal over both the major and minor grid styles. This can be used at several levels in the axis:
gridLinesVisible :: (HasGridLines f a, Applicative f) => LensLike' f a Bool Source #
Traversal over both the major and minor grid styles.
gridLinesVisible
::Traversal'
(Axis
b c n)Bool
gridLinesVisible
::Traversal'
(SingleAxis
b v n)Bool
gridLinesVisible
::Traversal'
(GridLines
v n)Bool
hideGridLines :: (HasGridLines Identity a, MonadState a m) => m () Source #
Hide both major and minor grid lines.
hideGridLines
::Axis
b c n ->Axis
b c nhideGridLines
::SingleAxis
b c n ->SingleAxis
b c nhideGridLines
::GridLines
b c n ->GridLines
b c n
showGridLines :: (HasGridLines Identity a, MonadState a m) => m () Source #
Show both major and minor grid lines.
showGridLines
::Axis
b c n ->Axis
b c nshowGridLines
::SingleAxis
b c n ->SingleAxis
b c nshowGridLines
::GridLines
b c n ->GridLines
b c n
Grid line functions
type GridLineFunction n = [n] -> (n, n) -> [n] Source #
A grid line function takes the positions of the respective ticks (minor ticks for minor grid lines, major ticks for major grid lines) and the bounds of the axis and returns the positions of the grid lines.
These functions are used in conjuction with majorGridLineFunction
and minorGridLineFunction
to control how the lines are drawn.
onTicksGridLineFunction :: GridLineFunction n Source #
Place grid lines at the same position as the respective ticks. This
is the Default
.
emptyGridLineFunction :: GridLineFunction n Source #
The GridLineFunction
such that no grid lines appear.
See hideGridLines
, majorGridLineVisible
or
minorGridLineVisible
if you just want to hide the grid lines.