plot-0.1: A plotting library, exportable as eps/pdf/svg/png or renderable with gtk

Portabilityportable
Stabilityprovisional
Maintainerhaskell.vivian.mcphail <at> gmail <dot> com

Graphics.Rendering.Plot.Figure

Contents

Description

Creation and manipulation of Figures

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

Synopsis

Top level operation

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

newFigure :: Figure ()Source

create a new blank Figure

Formatting

setFigurePadding :: Double -> Double -> Double -> Double -> Figure ()Source

set the padding of the figure

withTitle :: Text () -> Figure ()Source

operate on the title

withSubTitle :: Text () -> Figure ()Source

operate on the sub-title

setPlotsSource

Arguments

:: Int

rows

-> Int

columns

-> Figure () 

set the shape of the plots, losing all current plots

withPlot :: (Int, Int) -> Plot () -> Figure ()Source

perform some actions on the specified subplot

withPlots :: Plot () -> Figure ()Source

perform some actions all subplots

Sub-plots

data Plot a Source

Instances

Monad Plot 
Simple Plot 
MonadReader Options Plot 
MonadState PlotData Plot 
MonadSupply SupplyData Plot 

Plot elements

setBorder :: Border -> Plot ()Source

whether to draw a boundary around the plot area

setPlotPadding :: Double -> Double -> Double -> Double -> Plot ()Source

set the padding of the subplot

withHeading :: Text () -> Plot ()Source

set the heading of the subplot

Series data

class Abscissa a Source

Instances

type FormattedSeries = Data DecoratedSeriesSource

data SeriesType Source

Constructors

Line 
Point 
LinePoint 
Impulse 
Step 
Area 
Bar 
Hist 

Instances

(Abscissa a, Ordinate b) => Dataset [(SeriesType, a, b)] 
Ordinate a => Dataset (SeriesType, [a]) 
(Abscissa a, Ordinate b) => Dataset (SeriesType, a, [b]) 

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

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

data Scale Source

Constructors

Linear 
Log 

Instances

setRange :: AxisType -> AxisSide -> Scale -> Double -> Double -> Plot ()Source

set the axis range

setRangeFromData :: AxisType -> AxisSide -> Scale -> Plot ()Source

set the axis ranges to values based on dataset

Axes

data Axis a Source

Instances

Monad Axis 
MonadReader Options Axis 
MonadState AxisData Axis 

data AxisType Source

Constructors

XAxis 
YAxis 

Instances

data AxisPosn Source

Constructors

Side AxisSide 
Value Double 

Instances

clearAxes :: Plot ()Source

clear the axes of a subplot

clearAxis :: AxisType -> AxisPosn -> Plot ()Source

clear an axis of a subplot

addAxis :: AxisType -> AxisPosn -> Axis () -> Plot ()Source

add an axis to the subplot

withAxis :: AxisType -> AxisPosn -> Axis () -> Plot ()Source

operate on the given axis

Legend

data Legend a Source

Instances

Monad Legend 
MonadReader TextOptions Legend 
MonadState (Maybe LegendData) Legend 

clearLegend :: Plot ()Source

clear the legend

setLegend :: LegendBorder -> LegendLocation -> LegendOrientation -> Plot ()Source

set the legend location and orientation

withLegendFormat :: Text () -> Plot ()Source

format the legend text

Formatting

data Tick Source

Constructors

Minor 
Major 

Instances

type TickValuesSource

Arguments

 = Either Int (Vector Double)

Either (number of ticks) (tick values)

setTicks :: Tick -> TickValues -> Axis ()Source

format the axis ticks

setGridlines :: Tick -> GridLines -> Axis ()Source

should gridlines be displayed?

setTickLabelFormat :: String -> Axis ()Source

printf format that takes one argument, the tick value

withAxisLabel :: Text () -> Axis ()Source

operate on the axis label

withAxisLine :: Line () -> Axis ()Source

format the axis line

Lines

data Line a Source

Instances

data Dash Source

Constructors

Dot 
Dash 

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

data Point a Source

Instances

setGlyph :: Glyph -> Point ()Source

change the glyph of a point

setPointSize :: PointSize -> Point ()Source

change the size of a point

setPointColour :: Color -> Point ()Source

change the colour of a point

Bars

data Bar a Source

Instances

class BarFormat a Source

Instances

BarFormat Width 
Real a => BarFormat (Colour a) 
Real a => BarFormat (Width, Colour a) 
(Real a, Real b) => BarFormat (Width, Colour a, Colour b) 
Real a => BarFormat (Width, Colour a, LineWidth) 
(Real a, Real b) => BarFormat (Width, Colour a, LineWidth, Colour b) 

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

data Text a Source

Instances

Monad Text 
MonadReader TextOptions Text 
MonadState TextEntry Text 

A text element must exist for formatting to work

clearText :: Text ()Source

clear the text entry

clearTextFormat :: Text ()Source

set the text formatting to the default

setText :: String -> Text ()Source

set the value of a text entry

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