Portability | portable |
---|---|
Stability | provisional |
Maintainer | haskell.vivian.mcphail <at> gmail <dot> com |
Graphics.Rendering.Plot.Figure
Contents
Description
Creation and manipulation of Figure
s
The same problem of leaked instances as at http://hackage.haskell.org/packages/archive/graphviz/2999.10.0.1/doc/html/Data-GraphViz-Commands.html#t%3AGraphvizCanvas occurs here.
with, set, clear, new, and add are the operations that can be performed on various elements of a figure.
glib/data-accessor abstractions (verbs/modifiers) are planned for future implementations
- data Figure a
- data FigureState
- withTextDefaults :: Text () -> Figure ()
- withLineDefaults :: Line () -> Figure ()
- withPointDefaults :: Point () -> Figure ()
- withBarDefaults :: Bar () -> Figure ()
- newFigure :: Figure ()
- setFigurePadding :: Double -> Double -> Double -> Double -> Figure ()
- withTitle :: Text () -> Figure ()
- withSubTitle :: Text () -> Figure ()
- setPlots :: Int -> Int -> Figure ()
- withPlot :: (Int, Int) -> Plot () -> Figure ()
- withPlots :: Plot () -> Figure ()
- data Plot a
- type Border = Bool
- setBorder :: Border -> Plot ()
- setPlotPadding :: Double -> Double -> Double -> Double -> Plot ()
- withHeading :: Text () -> Plot ()
- type Function = Double -> Double
- type Series = Vector Double
- type ErrorSeries = Series
- type Surface = Matrix Double
- type SeriesLabel = String
- class Abscissa a
- class Ordinate a
- class Dataset a
- type FormattedSeries = Data DecoratedSeries
- data SeriesType
- line :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeries
- point :: (Ordinate a, PointFormat b) => a -> b -> FormattedSeries
- linepoint :: (Ordinate a, LineFormat b, PointFormat c) => a -> b -> c -> FormattedSeries
- impulse :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeries
- step :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeries
- area :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeries
- bar :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeries
- hist :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeries
- candle :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeries
- whisker :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeries
- setDataset :: Dataset a => a -> Plot ()
- setSeriesType :: Int -> SeriesType -> Plot ()
- setAllSeriesTypes :: SeriesType -> Plot ()
- class PlotFormats m
- withSeriesFormat :: PlotFormats m => Int -> m () -> Plot ()
- withAllSeriesFormats :: PlotFormats m => (Int -> m ()) -> Plot ()
- data Scale
- setRange :: AxisType -> AxisSide -> Scale -> Double -> Double -> Plot ()
- setRangeFromData :: AxisType -> AxisSide -> Scale -> Plot ()
- data Axis a
- data AxisType
- data AxisSide
- data AxisPosn
- clearAxes :: Plot ()
- clearAxis :: AxisType -> AxisPosn -> Plot ()
- addAxis :: AxisType -> AxisPosn -> Axis () -> Plot ()
- withAxis :: AxisType -> AxisPosn -> Axis () -> Plot ()
- data Legend a
- type LegendBorder = Bool
- data LegendLocation
- data LegendOrientation
- clearLegend :: Plot ()
- setLegend :: LegendBorder -> LegendLocation -> LegendOrientation -> Plot ()
- withLegendFormat :: Text () -> Plot ()
- data Tick
- type TickValues = Either Int (Vector Double)
- type GridLines = Bool
- setTicks :: Tick -> TickValues -> Axis ()
- setGridlines :: Tick -> GridLines -> Axis ()
- setTickLabelFormat :: String -> Axis ()
- withAxisLabel :: Text () -> Axis ()
- withAxisLine :: Line () -> Axis ()
- data Line a
- class LineFormat a
- type DashStyle = [Dash]
- data Dash
- type LineWidth = Double
- clearLineFormat :: Line ()
- setDashStyle :: DashStyle -> Line ()
- setLineWidth :: LineWidth -> Line ()
- setLineColour :: Color -> Line ()
- data Point a
- class PointFormat a
- data Glyph
- type PointSize = Double
- setGlyph :: Glyph -> Point ()
- setPointSize :: PointSize -> Point ()
- setPointColour :: Color -> Point ()
- data Bar a
- class BarFormat a
- clearBarFormat :: Bar ()
- setBarWidth :: Width -> Bar ()
- setBarColour :: Color -> Bar ()
- setBarBorderWidth :: LineWidth -> Bar ()
- setBarBorderColour :: Color -> Bar ()
- data Text a
- type FontFamily = String
- type FontSize = Double
- type Color = Colour Double
- clearText :: Text ()
- clearTextFormat :: Text ()
- setText :: String -> Text ()
- setFontFamily :: FontFamily -> Text ()
- setFontStyle :: FontStyle -> Text ()
- setFontVariant :: Variant -> Text ()
- setFontWeight :: Weight -> Text ()
- setFontStretch :: Stretch -> Text ()
- setFontSize :: FontSize -> Text ()
- setFontColour :: Color -> Text ()
Top level operation
Instances
data FigureState Source
Instances
Default options
withTextDefaults :: Text () -> Figure ()Source
perform some actions on the text defaults, must be run before other text element modifications
withLineDefaults :: Line () -> Figure ()Source
perform some actions on the line defaults, must be run before other line element modifications
withPointDefaults :: Point () -> Figure ()Source
perform some actions on the point defaults, must be run before other point modifications
withBarDefaults :: Bar () -> Figure ()Source
perform some actions on the bar defaults, must be run before other point modifications
Figures
Formatting
setFigurePadding :: Double -> Double -> Double -> Double -> Figure ()Source
set the padding of the figure
set the shape of the plots, losing all current plots
Sub-plots
Instances
Monad Plot | |
Simple Plot | |
MonadReader Options Plot | |
MonadState PlotData Plot | |
MonadSupply SupplyData Plot |
Plot elements
setPlotPadding :: Double -> Double -> Double -> Double -> Plot ()Source
set the padding of the subplot
Series data
type ErrorSeries = SeriesSource
type SeriesLabel = StringSource
Instances
Ordinate Function | |
Ordinate Series | |
Ordinate (Function, SeriesLabel) | |
Ordinate (Function, AxisSide) | |
Ordinate (MinMaxSeries, (ErrorSeries, ErrorSeries)) | |
Ordinate (Series, (ErrorSeries, ErrorSeries)) | |
Ordinate (Series, SeriesLabel) | |
Ordinate (Series, ErrorSeries) | |
Ordinate (Series, AxisSide) | |
Ordinate (Function, AxisSide, SeriesLabel) | |
Ordinate (MinMaxSeries, (ErrorSeries, ErrorSeries), AxisSide) | |
Ordinate (Series, (ErrorSeries, ErrorSeries), SeriesLabel) | |
Ordinate (Series, (ErrorSeries, ErrorSeries), AxisSide) | |
Ordinate (Series, ErrorSeries, SeriesLabel) | |
Ordinate (Series, ErrorSeries, AxisSide) | |
Ordinate (Series, AxisSide, SeriesLabel) | |
Ordinate (MinMaxSeries, (ErrorSeries, ErrorSeries), AxisSide, SeriesLabel) | |
Ordinate (Series, (ErrorSeries, ErrorSeries), AxisSide, SeriesLabel) | |
Ordinate (Series, ErrorSeries, AxisSide, SeriesLabel) |
Instances
Dataset Surface | |
Abscissa a => Dataset [(a, FormattedSeries)] | |
(Abscissa a, Ordinate b) => Dataset [(SeriesType, a, b)] | |
Dataset [FormattedSeries] | |
Abscissa a => Dataset (a, [FormattedSeries]) | |
Ordinate a => Dataset (SeriesType, [a]) | |
(Abscissa a, Ordinate b) => Dataset (SeriesType, a, [b]) |
type FormattedSeries = Data DecoratedSeriesSource
data SeriesType Source
Instances
(Abscissa a, Ordinate b) => Dataset [(SeriesType, a, b)] | |
Ordinate a => Dataset (SeriesType, [a]) | |
(Abscissa a, Ordinate b) => Dataset (SeriesType, a, [b]) |
line :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeriesSource
point :: (Ordinate a, PointFormat b) => a -> b -> FormattedSeriesSource
linepoint :: (Ordinate a, LineFormat b, PointFormat c) => a -> b -> c -> FormattedSeriesSource
impulse :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeriesSource
step :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeriesSource
area :: (Ordinate a, LineFormat b) => a -> b -> FormattedSeriesSource
bar :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeriesSource
hist :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeriesSource
candle :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeriesSource
whisker :: (Ordinate a, BarFormat b) => a -> b -> FormattedSeriesSource
setDataset :: Dataset a => a -> Plot ()Source
set the data series of the subplot
Plot type
setSeriesType :: Int -> SeriesType -> Plot ()Source
set the plot type of a given data series
setAllSeriesTypes :: SeriesType -> Plot ()Source
change the plot type of all data series
Formatting
class PlotFormats m Source
Instances
withSeriesFormat :: PlotFormats m => Int -> m () -> Plot ()Source
format the plot elements of a given series
withAllSeriesFormats :: PlotFormats m => (Int -> m ()) -> Plot ()Source
format the plot elements of all series
the operation to modify the formats is passed the series index. This allows, for example, colours to be selected from a list that gets indexed by the argument
setColour = withAllSeriesFormats (\i -> do setLineColour $ [black,blue,red,green,yellow] !! i setLineWidth 1.0)
Range
setRangeFromData :: AxisType -> AxisSide -> Scale -> Plot ()Source
set the axis ranges to values based on dataset
Axes
Instances
Monad Axis | |
MonadReader Options Axis | |
MonadState AxisData Axis |
Instances
Eq AxisSide | |
Ordinate (Function, AxisSide) | |
Ordinate (Series, AxisSide) | |
Ordinate (Function, AxisSide, SeriesLabel) | |
Ordinate (MinMaxSeries, (ErrorSeries, ErrorSeries), AxisSide) | |
Ordinate (Series, (ErrorSeries, ErrorSeries), AxisSide) | |
Ordinate (Series, ErrorSeries, AxisSide) | |
Ordinate (Series, AxisSide, SeriesLabel) | |
Ordinate (MinMaxSeries, (ErrorSeries, ErrorSeries), AxisSide, SeriesLabel) | |
Ordinate (Series, (ErrorSeries, ErrorSeries), AxisSide, SeriesLabel) | |
Ordinate (Series, ErrorSeries, AxisSide, SeriesLabel) |
Legend
Instances
Monad Legend | |
MonadReader TextOptions Legend | |
MonadState (Maybe LegendData) Legend |
type LegendBorder = BoolSource
data LegendLocation Source
Instances
data LegendOrientation Source
clear the legend
setLegend :: LegendBorder -> LegendLocation -> LegendOrientation -> Plot ()Source
set the legend location and orientation
Formatting
setTickLabelFormat :: String -> Axis ()Source
printf format that takes one argument, the tick value
Lines
Instances
Monad Line | |
PlotFormats Line | |
MonadReader LineOptions Line | |
MonadState LineType Line |
class LineFormat a Source
Instances
LineFormat LineWidth | |
LineFormat DashStyle | |
Real a => LineFormat (Colour a) | |
Real a => LineFormat (LineWidth, Colour a) | |
Real a => LineFormat (DashStyle, Colour a) | |
LineFormat (DashStyle, LineWidth) | |
Real a => LineFormat (DashStyle, LineWidth, Colour a) |
clearLineFormat :: Line ()Source
clear the formatting of a line
setDashStyle :: DashStyle -> Line ()Source
change the dash style of a line
setLineWidth :: LineWidth -> Line ()Source
change the line width of a line
setLineColour :: Color -> Line ()Source
change the line colour of a line
Points
Instances
Monad Point | |
PlotFormats Point | |
MonadReader PointOptions Point | |
MonadState PointType Point |
class PointFormat a Source
Instances
PointFormat Glyph | |
Real a => PointFormat (Colour a) | |
Real a => PointFormat (Glyph, Colour a) | |
PointFormat (Glyph, PointSize) | |
Real a => PointFormat (Glyph, PointSize, Colour a) |
Instances
PointFormat Glyph | |
Supply SupplyData Glyph | |
Real a => PointFormat (Glyph, Colour a) | |
PointFormat (Glyph, PointSize) | |
Real a => PointFormat (Glyph, PointSize, Colour a) |
setPointSize :: PointSize -> Point ()Source
change the size of a point
setPointColour :: Color -> Point ()Source
change the colour of a point
Bars
Instances
Monad Bar | |
PlotFormats Bar | |
MonadReader BarOptions Bar | |
MonadState BarType Bar |
clearBarFormat :: Bar ()Source
clear the formatting of a line
setBarWidth :: Width -> Bar ()Source
set the width of the bar
setBarColour :: Color -> Bar ()Source
set the colour of the bar
setBarBorderWidth :: LineWidth -> Bar ()Source
set the width of the bar border
setBarBorderColour :: Color -> Bar ()Source
set the colour of the bar border
Text labels
Instances
Monad Text | |
MonadReader TextOptions Text | |
MonadState TextEntry Text |
type FontFamily = StringSource
A text element must exist for formatting to work
clearTextFormat :: Text ()Source
set the text formatting to the default
setFontFamily :: FontFamily -> Text ()Source
set the font style of a text entry
setFontStyle :: FontStyle -> Text ()Source
set the font style of a text entry
setFontVariant :: Variant -> Text ()Source
set the font variant of a text entry
setFontWeight :: Weight -> Text ()Source
set the font weight of a text entry
setFontStretch :: Stretch -> Text ()Source
set the font stretch of a text entry
setFontSize :: FontSize -> Text ()Source
set the font size of a text entry
setFontColour :: Color -> Text ()Source
set the colour of a text entry