matplotlib-0.1.1.0: Bindings to Matplotlib; a Python plotting library

Safe HaskellNone
LanguageHaskell2010

Graphics.Matplotlib

Synopsis

Documentation

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

A handle internal function

data Matplotlib Source #

The wrapper type for a matplotlib computation. This is opaque.

Constructors

Matplotlib [MplotCommand] 

data MplotCommand Source #

A maplotlib command, right now we have a very shallow embedding essentially dealing in opaque strings containing python code as well as the ability to load data. The loaded should be a json object.

data Option Source #

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

Constructors

K String String

results in a=b

B String

just inserts the option verbatim as an argument at the end of the function

toPy :: MplotCommand -> String Source #

Convert an MplotCommand to python code, doesn't do much right now

withMplot :: Matplotlib -> ([String] -> IO a) -> IO a Source #

The io action is given a list of python commands to execute (note that these are commands in the sense of lines of python code; each inidivudal line may not be parseable on its own

python :: Foldable t => t String -> IO (Either String String) Source #

Run python given a code string.

pyIncludes :: [[Char]] Source #

The standard python includes of every plot

pyReadData :: [Char] -> [[Char]] Source #

The python command that reads external data into the python data array

pyDetach :: [[Char]] Source #

Detach python so we don't block (TODO This isn't working reliably)

pyOnscreen :: [[Char]] Source #

Python code to show a plot

pyFigure :: [Char] -> [[Char]] Source #

Python code that saves a figure

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

Show a plot, blocks until the figure is closed

code :: Matplotlib -> IO (Either a String) Source #

Print the python code that would be executed

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

Save to a file

mplot :: String -> Matplotlib Source #

Create a plot that executes the string as python code

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

combine two matplotlib commands

class MplotValue val where Source #

Values which can be combined together to form a matplotlib command. Right now matplotlib commands are strings and this is just a helper to construct them.

Minimal complete definition

(#)

Methods

(#) :: String -> val -> String infixl 6 Source #

Instances

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

Plot the a and b entries of the data object

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

Plot the Haskell objects x and y as a line

showPlot :: (ToJSON t, ToJSON t1) => t1 -> t -> [Option] -> IO (Either String String) Source #

Plot & show onscreen

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

Load the given data into the 'data' array

options :: [Option] -> String Source #

An internal helper to convert a list of options to the python code that applies those options in a call.

def :: Option -> [Option] -> [Option] Source #

Combine a list of user options with a default; useful for options such as line styles that require sane defaults but can be overriden.

gridLines :: Matplotlib Source #

Show grid lines

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.

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

Add a label to the x axis

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

Add a label to the y axis

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

Add a label to the z axis

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

Create a histogram for the a entry of the data array

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

Plot a histogram for the given values with bins

showHistogram :: (ToJSON t, MplotValue val) => t -> val -> [Option] -> IO (Either String String) Source #

Plot & show the histogram

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

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

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

Plot the given values as a scatter plot

showScatter :: (ToJSON t1, ToJSON t) => t1 -> t -> [Option] -> IO (Either String String) Source #

Plot and show a scatter plot

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

Create a line accessing the given entires of the data array

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

Plot a line

lineF :: (ToJSON a, ToJSON b) => (a -> b) -> [a] -> [Option] -> 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.

showLine :: (ToJSON t1, ToJSON t) => t1 -> t -> [Option] -> IO (Either String String) Source #

Plot and show a line

contour :: (Foldable t, Foldable t1, Foldable t2, Foldable t3, Foldable t4, Foldable t5, Ord (t val), Ord (t2 val1), Ord (t4 val2), Ord val, Ord val1, Ord val2, MplotValue val, MplotValue val2, MplotValue val1, ToJSON (t1 (t val)), ToJSON (t3 (t2 val1)), ToJSON (t5 (t4 val2))) => t5 (t4 val2) -> t3 (t2 val1) -> t1 (t val) -> Matplotlib Source #

Create a 3D contour

projections :: (Foldable t, Foldable t1, Foldable t2, Foldable t3, Foldable t4, Foldable t5, Ord (t val), Ord (t2 val1), Ord (t4 val2), Ord val, Ord val1, Ord val2, MplotValue val, MplotValue val2, MplotValue val1, ToJSON (t1 (t val)), ToJSON (t3 (t2 val1)), ToJSON (t5 (t4 val2))) => t5 (t4 val2) -> t3 (t2 val1) -> t1 (t val) -> Matplotlib Source #

Create a 3D projection

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

axis3DProjection :: Matplotlib Source #

Enable 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

minimum2 :: (Ord (t a), Ord a, Foldable t1, Foldable t) => t1 (t a) -> a Source #

Smallest element of a list of lists

maximum2 :: (Ord (t a), Ord a, Foldable t1, Foldable t) => t1 (t a) -> a Source #

Largest element of a list of lists

axis3DLabels :: (Foldable t, Foldable t1, Foldable t2, Foldable t3, Foldable t4, Foldable t5, Ord (t val), Ord (t2 val1), Ord (t4 val2), Ord val, Ord val1, Ord val2, MplotValue val, MplotValue val1, MplotValue val2) => t5 (t4 val2) -> t3 (t2 val1) -> t1 (t val) -> 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.

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

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

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

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

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

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

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

The default bar with

subplotBarsLabelled :: (MplotValue val, Foldable t, ToJSON (t a)) => [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..

addTitle :: MplotValue val => val -> [Option] -> Matplotlib Source #

Add a title

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

Set the spacing of ticks on the x axis

axisXTickLabels :: MplotValue val => val -> [Option] -> Matplotlib Source #

Set the labels on the x axis

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

Update the data array to linearly interpolate between array entries

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

Plot x against y interpolating with n steps

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

plotMapLinear :: ToJSON b => (Double -> b) -> Double -> Double -> Double -> [Option] -> 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 -> [Option] -> Matplotlib Source #

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

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

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

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

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