plots-0.1.1.1: 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 c where Source #

Renderable axes.

Methods

renderAxis :: Axis c -> Diagram (BaseSpace c) Source #

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

Instances
RenderAxis V3 Source # 
Instance details

Defined in Plots.Axis.Render

Methods

renderAxis :: Axis V3 -> Diagram (BaseSpace V3) Source #

RenderAxis V2 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 V2 -> Diagram (BaseSpace V2) Source #

RenderAxis Polar Source # 
Instance details

Defined in Plots.Axis.Render

Methods

renderAxis :: Axis Polar -> Diagram (BaseSpace Polar) Source #

r2AxisMain :: RenderOutcome t (Diagram V2) => t -> Axis V2 -> IO () Source #

mainWith specialised to a 2D Axis.

Low level

buildPlots :: BaseSpace c ~ v => Axis c -> [StyledPlot v] 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

RenderOutcome t (Diagram V3) => RenderOutcome t (Axis V3) Source # 
Instance details

Associated Types

type MainOpts t (Axis V3) :: Type

Methods

resultParser :: t -> proxy (Axis V3) -> Parser (MainOpts t (Axis V3))

renderOutcome :: t -> MainOpts t (Axis V3) -> Axis V3 -> IO ()

RenderOutcome t (Diagram V2) => RenderOutcome t (Axis V2) Source # 
Instance details

Associated Types

type MainOpts t (Axis V2) :: Type

Methods

resultParser :: t -> proxy (Axis V2) -> Parser (MainOpts t (Axis V2))

renderOutcome :: t -> MainOpts t (Axis V2) -> Axis V2 -> IO ()

RenderOutcome t (Diagram V2) => RenderOutcome t (Axis Polar) Source # 
Instance details

Associated Types

type MainOpts t (Axis Polar) :: Type

Methods

resultParser :: t -> proxy (Axis Polar) -> Parser (MainOpts t (Axis Polar))

renderOutcome :: t -> MainOpts t (Axis Polar) -> Axis Polar -> IO ()

WithOutcome (Axis V3) Source # 
Instance details

Associated Types

type Args (Axis V3) :: Type

type Outcome (Axis V3) :: Type

Methods

argsParser :: proxy (Axis V3) -> Parser (Args (Axis V3))

withOutcome :: (Outcome (Axis V3) -> IO ()) -> Args (Axis V3) -> Axis V3 -> IO ()

WithOutcome (Axis V2) Source # 
Instance details

Associated Types

type Args (Axis V2) :: Type

type Outcome (Axis V2) :: Type

Methods

argsParser :: proxy (Axis V2) -> Parser (Args (Axis V2))

withOutcome :: (Outcome (Axis V2) -> IO ()) -> Args (Axis V2) -> Axis V2 -> IO ()

WithOutcome (Axis Polar) Source # 
Instance details

Associated Types

type Args (Axis Polar) :: Type

type Outcome (Axis Polar) :: Type

Methods

argsParser :: proxy (Axis Polar) -> Parser (Args (Axis Polar))

withOutcome :: (Outcome (Axis Polar) -> IO ()) -> Args (Axis Polar) -> Axis Polar -> IO ()