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

Graphics.Matplotlib.Internal

Description

Internal representations of the Matplotlib data. These are not API-stable and may change. You can easily extend the provided bindings without relying on the internals exposed here but they are provided just in case.

Synopsis

Documentation

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

Basics

data Matplotlib Source #

The wrapper type for a matplotlib computation.

Constructors

Matplotlib 

Fields

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 MplotCommand Source #

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

Constructors

LoadData ByteString 
forall x.MplotImage x => LoadImage x 
Exec 

Fields

  • es :: String
     

Instances

Instances details
NFData MplotCommand Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

rnf :: MplotCommand -> ()

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

P String

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

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

toPy :: MplotCommand -> String Source #

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

resolvePending :: Matplotlib -> Matplotlib Source #

Resolve the pending command with no options provided.

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)

mplotString :: String -> Matplotlib Source #

Create a plot that executes the string as python code

mp :: Matplotlib Source #

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

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

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

Combine two matplotlib commands

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

Add Python code to the last matplotlib command

data S Source #

A string to be rendered in python as a string. In other words it is rendered as str.

Constructors

S String 

Instances

Instances details
Eq S Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

(==) :: S -> S -> Bool

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

Ord S Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

compare :: S -> S -> Ordering

(<) :: S -> S -> Bool

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

(>) :: S -> S -> Bool

(>=) :: S -> S -> Bool

max :: S -> S -> S

min :: S -> S -> S

Show S Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

showsPrec :: Int -> S -> ShowS

show :: S -> String

showList :: [S] -> ShowS

MplotValue S Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: S -> String Source #

toPythonOpt :: S -> String Source #

MplotValue [S] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [S] -> String Source #

toPythonOpt :: [S] -> String Source #

data R Source #

A string to be rendered in python as a raw string. In other words it is rendered as rstr.

Constructors

R String 

Instances

Instances details
Eq R Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

(==) :: R -> R -> Bool

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

Ord R Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

compare :: R -> R -> Ordering

(<) :: R -> R -> Bool

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

(>) :: R -> R -> Bool

(>=) :: R -> R -> Bool

max :: R -> R -> R

min :: R -> R -> R

Show R Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

showsPrec :: Int -> R -> ShowS

show :: R -> String

showList :: [R] -> ShowS

MplotValue R Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: R -> String Source #

toPythonOpt :: R -> String Source #

MplotValue [R] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [R] -> String Source #

toPythonOpt :: [R] -> String Source #

data L Source #

A string to be rendered in python as a raw literal/code. In other words it is inserted directly as is into the code.

Constructors

L String 

Instances

Instances details
Eq L Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

(==) :: L -> L -> Bool

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

Ord L Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

compare :: L -> L -> Ordering

(<) :: L -> L -> Bool

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

(>) :: L -> L -> Bool

(>=) :: L -> L -> Bool

max :: L -> L -> L

min :: L -> L -> L

Show L Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

showsPrec :: Int -> L -> ShowS

show :: L -> String

showList :: [L] -> ShowS

MplotValue L Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: L -> String Source #

toPythonOpt :: L -> String Source #

MplotValue [L] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [L] -> String Source #

toPythonOpt :: [L] -> String Source #

class MplotValue val where Source #

Values which can be combined together to form a matplotlib command. These specify how values are rendered in Python code.

Minimal complete definition

toPython

Methods

toPython :: val -> String Source #

Render a value inline in Python code

toPythonOpt :: val -> String Source #

Render a value as an optional parameter in Python code

Instances

Instances details
MplotValue Bool Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: Bool -> String Source #

toPythonOpt :: Bool -> String Source #

MplotValue Double Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: Double -> String Source #

toPythonOpt :: Double -> String Source #

MplotValue Int Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: Int -> String Source #

toPythonOpt :: Int -> String Source #

MplotValue Integer Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: Integer -> String Source #

toPythonOpt :: Integer -> String Source #

MplotValue String Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: String -> String Source #

toPythonOpt :: String -> String Source #

MplotValue L Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: L -> String Source #

toPythonOpt :: L -> String Source #

MplotValue R Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: R -> String Source #

toPythonOpt :: R -> String Source #

MplotValue S Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: S -> String Source #

toPythonOpt :: S -> String Source #

MplotValue [Double] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [Double] -> String Source #

toPythonOpt :: [Double] -> String Source #

MplotValue [Int] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [Int] -> String Source #

toPythonOpt :: [Int] -> String Source #

MplotValue [Integer] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [Integer] -> String Source #

toPythonOpt :: [Integer] -> String Source #

MplotValue [[Double]] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [[Double]] -> String Source #

toPythonOpt :: [[Double]] -> String Source #

MplotValue (x, y) => MplotValue [(x, y)] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [(x, y)] -> String Source #

toPythonOpt :: [(x, y)] -> String Source #

MplotValue [String] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [String] -> String Source #

toPythonOpt :: [String] -> String Source #

MplotValue [L] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [L] -> String Source #

toPythonOpt :: [L] -> String Source #

MplotValue [R] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [R] -> String Source #

toPythonOpt :: [R] -> String Source #

MplotValue [S] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: [S] -> String Source #

toPythonOpt :: [S] -> String Source #

MplotValue x => MplotValue (Maybe x) Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: Maybe x -> String Source #

toPythonOpt :: Maybe x -> String Source #

MplotValue x => MplotValue (x, x) Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

toPython :: (x, x) -> String Source #

toPythonOpt :: (x, x) -> String Source #

class MplotImage a where Source #

The class of Haskell images or references to imagese which can be transferred to matplotlib.

Methods

saveHaskellImage :: a -> FilePath -> IO String Source #

loadPythonImage :: a -> String -> FilePath -> String Source #

Instances

Instances details
MplotImage String Source #

An image that is a string is a file path.

Instance details

Defined in Graphics.Matplotlib.Internal

Methods

saveHaskellImage :: String -> FilePath -> IO String Source #

loadPythonImage :: String -> String -> FilePath -> String Source #

ToJSON a => MplotImage [[a]] Source # 
Instance details

Defined in Graphics.Matplotlib.Internal

Methods

saveHaskellImage :: [[a]] -> FilePath -> IO String Source #

loadPythonImage :: [[a]] -> String -> FilePath -> String Source #

Options

optFn :: ([Option] -> String) -> Matplotlib -> Matplotlib Source #

Add an option to the last matplotlib command. Commands can have only one option! optFn :: Matplotlib -> Matplotlib

options :: Matplotlib -> Matplotlib Source #

Merge two commands with options between

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

A combinator like # that also inserts an option

renderOptions :: [Option] -> [Char] Source #

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

optionFn :: ([Option] -> [Option]) -> Matplotlib -> Matplotlib Source #

An internal helper that modifies the options of a plot.

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

Apply a list of options to a plot resolving any pending options.

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

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

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

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

Merge two sets of options

Python operations

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

Run python given a code string.

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

pyIncludes :: String -> [[Char]] Source #

The standard python includes of every plot

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

These will be Python strings and slashes would cause unwanted control characters.

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

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

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

The python command that reads an image into the img variable

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

pySVG :: [[Char]] Source #

Python code that returns SVG for a figure

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

Create a positional option

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

Create a keyword option

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.

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