Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- mapLinear :: (Double -> b) -> Double -> Double -> Double -> [b]
- data Matplotlib = Matplotlib {
- mpCommands :: Seq MplotCommand
- mpPendingOption :: Maybe ([Option] -> MplotCommand)
- mpRest :: Seq MplotCommand
- data MplotCommand
- = LoadData ByteString
- | forall x.MplotImage x => LoadImage x
- | Exec { }
- data Option
- toPy :: MplotCommand -> String
- resolvePending :: Matplotlib -> Matplotlib
- withMplot :: Matplotlib -> ([String] -> IO a) -> IO a
- mplotString :: String -> Matplotlib
- mp :: Matplotlib
- readData :: ToJSON a => a -> Matplotlib
- readImage :: MplotImage i => i -> Matplotlib
- (%) :: Matplotlib -> Matplotlib -> Matplotlib
- (#) :: MplotValue val => Matplotlib -> val -> Matplotlib
- data S = S String
- data R = R String
- data L = L String
- class MplotValue val where
- toPython :: val -> String
- toPythonOpt :: val -> String
- class MplotImage a where
- saveHaskellImage :: a -> FilePath -> IO String
- loadPythonImage :: a -> String -> FilePath -> String
- optFn :: ([Option] -> String) -> Matplotlib -> Matplotlib
- options :: Matplotlib -> Matplotlib
- (##) :: MplotValue val => Matplotlib -> val -> Matplotlib
- renderOptions :: [Option] -> [Char]
- optionFn :: ([Option] -> [Option]) -> Matplotlib -> Matplotlib
- option :: Matplotlib -> [Option] -> Matplotlib
- (@@) :: Matplotlib -> [Option] -> Matplotlib
- def :: Matplotlib -> [Option] -> Matplotlib
- defFn :: [Option] -> [Option] -> [Option]
- python :: Foldable t => t String -> IO (Either String String)
- pyBackend :: [Char] -> [Char]
- pyIncludes :: String -> [[Char]]
- escapeSlashes :: [Char] -> [Char]
- pyReadData :: [Char] -> [[Char]]
- pyReadImage :: [Char] -> [[Char]]
- pyDetach :: [[Char]]
- pyOnscreen :: [[Char]]
- pyFigure :: [Char] -> [[Char]]
- pySVG :: [[Char]]
- o1 :: MplotValue val => val -> Option
- o2 :: MplotValue val => String -> val -> Option
- str :: String -> S
- raw :: String -> R
- lit :: String -> L
- updateAxes :: Matplotlib
- updateFigure :: Matplotlib
- minimum2 :: (Ord (t a), Ord a, Foldable t1, Foldable t) => t1 (t a) -> a
- maximum2 :: (Ord (t a), Ord a, Foldable t1, Foldable t) => t1 (t a) -> a
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.
Matplotlib | |
|
Instances
Semigroup Matplotlib Source # | |
Defined in Graphics.Matplotlib.Internal (<>) :: Matplotlib -> Matplotlib -> Matplotlib # sconcat :: NonEmpty Matplotlib -> Matplotlib # stimes :: Integral b => b -> Matplotlib -> Matplotlib # | |
Monoid Matplotlib Source # | Monoid instance for Matplotlib type |
Defined in Graphics.Matplotlib.Internal mempty :: Matplotlib # mappend :: Matplotlib -> Matplotlib -> Matplotlib # mconcat :: [Matplotlib] -> Matplotlib # | |
NFData Matplotlib Source # | |
Defined in Graphics.Matplotlib.Internal 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.
LoadData ByteString | |
forall x.MplotImage x => LoadImage x | |
Exec | |
Instances
NFData MplotCommand Source # | |
Defined in Graphics.Matplotlib.Internal rnf :: MplotCommand -> () # |
Throughout the API we need to accept options in order to expose matplotlib's many configuration options.
K String String | results in a=b |
P 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
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
A string to be rendered in python as a string. In other words it is
rendered as str
.
A string to be rendered in python as a raw string. In other words it is
rendered as rstr
.
A string to be rendered in python as a raw literal/code. In other words it is inserted directly as is into the code.
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.
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
MplotValue Bool Source # | |
MplotValue Double Source # | |
MplotValue Int Source # | |
MplotValue Integer Source # | |
MplotValue String Source # | |
MplotValue L Source # | |
MplotValue R Source # | |
MplotValue S Source # | |
MplotValue [Double] Source # | |
MplotValue [Int] Source # | |
MplotValue [Integer] Source # | |
MplotValue [[Double]] Source # | |
MplotValue (x, y) => MplotValue [(x, y)] Source # | |
Defined in Graphics.Matplotlib.Internal | |
MplotValue [String] Source # | |
MplotValue [L] Source # | |
MplotValue [R] Source # | |
MplotValue [S] Source # | |
MplotValue x => MplotValue (Maybe x) Source # | |
MplotValue x => MplotValue (x, x) Source # | |
Defined in Graphics.Matplotlib.Internal |
class MplotImage a where Source #
The class of Haskell images or references to imagese which can be transferred to matplotlib.
saveHaskellImage :: a -> FilePath -> IO String Source #
loadPythonImage :: a -> String -> FilePath -> String Source #
Instances
MplotImage String Source # | An image that is a string is a file path. |
Defined in Graphics.Matplotlib.Internal | |
ToJSON a => MplotImage [[a]] Source # | |
Defined in Graphics.Matplotlib.Internal |
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
def :: 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
Python operations
python :: Foldable t => t String -> IO (Either String String) Source #
Run python given a code string.
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
pyOnscreen :: [[Char]] Source #
Python code to show a plot
o1 :: MplotValue val => val -> Option Source #
Create a positional option
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.