Safe Haskell | None |
---|
Graphics.Rendering.Chart
Description
A 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
For a simpler though less flexible API, see Graphics.Rendering.Chart.Simple.
- data Renderable = Renderable {}
- class ToRenderable a where
- toRenderable :: a -> Renderable
- data Layout1 = Layout1 {}
- data Axis = Axis {
- axis_viewport :: Range -> Double -> Double
- axis_title :: String
- axis_ticks :: [(Double, Double)]
- axis_labels :: [(Double, String)]
- axis_grid :: [Double]
- axis_label_gap :: Double
- axis_title_style :: CairoFontStyle
- axis_line_style :: CairoLineStyle
- axis_label_style :: CairoFontStyle
- axis_grid_style :: CairoLineStyle
- data LinearAxisParams = LinearAxisParams {
- la_labelf :: Double -> String
- la_nLabels :: Int
- la_nTicks :: Int
- la_gridAtMinor :: Bool
- data Plot = Plot {
- plot_render :: PointMapFn -> CRender ()
- plot_render_legend :: Rect -> CRender ()
- plot_all_points :: [Point]
- class ToPlot a where
- data PlotPoints = PlotPoints {}
- data PlotErrBars = PlotErrBars {}
- data PlotLines = PlotLines {}
- data PlotFillBetween = PlotFillBetween {}
- data HAxis
- data VAxis
- data LegendStyle = LegendStyle {}
- data Rect = Rect Point Point
- data Point = Point {}
- data Color = Color {}
- data ErrPoint = ErrPoint {}
- data PieChart = PieChart {}
- data PieLayout = PieLayout {}
- data PieItem = PieItem {}
- defaultAxisLineStyle :: CairoLineStyle
- defaultPlotLineStyle :: CairoLineStyle
- defaultAxis :: Axis
- defaultPlotPoints :: PlotPoints
- defaultPlotErrBars :: PlotErrBars
- defaultPlotLines :: PlotLines
- defaultPlotFillBetween :: PlotFillBetween
- defaultLayout1 :: Layout1
- defaultLinearAxis :: LinearAxisParams
- defaultPieLayout :: PieLayout
- defaultPieChart :: PieChart
- defaultPieItem :: PieItem
- defaultLegendStyle :: LegendStyle
- filledCircles :: Double -> Color -> CairoPointStyle
- hollowCircles :: Double -> Double -> Color -> CairoPointStyle
- exes :: Double -> Double -> Color -> CairoPointStyle
- plusses :: Double -> Double -> Color -> CairoPointStyle
- stars :: Double -> Double -> Color -> CairoPointStyle
- filledPolygon :: Double -> Int -> Bool -> Color -> CairoPointStyle
- hollowPolygon :: Double -> Double -> Int -> Bool -> Color -> CairoPointStyle
- solidLine :: Double -> Color -> CairoLineStyle
- dashedLine :: Double -> [Double] -> Color -> CairoLineStyle
- solidFillStyle :: Color -> CairoFillStyle
- independentAxes :: AxisFn -> AxisFn -> AxesFn
- linkedAxes :: AxisFn -> AxesFn
- linkedAxes' :: AxisFn -> AxesFn
- explicitAxis :: Maybe Axis -> AxisFn
- autoScaledAxis :: Axis -> AxisFn
- autoScaledAxis' :: LinearAxisParams -> Axis -> AxisFn
- autoScaledLogAxis :: Axis -> AxisFn
- autoScaledLogAxis' :: (Double -> String) -> Axis -> AxisFn
- timeAxis :: TimeSeq -> TimeSeq -> TimeLabelFn -> Axis -> AxisFn
- autoTimeAxis :: Axis -> AxisFn
- days :: TimeSeq
- months :: TimeSeq
- years :: TimeSeq
- renderableToPNGFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- renderableToPDFFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- renderableToPSFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- renderableToSVGFile :: Renderable -> Int -> Int -> FilePath -> IO ()
- doubleFromLocalTime :: LocalTime -> Double
- localTimeFromDouble :: Double -> LocalTime
- data CairoLineStyle = CairoLineStyle {
- line_width :: Double
- line_color :: Color
- line_dashes :: [Double]
- line_cap :: LineCap
- line_join :: LineJoin
- newtype CairoFillStyle = CairoFillStyle (CRender ())
- data CairoFontStyle = CairoFontStyle {}
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
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
|
data LinearAxisParams Source
Constructors
LinearAxisParams | |
Fields
|
Interface to control plotting on a 2D area.
Constructors
Plot | |
Fields
|
a type class abstracting the conversion of a value to a Plot.
data PlotPoints Source
Value defining a series of datapoints, and a style in which to render them
Constructors
PlotPoints | |
Fields |
Instances
data PlotErrBars Source
Value defining a series of error intervals, and a style in which to render them
Constructors
PlotErrBars | |
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
data LegendStyle Source
Constructors
LegendStyle | |
Fields |
A rectangle is defined by two points
A point in two dimensions
Value for holding a point with associated error bounds for each axis.
Constructors
PieChart | |
Fields |
Instances
Constructors
PieLayout | |
Fields |
Instances
Constructors
PieItem | |
Fields
|
Arguments
:: Double | radius of circle |
-> Color | colour |
-> CairoPointStyle |
Arguments
:: Double | radius of circle |
-> Double | thickness of line |
-> Color | |
-> CairoPointStyle |
Arguments
:: Double | radius of circle |
-> Double | thickness of line |
-> Color | |
-> CairoPointStyle |
Arguments
:: Double | radius of circle |
-> Double | thickness of line |
-> Color | |
-> CairoPointStyle |
Arguments
:: Double | radius of circle |
-> Int | Number of vertices |
-> Bool | Is right-side-up? |
-> Color | |
-> CairoPointStyle |
Arguments
:: Double | width of line |
-> Color | |
-> CairoLineStyle |
Arguments
:: Double | width of line |
-> [Double] | the dash pattern in device coordinates |
-> Color | |
-> CairoLineStyle |
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
autoScaledAxis' :: LinearAxisParams -> 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' :: (Double -> String) -> 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.
timeAxis :: TimeSeq -> TimeSeq -> TimeLabelFn -> Axis -> AxisFnSource
Create an AxisFn
to for a time axis. The first TimeSeq
sets the minor ticks,
and the ultimate range will aligned to it's elements. The second TimeSeq
sets
the labels and grid. The TimeLabelFn
is used to format LocalTimes for labels.
The values to be plotted against this axis can be created with doubleFromLocalTime
autoTimeAxis :: Axis -> AxisFnSource
Automatically choose a suitable time axis, based upon the time range of data.
The values to be plotted against this axis can be created with doubleFromLocalTime
renderableToPNGFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
Output the given renderable to a PNG file of the specifed size (in pixels), to the specified file.
renderableToPDFFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
Output the given renderable to a PDF file of the specifed size (in points), to the specified file.
renderableToPSFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
Output the given renderable to a postscript file of the specifed size (in points), to the specified file.
renderableToSVGFile :: Renderable -> Int -> Int -> FilePath -> IO ()Source
Output the given renderable to an SVG file of the specifed size (in points), to the specified file.
doubleFromLocalTime :: LocalTime -> DoubleSource
Map a LocalTime value to a plot cordinate
localTimeFromDouble :: Double -> LocalTimeSource
Map a plot cordinate to a LocalTime
data CairoLineStyle Source
Data type for the style of a line
Constructors
CairoLineStyle | |
Fields
|
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 (CRender ()) |
data CairoFontStyle Source
Data type for a font
Constructors
CairoFontStyle | |
Fields
|