Chart-1.9.3: A library for generating 2D Charts and Plots

Copyright(c) Tim Docker 2006 2014
LicenseBSD-style (see chart/COPYRIGHT)
Safe HaskellNone
LanguageHaskell98

Graphics.Rendering.Chart.Plot.Types

Description

Datatypes and functions common to the implementation of the various plot types.

Synopsis

Documentation

data Plot x y Source #

Interface to control plotting on a 2D area.

Constructors

Plot 

Fields

  • _plot_render :: PointMapFn x y -> BackendProgram ()

    Given the mapping between model space coordinates and device coordinates, render this plot into a chart.

  • _plot_legend :: [(String, Rect -> BackendProgram ())]

    Details for how to show this plot in a legend. For each item the string is the text to show, and the function renders a graphical sample of the plot.

  • _plot_all_points :: ([x], [y])

    All of the model space coordinates to be plotted. These are used to autoscale the axes where necessary.

Instances
ToPlot Plot Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Types

Methods

toPlot :: Plot x y -> Plot x y Source #

joinPlot :: Plot x y -> Plot x y -> Plot x y Source #

Join any two plots together (they will share a legend).

class ToPlot a where Source #

A type class abstracting the conversion of a value to a Plot.

Methods

toPlot :: a x y -> Plot x y Source #

Instances
ToPlot Plot Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Types

Methods

toPlot :: Plot x y -> Plot x y Source #

ToPlot PlotPoints Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Points

Methods

toPlot :: PlotPoints x y -> Plot x y Source #

ToPlot PlotLines Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Lines

Methods

toPlot :: PlotLines x y -> Plot x y Source #

ToPlot PlotHidden Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Hidden

Methods

toPlot :: PlotHidden x y -> Plot x y Source #

ToPlot PlotFillBetween Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.FillBetween

Methods

toPlot :: PlotFillBetween x y -> Plot x y Source #

ToPlot PlotErrBars Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.ErrBars

Methods

toPlot :: PlotErrBars x y -> Plot x y Source #

ToPlot PlotCandle Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Candle

Methods

toPlot :: PlotCandle x y -> Plot x y Source #

ToPlot PlotAnnotation Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.Annotation

Methods

toPlot :: PlotAnnotation x y -> Plot x y Source #

PlotValue z => ToPlot (AreaSpots z) Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.AreaSpots

Methods

toPlot :: AreaSpots z x y -> Plot x y Source #

(PlotValue z, PlotValue t, Show t) => ToPlot (AreaSpots4D z t) Source # 
Instance details

Defined in Graphics.Rendering.Chart.Plot.AreaSpots

Methods

toPlot :: AreaSpots4D z t x y -> Plot x y Source #

mapXY :: PointMapFn x y -> (x, y) -> Point Source #

plot_render :: forall x y. Lens' (Plot x y) (PointMapFn x y -> BackendProgram ()) Source #

plot_legend :: forall x y. Lens' (Plot x y) [(String, Rect -> BackendProgram ())] Source #

plot_all_points :: forall x y. Lens' (Plot x y) ([x], [y]) Source #