| 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 |
Plots.Axis.Line
Contents
Description
The lines that make up an axis.
Synopsis
- data AxisLine v
- class HasAxisLine f a where
- axisLine :: LensLike' f a (AxisLine (V a))
- axisLineType :: Functor f => LensLike' f a AxisLineType
- axisLineStyle :: Functor f => LensLike' f a (Style (V a) Double)
- data AxisLineType
Grid lines
Information about position and style of axis lines.
Instances
| HasAxisLine f (AxisLine v) Source # | |
| Default (AxisLine v) Source # | |
Defined in Plots.Axis.Line | |
| ApplyStyle (AxisLine v) Source # | |
Defined in Plots.Axis.Line Methods applyStyle :: Style (V (AxisLine v)) (N (AxisLine v)) -> AxisLine v -> AxisLine v | |
| HasStyle (AxisLine v) Source # | |
| HasVisibility (AxisLine v) Source # | |
| type N (AxisLine v) Source # | |
Defined in Plots.Axis.Line | |
| type V (AxisLine v) Source # | |
Defined in Plots.Axis.Line type V (AxisLine v) = v | |
class HasAxisLine f a where Source #
Class of object that have an AxisLine.
Minimal complete definition
Methods
axisLine :: LensLike' f a (AxisLine (V a)) Source #
Lens onto the AxisLine.
axisLineType :: Functor f => LensLike' f a AxisLineType Source #
The position of the axis line around the axis.
Default is BoxAxisLine.
axisLineStyle :: Functor f => LensLike' f a (Style (V a) Double) Source #
The options for if you want the axis line to have arrows at the end.
XXX (feature not currently implimented) axisLineArrowOpts :: Functor f => LensLike' f a (Maybe (ArrowOpts (N a))) axisLineArrowOpts = axisLine . lens alArrowOpts (al sty -> al {alArrowOpts = sty})
The Style applied to the axis line
Instances
| HasAxisLine f (AxisLine v) Source # | |
| (Applicative f, Traversable c) => HasAxisLine f (Axis c) Source # | |
| Functor f => HasAxisLine f (SingleAxis v) Source # | |
Defined in Plots.Axis Methods axisLine :: LensLike' f (SingleAxis v) (AxisLine (V (SingleAxis v))) Source # axisLineType :: LensLike' f (SingleAxis v) AxisLineType Source # axisLineStyle :: LensLike' f (SingleAxis v) (Style (V (SingleAxis v)) Double) Source # | |
Axis line types
data AxisLineType Source #
Where axis line for coordinate should be drawn. The Default is
BoxAxisLine.
Constructors
| BoxAxisLine | |
| LeftAxisLine | |
| MiddleAxisLine | |
| RightAxisLine | |
| NoAxisLine |
Instances
| Eq AxisLineType Source # | |
Defined in Plots.Axis.Line | |
| Show AxisLineType Source # | |
Defined in Plots.Axis.Line Methods showsPrec :: Int -> AxisLineType -> ShowS # show :: AxisLineType -> String # showList :: [AxisLineType] -> ShowS # | |
| Default AxisLineType Source # | |
Defined in Plots.Axis.Line Methods def :: AxisLineType # | |