plots-0.1.1.2: Diagrams based plotting library.

Copyright(C) 2016 Christopher Chalmers
LicenseBSD-style (see the file LICENSE)
MaintainerChristopher Chalmers
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Plots.Axis.Render

Contents

Description

Low level module containing functions for rendering different types of axis.

Synopsis

Rendering axes

class RenderAxis b v n where Source #

Renderable axes.

Methods

renderAxis :: Axis b v n -> QDiagram b (BaseSpace v) n Any Source #

Render an axis to a diagram. The size of the diagram is determined by the axisSize.

Instances
(TypeableFloat n, Renderable (Path V2 n) b) => RenderAxis b Polar n Source # 
Instance details

Defined in Plots.Axis.Render

Methods

renderAxis :: Axis b Polar n -> QDiagram b (BaseSpace Polar) n Any Source #

(TypeableFloat n, Renderable (Path V2 n) b) => RenderAxis b V2 n Source #

The RenderAxis class provides a default way to render an axis for each space.

Instance details

Defined in Plots.Axis.Render

Methods

renderAxis :: Axis b V2 n -> QDiagram b (BaseSpace V2) n Any Source #

r2AxisMain :: (Parseable (MainOpts (QDiagram b V2 Double Any)), Mainable (Axis b V2 Double)) => Axis b V2 Double -> IO () Source #

mainWith specialised to a 2D Axis.

Low level

buildPlots :: BaseSpace c ~ v => Axis b c n -> [StyledPlot b v n] Source #

Build a list of styled plots from the axis, ready to be rendered. This takes into account any AxisStyle changes and applies the finalPlots modifications.

The StyledPlots can be rendered with renderStyledPlot and the legend entries can be obtained with styledPlotLegends. This is what renderAxis can uses internally but might be useful for debugging or generating your own legend.

Orphan instances

(TypeableFloat n, Renderable (Path V2 n) b, Mainable (QDiagram b V2 n Any)) => Mainable (Axis b V2 n) Source # 
Instance details

Associated Types

type MainOpts (Axis b V2 n) :: Type

Methods

mainArgs :: Axis b V2 n -> IO (MainOpts (Axis b V2 n))

mainRender :: MainOpts (Axis b V2 n) -> Axis b V2 n -> IO ()

mainWith :: Axis b V2 n -> IO ()

(TypeableFloat n, Renderable (Path V2 n) b, Mainable (QDiagram b V2 n Any)) => Mainable (Axis b Polar n) Source # 
Instance details

Associated Types

type MainOpts (Axis b Polar n) :: Type

Methods

mainArgs :: Axis b Polar n -> IO (MainOpts (Axis b Polar n))

mainRender :: MainOpts (Axis b Polar n) -> Axis b Polar n -> IO ()

mainWith :: Axis b Polar n -> IO ()

ToResult (Axis b v n) Source # 
Instance details

Associated Types

type Args (Axis b v n) :: Type

type ResultOf (Axis b v n) :: Type

Methods

toResult :: Axis b v n -> Args (Axis b v n) -> ResultOf (Axis b v n)