matplotlib-0.7.7: Bindings to Matplotlib; a Python plotting library
Safe HaskellNone
LanguageHaskell2010

Graphics.Matplotlib

Description

Matplotlib bindings and an interface to easily bind to new portions of the API. The most essential parts of Matplotlib are wrapped and exposed to Haskell through an interface that allows extenisbility. Code is generated on the fly and Python is called.

You should start by looking at the tests, they demonstrate how to create many different types of plots.

This is not a very Haskell-ish library. Type safety is non-existent. It's easy to generate incorrect Python code. But in exchange, we can bind to arbitrary matplotlib APIs with ease, so it's also easy to generate correct Python code.

The generated code follows a few simple conventions. Data is always loaded into a data variable that is a Python array. Data is transffered via JSON. This data variable is indexed by various rendering commands.

Functions which start with the word data operate on the data array, arguments are Python code that should access that array. Most other functions take Haskell objects and load them into Python.

This module should expose enough tools so that you can bind any part of the matplotlib API. A binding with options, such as that of plot, looks like:

  readData (x, y)
  % mp # "p = plot.plot(data[" # a # "], data[" # b # "]" ## ")"
  % mp # "plot.xlabel(" # str label # ")"

Where important functions are:

readData
Load the given data by serializing it to JSON and place it in a Python array named "data".
readImage
Load an image from a given path and place it in a Python variable named "img".
%
Sequence two plots
mp
Create an empty plot
#
Append Python code to the last command in a plot
##
Just like # but also adds in a placeholder for an options list
bindDefault
Set a default in the last options list, keeping it open for additions

You can call this plot with

plot [1,2,3,4,5,6] [1,3,2,5,2] @@ [o1 "go-", o2 "linewidth" 2]

where @@ applies an options list replacing the last ##

o1
A single positional option. The value is rendered into Python as the appropriate datatype. Strings become Python strings, bools become bools, etc. If you want to insert code verbatim into an option use lit. If you want to have a raw string with no escapes use raw.
o2
A keyword option. The key is always a string, the value is treated the same way that the option in o1 is treated.

Right now there's no easy way to bind to an option other than the last one unless you want to pass options in as parameters.

The generated Python code should follow some invariants. It must maintain the current figure in "fig", all available axes in "axes", and the current axis in "ax". Plotting commands should use the current axis, never the plot itself; the two APIs are almost identical. When creating low-level bindings one must remember to call "plot.sci" to set the current image when plotting a graph. The current spine of the axes that's being manipulated is in "spine". The current quiver is in "q".

Synopsis

Documentation

onscreen :: Matplotlib -> IO () Source #

Show a plot, blocks until the figure is closed

code :: Matplotlib -> IO String Source #

Print the python code that would be executed

file :: [Char] -> Matplotlib -> IO (Either String String) Source #

Save to a file

toSvg :: Matplotlib -> IO (Either String String) Source #

Get the SVG for a figure

xacorr :: (ToJSON a, ToJSON b) => a -> b -> [Option] -> Matplotlib Source #

Plot the cross-correlation and autocorrelation of several variables. TODO Due to a limitation in the options mechanism this takes explicit options.

histogram :: (MplotValue val, ToJSON t) => t -> val -> Matplotlib Source #

Plot a histogram for the given values with bins

histogram2D :: ToJSON a => a -> a -> Matplotlib Source #

Plot a 2D histogram for the given values with bins

scatter :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib Source #

Plot the given values as a scatter plot

bar :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib Source #

Create a bar at a position with a height

line :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib Source #

Plot a line

errorbar :: (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => a -> b -> c -> d -> Matplotlib Source #

Like plot but takes an error bar value per point errorbar :: (ToJSON x, ToJSON y, ToJSON xs, ToJSON ys) => x -> y -> Maybe xs -> Maybe ys -> Matplotlib

lineF :: (ToJSON a, ToJSON b) => (a -> b) -> [a] -> Matplotlib Source #

Plot a line given a function that will be executed for each element of given list. The list provides the x values, the function the y values.

boxplot :: ToJSON a => a -> Matplotlib Source #

Create a box plot for the given data

violinplot :: ToJSON a => a -> Matplotlib Source #

Create a violin plot for the given data

contourF :: (ToJSON val, MplotValue val, Ord val) => (Double -> Double -> val) -> Double -> Double -> Double -> Double -> Double -> Matplotlib Source #

Given a grid of x and y values and a number of steps call the given function and plot the 3D contour

projectionsF :: (ToJSON val, MplotValue val, Ord val) => (Double -> Double -> val) -> Double -> Double -> Double -> Double -> Double -> Matplotlib Source #

Given a grid of x and y values and a number of steps call the given function and plot the 3D projection

plotInterpolated :: (MplotValue val, ToJSON t, ToJSON t1) => t1 -> t -> val -> Matplotlib Source #

Plot x against y interpolating with n steps

plotMapLinear :: ToJSON b => (Double -> b) -> Double -> Double -> Double -> Matplotlib Source #

A handy function to plot a line between two points give a function and a number o steps

line1 :: (Foldable t, ToJSON (t a)) => t a -> Matplotlib Source #

Plot a line between 0 and the length of the array with the given y values

matShow :: ToJSON a => a -> Matplotlib Source #

Plot a matrix

imshow :: MplotImage a => a -> Matplotlib Source #

Plot an image

pcolor :: ToJSON a => a -> Matplotlib Source #

Plot a matrix

pcolor3 :: (ToJSON a, ToJSON b, ToJSON c) => a -> b -> c -> Matplotlib Source #

Plot a matrix

nonUniformImage :: (ToJSON a, ToJSON b, ToJSON c) => a -> b -> c -> Matplotlib Source #

Create a non-uniform image from samples

pie :: (ToJSON val, MplotValue val) => val -> Matplotlib Source #

Create a pie chart

density :: [Double] -> Maybe (Double, Double) -> Matplotlib Source #

Plot a KDE of the given functions; a good bandwith will be chosen automatically

rc :: String -> Matplotlib Source #

Set an rc parameter

setParameter :: MplotValue val => String -> val -> Matplotlib Source #

Set an rcParams key-value

setTeX :: Bool -> Matplotlib Source #

Enable or disable TeX

dataPlot :: (MplotValue val, MplotValue val1) => val1 -> val -> Matplotlib Source #

Plot the a and b entries of the data object

plot :: (ToJSON t, ToJSON t1) => t1 -> t -> Matplotlib Source #

Plot the Haskell objects x and y as a line

streamplot :: (ToJSON a, ToJSON b, ToJSON c, ToJSON d) => a -> b -> c -> d -> Matplotlib Source #

dateLine :: (ToJSON t1, ToJSON t2) => t1 -> t2 -> String -> (Int, Int, Int) -> Matplotlib Source #

Plot x against y where x is a date. xunit is something like weeks, yearStart, monthStart, dayStart are an offset to x. TODO This isn't general enough; it's missing some settings about the format. The call is also a mess.

dataHistogram :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Create a histogram for the a entry of the data array

dataScatter :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Create a scatter plot accessing the given fields of the data array

dataLine :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Create a line accessing the given entires of the data array

contour :: (ToJSON (t2 (t3 val1)), ToJSON (t4 (t5 val2)), ToJSON (t6 (t7 val3)), MplotValue val2, MplotValue val1, MplotValue val3, Ord val1, Ord val2, Ord val3, Ord (t3 val1), Ord (t5 val2), Ord (t7 val3), Foldable t2, Foldable t3, Foldable t4, Foldable t5, Foldable t6, Foldable t7) => t2 (t3 val1) -> t4 (t5 val2) -> t6 (t7 val3) -> Matplotlib Source #

Create a 3D contour

projections :: (ToJSON (t2 (t3 val1)), ToJSON (t4 (t5 val2)), ToJSON (t6 (t7 val3)), MplotValue val2, MplotValue val1, MplotValue val3, Ord val1, Ord val2, Ord val3, Ord (t3 val1), Ord (t5 val2), Ord (t7 val3), Foldable t2, Foldable t3, Foldable t4, Foldable t5, Foldable t6, Foldable t7) => t2 (t3 val1) -> t4 (t5 val2) -> t6 (t7 val3) -> Matplotlib Source #

Create a 3D projection

wireframe :: (MplotValue val2, MplotValue val1, MplotValue val) => val2 -> val1 -> val -> Matplotlib Source #

Plot a 3D wireframe accessing the given elements of the data array

surface :: (MplotValue val2, MplotValue val1, MplotValue val) => val2 -> val1 -> val -> Matplotlib Source #

Plot a 3D surface accessing the given elements of the data array

contourRaw :: (MplotValue val1, MplotValue val2, MplotValue val5, MplotValue val4, MplotValue val3, MplotValue val) => val5 -> val4 -> val3 -> val2 -> val1 -> val -> Matplotlib Source #

Plot a contour accessing the given elements of the data array

subplotDataBar :: (MplotValue val1, MplotValue val2, MplotValue val3) => val2 -> val1 -> val3 -> [Option] -> Matplotlib Source #

Draw a bag graph in a subplot TODO Why do we need this?

barDefaultWidth :: (Fractional a1, Integral a2) => a2 -> a1 Source #

The default bar with

subplotBarsLabelled :: (ToJSON (t a), Foldable t, MplotValue val) => [t a] -> val -> [[Option]] -> Matplotlib Source #

Create a set of labelled bars of a given height

subplotBars :: ToJSON a => [a] -> [[Option]] -> Matplotlib Source #

Create a subplot and a set of labelled bars TODO This is a mess..

interpolate :: (MplotValue val, MplotValue val2, MplotValue val1) => val2 -> val1 -> val -> Matplotlib Source #

Update the data array to linearly interpolate between array entries

densityBandwidth :: [Double] -> Double -> Maybe (Double, Double) -> Matplotlib Source #

Plot a KDE of the given functions with an optional start/end and a bandwidth h

xcorr :: (ToJSON a, ToJSON b) => a -> b -> Matplotlib Source #

Plot cross-correlation

acorr :: ToJSON a => a -> Matplotlib Source #

Plot auto-correlation

quiver :: (ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => a -> b -> c -> d -> Maybe e -> Matplotlib Source #

A quiver plot; color is optional and can be nothing

quiverKey :: (MplotValue val1, MplotValue val2, MplotValue val3, MplotValue val4) => val4 -> val3 -> val2 -> val1 -> Matplotlib Source #

A key of a given size with a label for a quiver plot

text :: (MplotValue val1, MplotValue val2) => val2 -> val1 -> String -> Matplotlib Source #

Plot text at a specified location

figText :: (MplotValue val1, MplotValue val2) => val2 -> val1 -> String -> Matplotlib Source #

Add a text to a figure instead of a particular plot

annotate :: String -> Matplotlib Source #

Add an annotation

setAspect :: Matplotlib Source #

Square up the aspect ratio of a plot.

squareAxes :: Matplotlib Source #

Square up the aspect ratio of a plot.

roateAxesLabels :: MplotValue val => val -> Matplotlib Source #

Set the rotation of the labels on the x axis to the given number of degrees

verticalAxes :: Matplotlib Source #

Set the x labels to be vertical

logX :: Matplotlib Source #

Set the x scale to be logarithmic

logY :: Matplotlib Source #

Set the y scale to be logarithmic

xlim :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Set limits on the x axis

ylim :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Set limits on the y axis

axhline :: MplotValue val => val -> Matplotlib Source #

Add a horizontal line across the axis

legend :: Matplotlib Source #

Insert a legend

colorbar :: Matplotlib Source #

Insert a color bar TODO This refers to the plot and not an axis. Might cause trouble with subplots

title :: String -> Matplotlib Source #

Add a title

grid :: Bool -> Matplotlib Source #

Show/hide grid lines

axis3DProjection :: Matplotlib Source #

Enable 3D projection

axis3DLabels :: (MplotValue val1, MplotValue val2, MplotValue val3, Ord val1, Ord val2, Ord val3, Ord (t2 val1), Ord (t3 val2), Ord (t4 val3), Foldable t5, Foldable t2, Foldable t6, Foldable t3, Foldable t7, Foldable t4) => t5 (t2 val1) -> t6 (t3 val2) -> t7 (t4 val3) -> Matplotlib Source #

Label and set limits of a set of 3D axis TODO This is a mess, does both more and less than it claims.

xlabel :: String -> Matplotlib Source #

Add a label to the x axis

ylabel :: String -> Matplotlib Source #

Add a label to the y axis

zlabel :: String -> Matplotlib Source #

Add a label to the z axis

setSizeInches :: (MplotValue val1, MplotValue val2) => val2 -> val1 -> Matplotlib Source #

axisXTickSpacing :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Set the spacing of ticks on the x axis

axisXTickLabels :: MplotValue val => val -> Matplotlib Source #

Set the labels on the x axis

axisYTickSpacing :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib Source #

Set the spacing of ticks on the y axis

axisYTickLabels :: MplotValue val => val -> Matplotlib Source #

Set the labels on the y axis

spineSetBounds :: (MplotValue val1, MplotValue val2) => val2 -> val1 -> Matplotlib Source #

spineSetPosition :: (MplotValue val1, MplotValue val2) => val2 -> val1 -> Matplotlib Source #

addSubplot :: (MplotValue val1, MplotValue val2, MplotValue val3) => val3 -> val2 -> val1 -> Matplotlib Source #

Create a subplot with the coordinates (r,c,f)

getSubplot :: (MplotValue val1, MplotValue val2, MplotValue val3) => val3 -> val2 -> val1 -> Matplotlib Source #

Access a subplot with the coordinates (r,c,f)

subplots :: Matplotlib Source #

Creates subplots and stores them in an internal variable

setSubplot :: MplotValue val => val -> Matplotlib Source #

Access a subplot

axes :: Matplotlib Source #

Add axes to a plot

addAxes :: Matplotlib Source #

Add axes to a figure

figure :: Matplotlib Source #

Creates a new figure with the given id. If the Id is already in use it switches to that figure.

Creating custom plots and applying options

data Matplotlib Source #

The wrapper type for a matplotlib computation.

Instances

Instances details
Semigroup Matplotlib Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

(<>) :: Matplotlib -> Matplotlib -> Matplotlib

sconcat :: NonEmpty Matplotlib -> Matplotlib

stimes :: Integral b => b -> Matplotlib -> Matplotlib

Monoid Matplotlib Source #

Monoid instance for Matplotlib type

Instance details

Defined in Graphics.Matplotlib.Internal

NFData Matplotlib Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

rnf :: Matplotlib -> ()

data Option Source #

Throughout the API we need to accept options in order to expose matplotlib's many configuration options.

Instances

Instances details
Eq Option Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

(==) :: Option -> Option -> Bool

(/=) :: Option -> Option -> Bool

Ord Option Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

compare :: Option -> Option -> Ordering

(<) :: Option -> Option -> Bool

(<=) :: Option -> Option -> Bool

(>) :: Option -> Option -> Bool

(>=) :: Option -> Option -> Bool

max :: Option -> Option -> Option

min :: Option -> Option -> Option

Show Option Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

showsPrec :: Int -> Option -> ShowS

show :: Option -> String

showList :: [Option] -> ShowS

(@@) :: Matplotlib -> [Option] -> Matplotlib infixl 6 Source #

A combinator for option that applies a list of options to a plot

(%) :: Matplotlib -> Matplotlib -> Matplotlib infixl 5 Source #

Combine two matplotlib commands

o1 :: MplotValue val => val -> Option Source #

Create a positional option

o2 :: MplotValue val => String -> val -> Option Source #

Create a keyword option

(##) :: MplotValue val => Matplotlib -> val -> Matplotlib infixl 6 Source #

A combinator like # that also inserts an option

(#) :: MplotValue val => Matplotlib -> val -> Matplotlib infixl 6 Source #

Add Python code to the last matplotlib command

mp :: Matplotlib Source #

Create an empty plot. This the beginning of most plotting commands.

bindDefault :: Matplotlib -> [Option] -> Matplotlib Source #

Bind a list of default options to a plot. Positional options are kept in order and default that way as well. Keyword arguments are also handled

readData :: ToJSON a => a -> Matplotlib Source #

Load the given data into the python "data" array

readImage :: MplotImage i => i -> Matplotlib Source #

Load the given image into python "img" variable

str :: String -> S Source #

Create a string that will be rendered as a python string

raw :: String -> R Source #

Create a string that will be rendered as a raw python string

lit :: String -> L Source #

Create a literal that will inserted into the python code directly

updateAxes :: Matplotlib Source #

Update axes. Should be called any time the state is changed.

updateFigure :: Matplotlib Source #

Update the figure and the axes. Should be called any time the state is changed.

mapLinear :: (Double -> b) -> Double -> Double -> Double -> [b] Source #

A handy miscellaneous function to linearly map over a range of numbers in a given number of steps