Safe Haskell | None |
---|
Graphics.Rendering.Chart
Description
A Simple framework for creating 2D charts in Haskell.
The basic model is that you define a value of type Renderable
,
typically by applying toRenderable
to some other value. This
Renderable
is then actually displayed or output by calling either
renderableToPNGFile
, or renderableToWindow
.
Currently, the only useful Renderable
for displaying charts
is created by applying toRenderable
to a value of type
Layout1
- data Renderable = Renderable {}
- class ToRenderable a where
- toRenderable :: a -> Renderable
- data Layout1 = Layout1 {}
- data Axis = Axis {
- axis_viewport :: Range -> Double -> Double
- axis_ticks :: [(Double, Double)]
- axis_labels :: [(Double, String)]
- axis_grid :: [Double]
- axis_label_gap :: Double
- axis_line_style :: CairoLineStyle
- axis_label_style :: CairoFontStyle
- axis_grid_style :: CairoLineStyle
- data Plot = Plot {
- plot_render :: PointMapFn -> Render ()
- plot_render_legend :: Rect -> Render ()
- plot_all_points :: [Point]
- class ToPlot a where
- data PlotPoints = PlotPoints {}
- data PlotLines = PlotLines {}
- data PlotFillBetween = PlotFillBetween {}
- data HAxis
- data VAxis
- data Rect = Rect Point Point
- data Point = Point {}
- defaultAxisLineStyle :: CairoLineStyle
- defaultPlotLineStyle :: CairoLineStyle
- defaultAxis :: Axis
- defaultPlotPoints :: PlotPoints
- defaultPlotLines :: PlotLines
- defaultPlotFillBetween :: PlotFillBetween
- defaultLayout1 :: Layout1
- filledCircles :: Double -> Double -> Double -> Double -> CairoPointStyle
- solidLine :: Double -> Double -> Double -> Double -> CairoLineStyle
- dashedLine :: Double -> [Double] -> Double -> Double -> Double -> CairoLineStyle
- solidFillStyle :: Double -> Double -> Double -> CairoFillStyle
- fontStyle :: String -> Double -> FontSlant -> FontWeight -> CairoFontStyle
- independentAxes :: AxisFn -> AxisFn -> AxesFn
- linkedAxes :: AxisFn -> AxesFn
- linkedAxes' :: AxisFn -> AxesFn
- explicitAxis :: Maybe Axis -> AxisFn
- autoScaledAxis :: Axis -> AxisFn
- autoScaledLogAxis :: Axis -> AxisFn
- monthsAxis :: Axis -> AxisFn
- renderableToPNGFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- renderableToPDFFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- renderableToPSFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- doubleFromClockTime :: ClockTime -> Double
- clockTimeFromDouble :: Double -> ClockTime
- newtype CairoLineStyle = CairoLineStyle (Render ())
- newtype CairoFillStyle = CairoFillStyle (Render ())
- newtype CairoFontStyle = CairoFontStyle (Render ())
Documentation
data Renderable Source
A Renderable is a record of functions required to layout a graphic element.
class ToRenderable a whereSource
A type class abtracting the conversion of a value to a Renderable.
Methods
toRenderable :: a -> RenderableSource
Instances
A Layout1 value is a single plot area, with optional: axes on each of the 4 sides; title at the top; legend at the bottom.
Constructors
Layout1 | |
Fields |
Instances
The concrete data type for an axis
Constructors
Axis | |
Fields
|
Interface to control plotting on a 2D area.
Constructors
Plot | |
Fields
|
a type class abstracting the conversion of a value to a Plot.
Instances
data PlotPoints Source
Value defining a series of datapoints, and a style in which to render them
Constructors
PlotPoints | |
Fields |
Instances
Value defining a series of (possibly disjointed) lines, and a style in which to render them
Constructors
PlotLines | |
Fields
|
data PlotFillBetween Source
Value specifying a plot filling the area between two sets of Y coordinates, given common X coordinates.
Constructors
PlotFillBetween | |
Fields |
Instances
A rectangle is defined by two points
A point in two dimensions
Arguments
:: Double | radius of circle |
-> Double | red component of colour |
-> Double | green component of colour |
-> Double | blue component of colour |
-> CairoPointStyle |
Arguments
:: Double | width of line |
-> Double | red component of colour |
-> Double | green component of colour |
-> Double | blue component of colour |
-> CairoLineStyle |
Arguments
:: Double | red component of colour |
-> Double | green component of colour |
-> Double | blue component of colour |
-> CairoFillStyle |
Arguments
:: String | the font name |
-> Double | the font size |
-> FontSlant | the font slant |
-> FontWeight | the font weight |
-> CairoFontStyle |
independentAxes :: AxisFn -> AxisFn -> AxesFnSource
Show independent axes on each side of the layout
linkedAxes :: AxisFn -> AxesFnSource
Show the same axis on both sides of the layout
linkedAxes' :: AxisFn -> AxesFnSource
Show the same axis on both sides of the layout, but with labels only on the primary side
explicitAxis :: Maybe Axis -> AxisFnSource
Explicitly specify an axis
autoScaledAxis :: Axis -> AxisFnSource
Generate a linear axis automatically. The supplied axis is used as a template, with the viewport, ticks, labels and grid set appropriately for the data displayed against that axies. The resulting axis will only show a grid if the template has some grid values.
autoScaledLogAxis :: Axis -> AxisFnSource
Generate a log axis automatically. The supplied axis is used as a template, with the viewport, ticks, labels and grid set appropriately for the data displayed against that axies. The resulting axis will only show a grid if the template has some grid values.
monthsAxis :: Axis -> AxisFnSource
An axis that plots dates, with ticks and labels corresponding to
calendar months. The values to be plotted against this axis can
be created with doubleFromClockTime
renderableToPNGFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
renderableToPDFFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
renderableToPSFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
doubleFromClockTime :: ClockTime -> DoubleSource
Map a clocktime value to a plot cordinate
clockTimeFromDouble :: Double -> ClockTimeSource
Map a plot cordinate to a clocktime
newtype CairoLineStyle Source
Abstract data type for the style of a line
The contained Cairo action sets the required line in the Cairo rendering state.
Constructors
CairoLineStyle (Render ()) |
newtype CairoFillStyle Source
Abstract data type for a fill style
The contained Cairo action sets the required fill style in the Cairo rendering state.
Constructors
CairoFillStyle (Render ()) |
newtype CairoFontStyle Source
Abstract data type for a font.
The contained Cairo action sets the required font in the Cairo rendering state.
Constructors
CairoFontStyle (Render ()) |