{-# LANGUAGE ExtendedDefaultRules #-}
-----------------------------------------------------------------------------
-- |
-- 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.
--
-- This is not a very Haskell-ish library. Type safety is non-existent, it's
-- easy to generate incorrect Python code, in exchange for being able to 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 into the python data array by serializing it to JSON.
--   [@'%'@] 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
--
-- 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"
-----------------------------------------------------------------------------

module Graphics.Matplotlib
  ( module Graphics.Matplotlib
    -- * Creating custom plots and applying options
  , Matplotlib(), Option(),(@@), (%), o1, o2, (##), (#), mp, def, readData, readImage
  , str, raw, lit, updateAxes, updateFigure, mapLinear)
where
import Data.List
import Data.Aeson
import Graphics.Matplotlib.Internal
import Control.Concurrent(forkIO)

-- * Running a plot

-- | Show a plot, blocks until the figure is closed
onscreen :: Matplotlib -> IO ()
onscreen :: Matplotlib -> IO ()
onscreen Matplotlib
m = (IO () -> IO ThreadId
forkIO (IO () -> IO ThreadId) -> IO () -> IO ThreadId
forall a b. (a -> b) -> a -> b
$ (Matplotlib
-> ([String] -> IO (Either String String))
-> IO (Either String String)
forall a. Matplotlib -> ([String] -> IO a) -> IO a
withMplot Matplotlib
m (\[String]
s -> [String] -> IO (Either String String)
forall (t :: * -> *).
Foldable t =>
t String -> IO (Either String String)
python ([String] -> IO (Either String String))
-> [String] -> IO (Either String String)
forall a b. (a -> b) -> a -> b
$ String -> [String]
pyIncludes String
"" [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pyOnscreen) IO (Either String String) -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ())) IO ThreadId -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | Print the python code that would be executed
code :: Matplotlib -> IO String
code :: Matplotlib -> IO String
code Matplotlib
m = Matplotlib -> ([String] -> IO String) -> IO String
forall a. Matplotlib -> ([String] -> IO a) -> IO a
withMplot Matplotlib
m (\[String]
s -> String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> IO String) -> String -> IO String
forall a b. (a -> b) -> a -> b
$ [String] -> String
unlines ([String] -> String) -> [String] -> String
forall a b. (a -> b) -> a -> b
$ String -> [String]
pyIncludes (String -> String
pyBackend String
"agg") [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pyOnscreen)

-- | Save to a file
file :: [Char] -> Matplotlib -> IO (Either String String)
file :: String -> Matplotlib -> IO (Either String String)
file String
filename Matplotlib
m = Matplotlib
-> ([String] -> IO (Either String String))
-> IO (Either String String)
forall a. Matplotlib -> ([String] -> IO a) -> IO a
withMplot Matplotlib
m (\[String]
s -> [String] -> IO (Either String String)
forall (t :: * -> *).
Foldable t =>
t String -> IO (Either String String)
python ([String] -> IO (Either String String))
-> [String] -> IO (Either String String)
forall a b. (a -> b) -> a -> b
$ String -> [String]
pyIncludes (String -> String
pyBackend String
"agg") [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ String -> [String]
pyFigure String
filename)

-- | Get the SVG for a figure
toSvg :: Matplotlib -> IO (Either String String)
toSvg :: Matplotlib -> IO (Either String String)
toSvg Matplotlib
m = Matplotlib
-> ([String] -> IO (Either String String))
-> IO (Either String String)
forall a. Matplotlib -> ([String] -> IO a) -> IO a
withMplot Matplotlib
m (\[String]
s -> [String] -> IO (Either String String)
forall (t :: * -> *).
Foldable t =>
t String -> IO (Either String String)
python ([String] -> IO (Either String String))
-> [String] -> IO (Either String String)
forall a b. (a -> b) -> a -> b
$ String -> [String]
pyIncludes String
"" [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
s [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
pySVG)

-- * Useful plots

-- | Plot the cross-correlation and autocorrelation of several variables. TODO Due to
-- a limitation in the options mechanism this takes explicit options.
xacorr :: a -> b -> [Option] -> Matplotlib
xacorr a
xs b
ys [Option]
opts = (a, b) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
xs, b
ys)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
figure
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> Matplotlib
forall val val val.
(MplotValue val, MplotValue val, MplotValue val) =>
val -> val -> val -> Matplotlib
addSubplot Integer
2 Integer
1 Integer
1
  Matplotlib -> Matplotlib -> Matplotlib
% a -> b -> Matplotlib
forall a b. (ToJSON a, ToJSON b) => a -> b -> Matplotlib
xcorr a
xs b
ys Matplotlib -> [Option] -> Matplotlib
@@ [Option]
opts
  Matplotlib -> Matplotlib -> Matplotlib
% Bool -> Matplotlib
grid Bool
True
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Matplotlib
forall val. MplotValue val => val -> Matplotlib
axhline Integer
0 Matplotlib -> [Option] -> Matplotlib
@@ [Integer -> Option
forall val. MplotValue val => val -> Option
o1 Integer
0, String -> String -> Option
forall val. MplotValue val => String -> val -> Option
o2 String
"color" String
"black", String -> Integer -> Option
forall val. MplotValue val => String -> val -> Option
o2 String
"lw" Integer
2]
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> Matplotlib
forall val val val.
(MplotValue val, MplotValue val, MplotValue val) =>
val -> val -> val -> Matplotlib
addSubplot Integer
2 Integer
1 Integer
2 Matplotlib -> [Option] -> Matplotlib
@@ [String -> L -> Option
forall val. MplotValue val => String -> val -> Option
o2 String
"sharex" (L -> Option) -> L -> Option
forall a b. (a -> b) -> a -> b
$ String -> L
lit String
"ax"]
  Matplotlib -> Matplotlib -> Matplotlib
% a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
acorr a
xs Matplotlib -> [Option] -> Matplotlib
@@ [Option]
opts
  Matplotlib -> Matplotlib -> Matplotlib
% Bool -> Matplotlib
grid Bool
True
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Matplotlib
forall val. MplotValue val => val -> Matplotlib
axhline Integer
0 Matplotlib -> [Option] -> Matplotlib
@@ [String -> String -> Option
forall val. MplotValue val => String -> val -> Option
o2 String
"color" String
"black", String -> Integer -> Option
forall val. MplotValue val => String -> val -> Option
o2 String
"lw" Integer
2]

-- | Plot a histogram for the given values with 'bins'
histogram :: (MplotValue val, ToJSON t) => t -> val -> Matplotlib
histogram :: t -> val -> Matplotlib
histogram t
values val
bins = [t] -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData [t
values] Matplotlib -> Matplotlib -> Matplotlib
% Integer -> val -> Matplotlib
forall val1 val.
(MplotValue val1, MplotValue val) =>
val1 -> val -> Matplotlib
dataHistogram Integer
0 val
bins

-- | Plot a 2D histogram for the given values with 'bins'
histogram2D :: a -> a -> Matplotlib
histogram2D a
x a
y = [a] -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData [a
x,a
y] Matplotlib -> Matplotlib -> Matplotlib
%
  Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.hist2d(data[0], data[1]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")[-1])"

-- | Plot the given values as a scatter plot
scatter :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib
scatter :: t1 -> t -> Matplotlib
scatter t1
x t
y = (t1, t) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1
x, t
y)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.scatter(data[0], data[1]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
"))"

-- | Create a bar at a position with a height
bar :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib
bar :: t1 -> t -> Matplotlib
bar t1
left t
height = (t1, t) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1
left, t
height)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.bar(data[0], data[1]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Plot a line
line :: (ToJSON t1, ToJSON t) => t1 -> t -> Matplotlib
line :: t1 -> t -> Matplotlib
line t1
x t
y = t1 -> t -> Matplotlib
forall t t1. (ToJSON t, ToJSON t1) => t1 -> t -> Matplotlib
plot t1
x t
y Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"-"]

-- | 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
errorbar :: a -> b -> c -> d -> Matplotlib
errorbar a
xs b
ys c
xerrs d
yerrs = (a, b, c, d) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
xs, b
ys, c
xerrs, d
yerrs)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.errorbar(data[0], data[1], xerr=data[2], yerr=data[3]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | 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.
lineF :: (ToJSON a, ToJSON b) => (a -> b) -> [a] -> Matplotlib
lineF :: (a -> b) -> [a] -> Matplotlib
lineF a -> b
f [a]
l = [a] -> [b] -> Matplotlib
forall t t1. (ToJSON t, ToJSON t1) => t1 -> t -> Matplotlib
plot [a]
l ((a -> b) -> [a] -> [b]
forall a b. (a -> b) -> [a] -> [b]
map a -> b
f [a]
l) Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"-"]

-- | Create a box plot for the given data
boxplot :: a -> Matplotlib
boxplot a
d = a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData a
d
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.boxplot(data" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Create a violin plot for the given data
violinplot :: a -> Matplotlib
violinplot a
d = a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData a
d
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.violinplot(data" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Given a grid of x and y values and a number of steps call the given
-- function and plot the 3D contour
contourF :: (ToJSON val, MplotValue val, Ord val) => (Double -> Double -> val) -> Double -> Double -> Double -> Double -> Double -> Matplotlib
contourF :: (Double -> Double -> val)
-> Double -> Double -> Double -> Double -> Double -> Matplotlib
contourF Double -> Double -> val
f Double
xStart Double
xEnd Double
yStart Double
yEnd Double
steps = [[Double]] -> [[Double]] -> [[val]] -> Matplotlib
forall (t1 :: * -> *) (t :: * -> *) val (t1 :: * -> *)
       (t :: * -> *) val (t1 :: * -> *) (t :: * -> *) val.
(ToJSON (t1 (t val)), ToJSON (t1 (t val)), ToJSON (t1 (t val)),
 MplotValue val, MplotValue val, MplotValue val, Ord val, Ord val,
 Ord val, Ord (t val), Ord (t val), Ord (t val), Foldable t1,
 Foldable t, Foldable t1, Foldable t, Foldable t1, Foldable t) =>
t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
contour [[Double]]
xs [[Double]]
ys [[val]]
zs
  where xs :: [[Double]]
xs = (Double -> [Double]) -> Double -> Double -> Double -> [[Double]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> ((Double -> Double) -> Double -> Double -> Double -> [Double]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
_ -> Double
x) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps
        ys :: [[Double]]
ys = (Double -> [Double]) -> Double -> Double -> Double -> [[Double]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
_ -> ((Double -> Double) -> Double -> Double -> Double -> [Double]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
y -> Double
y) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps
        zs :: [[val]]
zs = (Double -> [val]) -> Double -> Double -> Double -> [[val]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> ((Double -> val) -> Double -> Double -> Double -> [val]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
y -> Double -> Double -> val
f Double
x Double
y) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps

-- | Given a grid of x and y values and a number of steps call the given
-- function and plot the 3D projection
projectionsF :: (ToJSON val, MplotValue val, Ord val) => (Double -> Double -> val) -> Double -> Double -> Double -> Double -> Double -> Matplotlib
projectionsF :: (Double -> Double -> val)
-> Double -> Double -> Double -> Double -> Double -> Matplotlib
projectionsF Double -> Double -> val
f Double
xStart Double
xEnd Double
yStart Double
yEnd Double
steps = [[Double]] -> [[Double]] -> [[val]] -> Matplotlib
forall (t1 :: * -> *) (t :: * -> *) val (t1 :: * -> *)
       (t :: * -> *) val (t1 :: * -> *) (t :: * -> *) val.
(ToJSON (t1 (t val)), ToJSON (t1 (t val)), ToJSON (t1 (t val)),
 MplotValue val, MplotValue val, MplotValue val, Ord val, Ord val,
 Ord val, Ord (t val), Ord (t val), Ord (t val), Foldable t1,
 Foldable t, Foldable t1, Foldable t, Foldable t1, Foldable t) =>
t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
projections [[Double]]
xs [[Double]]
ys [[val]]
zs
  where xs :: [[Double]]
xs = (Double -> [Double]) -> Double -> Double -> Double -> [[Double]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> ((Double -> Double) -> Double -> Double -> Double -> [Double]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
_ -> Double
x) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps
        ys :: [[Double]]
ys = (Double -> [Double]) -> Double -> Double -> Double -> [[Double]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
_ -> ((Double -> Double) -> Double -> Double -> Double -> [Double]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
y -> Double
y) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps
        zs :: [[val]]
zs = (Double -> [val]) -> Double -> Double -> Double -> [[val]]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> ((Double -> val) -> Double -> Double -> Double -> [val]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
y -> Double -> Double -> val
f Double
x Double
y) Double
yStart Double
yEnd Double
steps)) Double
xStart Double
xEnd Double
steps

-- | Plot x against y interpolating with n steps
plotInterpolated :: (MplotValue val, ToJSON t, ToJSON t1) => t1 -> t -> val -> Matplotlib
plotInterpolated :: t1 -> t -> val -> Matplotlib
plotInterpolated t1
x t
y val
n =
  (t1, t) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1
x, t
y)
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> val -> Matplotlib
forall val val2 val1.
(MplotValue val, MplotValue val2, MplotValue val1) =>
val2 -> val1 -> val -> Matplotlib
interpolate Integer
0 Integer
1 val
n
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Matplotlib
forall val val1.
(MplotValue val, MplotValue val1) =>
val1 -> val -> Matplotlib
dataPlot Integer
0 Integer
1 Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"-"]

-- | A handy function to plot a line between two points give a function and a number o steps
plotMapLinear :: ToJSON b => (Double -> b) -> Double -> Double -> Double -> Matplotlib
plotMapLinear :: (Double -> b) -> Double -> Double -> Double -> Matplotlib
plotMapLinear Double -> b
f Double
s Double
e Double
n = [Double] -> [b] -> Matplotlib
forall a b. (ToJSON a, ToJSON b) => a -> b -> Matplotlib
line [Double]
xs [b]
ys
  where xs :: [Double]
xs = (Double -> Double) -> Double -> Double -> Double -> [Double]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> Double
x) Double
s Double
e Double
n
        ys :: [b]
ys = (Double -> b) -> Double -> Double -> Double -> [b]
forall b. (Double -> b) -> Double -> Double -> Double -> [b]
mapLinear (\Double
x -> Double -> b
f Double
x) Double
s Double
e Double
n

-- | Plot a line between 0 and the length of the array with the given y values
line1 :: (Foldable t, ToJSON (t a)) => t a -> Matplotlib
line1 :: t a -> Matplotlib
line1 t a
y = [Int] -> t a -> Matplotlib
forall a b. (ToJSON a, ToJSON b) => a -> b -> Matplotlib
line [Int
0..t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length t a
y] t a
y

-- | Plot a matrix
matShow :: ToJSON a => a -> Matplotlib
matShow :: a -> Matplotlib
matShow a
d = a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData a
d
            Matplotlib -> Matplotlib -> Matplotlib
% (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.matshow(data" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
"))")

-- | Plot an image
imshow :: MplotImage a => a -> Matplotlib
imshow :: a -> Matplotlib
imshow a
i = a -> Matplotlib
forall i. MplotImage i => i -> Matplotlib
readImage a
i
            Matplotlib -> Matplotlib -> Matplotlib
% (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.imshow(img" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
"))")

-- | Plot a matrix
pcolor :: ToJSON a => a -> Matplotlib
pcolor :: a -> Matplotlib
pcolor a
d = a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData a
d
            Matplotlib -> Matplotlib -> Matplotlib
% (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.pcolor(np.array(data)" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
"))")

-- | Plot a matrix
pcolor3 :: a -> b -> c -> Matplotlib
pcolor3 a
x b
y c
z = (a, b, c) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
x,b
y,c
z)
                Matplotlib -> Matplotlib -> Matplotlib
% (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sci(ax.pcolor(np.array(data[0]),np.array(data[1]),np.array(data[2])" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
"))")

-- | Create a non-uniform image from samples
nonUniformImage :: a -> b -> c -> Matplotlib
nonUniformImage a
x b
y c
z = (a, b, c) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
x,b
y,c
z)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"im = mpimg.NonUniformImage(ax" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"im.set_data(data[0], data[1], data[2])"

-- | Create a pie chart
pie :: val -> Matplotlib
pie val
l = val -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData val
l
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.pie(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Plot a KDE of the given functions; a good bandwith will be chosen automatically
density :: [Double] -> Maybe (Double, Double) -> Matplotlib
density :: [Double] -> Maybe (Double, Double) -> Matplotlib
density [Double]
l Maybe (Double, Double)
maybeStartEnd =
  [Double] -> Double -> Maybe (Double, Double) -> Matplotlib
densityBandwidth [Double]
l (((Double
4 Double -> Double -> Double
forall a. Num a => a -> a -> a
* (Double
variance Double -> Double -> Double
forall a. Floating a => a -> a -> a
** Double
5)) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ Int
3 Int -> Int -> Int
forall a. Num a => a -> a -> a
* [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
l)) Double -> Double -> Double
forall a. Floating a => a -> a -> a
** (Double
1 Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
5) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
3) Maybe (Double, Double)
maybeStartEnd
  where mean :: Double
mean = (Double -> Double -> Double) -> Double -> [Double] -> Double
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Double -> Double -> Double
forall a. Num a => a -> a -> a
(+) Double
0 [Double]
l Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
l)
        variance :: Double
variance = (Double -> Double -> Double) -> Double -> [Double] -> Double
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' Double -> Double -> Double
forall a. Num a => a -> a -> a
(+) Double
0 ((Double -> Double) -> [Double] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (\Double
x -> Double -> Double
forall a. Num a => a -> a
sqr (Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
mean)) [Double]
l) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ (Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
l)
        sqr :: a -> a
sqr a
x = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x

-- * Matplotlib configuration

-- | Set an rc parameter
rc :: String -> Matplotlib
rc String
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.rc(" Matplotlib -> S -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> S
str String
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Set an rcParams key-value
setParameter :: String -> val -> Matplotlib
setParameter String
k val
v = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"matplotlib.rcParams["Matplotlib -> S -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> S
str String
k Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
"] = " Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
v

-- | Enable or disable TeX
setTeX :: Bool -> Matplotlib
setTeX :: Bool -> Matplotlib
setTeX Bool
b = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.rc('text', usetex="Matplotlib -> Bool -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# Bool
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
")"

-- * Basic plotting commands

-- | Plot the 'a' and 'b' entries of the data object
dataPlot :: (MplotValue val, MplotValue val1) => val1 -> val -> Matplotlib
dataPlot :: val1 -> val -> Matplotlib
dataPlot val1
a val
b = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"p = ax.plot(data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Plot the Haskell objects 'x' and 'y' as a line
plot :: (ToJSON t, ToJSON t1) => t1 -> t -> Matplotlib
plot :: t1 -> t -> Matplotlib
plot t1
x t
y = (t1, t) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1
x, t
y) Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Matplotlib
forall val val1.
(MplotValue val, MplotValue val1) =>
val1 -> val -> Matplotlib
dataPlot Integer
0 Integer
1

streamplot :: a -> b -> c -> d -> Matplotlib
streamplot a
x b
y c
u d
v = (a, b, c, d) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
x, b
y, c
u, d
v)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.streamplot(np.asarray(data[0]), np.asarray(data[1]), np.asarray(data[2]), np.asarray(data[3])" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | 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.
dateLine :: (ToJSON t1, ToJSON t2) => t1 -> t2 -> String -> (Int, Int, Int) -> Matplotlib
dateLine :: t1 -> t2 -> String -> (Int, Int, Int) -> Matplotlib
dateLine t1
x t2
y String
xunit (Int
yearStart, Int
monthStart, Int
dayStart) =
    (t1, t2) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1
x, t2
y)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"data[0] = [datetime.timedelta("Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
xunitMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
"=i) + datetime.datetime("Matplotlib -> Int -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#Int
yearStartMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
","Matplotlib -> Int -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#Int
monthStartMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
","Matplotlib -> Int -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#Int
dayStartMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
") for i in data[0]]"
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Matplotlib
forall val val1.
(MplotValue val, MplotValue val1) =>
val1 -> val -> Matplotlib
dataPlot Integer
0 Integer
1 Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"-"]
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.xaxis.set_major_formatter(DateFormatter('%B'))"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.xaxis.set_minor_locator(WeekdayLocator(byweekday=6))"

-- | Create a histogram for the 'a' entry of the data array
dataHistogram :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
dataHistogram :: val1 -> val -> Matplotlib
dataHistogram val1
a val
bins = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.hist(data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
bins Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Create a scatter plot accessing the given fields of the data array
dataScatter :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
dataScatter :: val1 -> val -> Matplotlib
dataScatter val1
a val
b = val1 -> val -> Matplotlib
forall val val1.
(MplotValue val, MplotValue val1) =>
val1 -> val -> Matplotlib
dataPlot val1
a val
b Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"."]

-- | Create a line accessing the given entires of the data array
dataLine :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
dataLine :: val1 -> val -> Matplotlib
dataLine val1
a val
b = val1 -> val -> Matplotlib
forall val val1.
(MplotValue val, MplotValue val1) =>
val1 -> val -> Matplotlib
dataPlot val1
a val
b Matplotlib -> [Option] -> Matplotlib
`def` [String -> Option
forall val. MplotValue val => val -> Option
o1 String
"-"]

-- | Create a 3D contour
contour :: t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
contour t1 (t val)
xs t1 (t val)
ys t1 (t val)
zs =
  (t1 (t val), t1 (t val), t1 (t val)) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1 (t val)
xs, t1 (t val)
ys, t1 (t val)
zs)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
axis3DProjection
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> Matplotlib
forall val2 val1 val.
(MplotValue val2, MplotValue val1, MplotValue val) =>
val2 -> val1 -> val -> Matplotlib
surface Integer
0 Integer
1 Integer
2
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> val -> val -> val -> Matplotlib
forall val1 val2 val5 val4 val3 val.
(MplotValue val1, MplotValue val2, MplotValue val5,
 MplotValue val4, MplotValue val3, MplotValue val) =>
val5 -> val4 -> val3 -> val2 -> val1 -> val -> Matplotlib
contourRaw Integer
0 Integer
1 Integer
2 (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
xs) (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
ys) (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
minimum2 t1 (t val)
zs)
  Matplotlib -> Matplotlib -> Matplotlib
% t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
forall val val val (t :: * -> *) (t :: * -> *) (t :: * -> *)
       (t1 :: * -> *) (t1 :: * -> *) (t1 :: * -> *).
(MplotValue val, MplotValue val, MplotValue val, Ord val, Ord val,
 Ord val, Ord (t val), Ord (t val), Ord (t val), Foldable t1,
 Foldable t, Foldable t1, Foldable t, Foldable t1, Foldable t) =>
t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
axis3DLabels t1 (t val)
xs t1 (t val)
ys t1 (t val)
zs

-- | Create a 3D projection
projections :: t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
projections t1 (t val)
xs t1 (t val)
ys t1 (t val)
zs =
  (t1 (t val), t1 (t val), t1 (t val)) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (t1 (t val)
xs, t1 (t val)
ys, t1 (t val)
zs)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
axis3DProjection
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> val -> val -> val -> Matplotlib
forall val1 val2 val5 val4 val3 val.
(MplotValue val1, MplotValue val2, MplotValue val5,
 MplotValue val4, MplotValue val3, MplotValue val) =>
val5 -> val4 -> val3 -> val2 -> val1 -> val -> Matplotlib
contourRaw Integer
0 Integer
1 Integer
2 (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
xs) (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
ys) (t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
minimum2 t1 (t val)
zs)
  Matplotlib -> Matplotlib -> Matplotlib
% t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
forall val val val (t :: * -> *) (t :: * -> *) (t :: * -> *)
       (t1 :: * -> *) (t1 :: * -> *) (t1 :: * -> *).
(MplotValue val, MplotValue val, MplotValue val, Ord val, Ord val,
 Ord val, Ord (t val), Ord (t val), Ord (t val), Foldable t1,
 Foldable t, Foldable t1, Foldable t, Foldable t1, Foldable t) =>
t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
axis3DLabels t1 (t val)
xs t1 (t val)
ys t1 (t val)
zs

-- | Plot a 3D wireframe accessing the given elements of the data array
wireframe :: (MplotValue val2, MplotValue val1, MplotValue val) => val2 -> val1 -> val -> Matplotlib
wireframe :: val2 -> val1 -> val -> Matplotlib
wireframe val2
a val1
b val
c = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.plot_wireframe(np.array(data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), np.array(data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), np.array(data[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), rstride=1, cstride=1)"

-- | Plot a 3D surface accessing the given elements of the data array
surface :: (MplotValue val2, MplotValue val1, MplotValue val) => val2 -> val1 -> val -> Matplotlib
surface :: val2 -> val1 -> val -> Matplotlib
surface val2
a val1
b val
c = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.plot_surface(np.array(data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), np.array(data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), np.array(data[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]), rstride=1, cstride=1, cmap=cm.Blues, alpha=0.3)"

-- | Plot a contour 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
contourRaw :: val5 -> val4 -> val3 -> val2 -> val1 -> val -> Matplotlib
contourRaw val5
a val4
b val3
c val2
maxA val1
maxB val
minC =
  Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.contour(data[" Matplotlib -> val5 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val5
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val4 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val4
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val3 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val3
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], zdir='z', offset=" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
minC Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.contour(data[" Matplotlib -> val5 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val5
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val4 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val4
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val3 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val3
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], zdir='x', offset=-" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
maxA Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.contour(data[" Matplotlib -> val5 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val5
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val4 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val4
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], data[" Matplotlib -> val3 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val3
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], zdir='y', offset=" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
maxB Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
")"

-- | Draw a bag graph in a subplot
-- TODO Why do we need this?
subplotDataBar :: val -> val -> val -> [Option] -> Matplotlib
subplotDataBar val
a val
width val
offset [Option]
opts =
  Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.bar(np.arange(len(data[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]))+" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
offset Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
", data[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"], " Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
width Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> [Option] -> Matplotlib
@@ [Option]
opts

-- | The default bar with
barDefaultWidth :: a -> a
barDefaultWidth a
nr = a
1.0 a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
nr a -> a -> a
forall a. Num a => a -> a -> a
+ a
1)

-- | Create a set of labelled bars of a given height
subplotBarsLabelled :: [t a] -> val -> [[Option]] -> Matplotlib
subplotBarsLabelled [t a]
valuesList val
labels [[Option]]
optsList =
  [t a] -> [[Option]] -> Matplotlib
forall a. ToJSON a => [a] -> [[Option]] -> Matplotlib
subplotBars [t a]
valuesList [[Option]]
optsList
  Matplotlib -> Matplotlib -> Matplotlib
% Int -> Double -> Matplotlib
forall val1 val.
(MplotValue val1, MplotValue val) =>
val1 -> val -> Matplotlib
axisXTickSpacing (t a -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length (t a -> Int) -> t a -> Int
forall a b. (a -> b) -> a -> b
$ [t a] -> t a
forall a. [a] -> a
head ([t a] -> t a) -> [t a] -> t a
forall a b. (a -> b) -> a -> b
$ [t a]
valuesList) (Double
1.0 Double -> Double -> Double
forall a. Num a => a -> a -> a
- Int -> Double
forall a a. (Fractional a, Integral a) => a -> a
barDefaultWidth ([t a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [t a]
valuesList) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ Double
2.0)
  Matplotlib -> Matplotlib -> Matplotlib
% val -> Matplotlib
forall val. MplotValue val => val -> Matplotlib
axisXTickLabels val
labels

-- | Create a subplot and a set of labelled bars
-- TODO This is a mess..
subplotBars :: [a] -> [[Option]] -> Matplotlib
subplotBars [a]
valuesList [[Option]]
optsList =
  [a] -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData [a]
valuesList
  Matplotlib -> Matplotlib -> Matplotlib
% Integer -> Integer -> Integer -> Matplotlib
forall val val val.
(MplotValue val, MplotValue val, MplotValue val) =>
val -> val -> val -> Matplotlib
addSubplot Integer
1 Integer
1 Integer
1
  Matplotlib -> Matplotlib -> Matplotlib
% (let width :: Double
width = Int -> Double
forall a a. (Fractional a, Integral a) => a -> a
barDefaultWidth ([a] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [a]
valuesList) in
       (Matplotlib -> Matplotlib -> Matplotlib)
-> [Matplotlib] -> Matplotlib
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
foldl1 Matplotlib -> Matplotlib -> Matplotlib
(%) ((a -> [Option] -> Double -> Matplotlib)
-> [a] -> [[Option]] -> [Double] -> [Matplotlib]
forall a b c d. (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
zipWith3 (\a
_ [Option]
opts Double
i -> Double -> Double -> Double -> [Option] -> Matplotlib
forall val val val.
(MplotValue val, MplotValue val, MplotValue val) =>
val -> val -> val -> [Option] -> Matplotlib
subplotDataBar Double
i Double
width (Double
width Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
i) [Option]
opts) [a]
valuesList [[Option]]
optsList [Double
0..]))

-- | Update the data array to linearly interpolate between array entries
interpolate :: (MplotValue val, MplotValue val2, MplotValue val1) => val2 -> val1 -> val -> Matplotlib
interpolate :: val2 -> val1 -> val -> Matplotlib
interpolate val2
a val1
b val
n =
  (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"] = mlab.stineman_interp(np.linspace(data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"][0],data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"][-1]," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
n Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"),data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"],data[" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"],None)")
  Matplotlib -> Matplotlib -> Matplotlib
% (Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"] = np.linspace(data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"][0],data[" Matplotlib -> val2 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val2
a Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"][-1]," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
n Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")")

-- | Plot a KDE of the given functions with an optional start/end and a bandwidth h
densityBandwidth :: [Double] -> Double -> Maybe (Double, Double) -> Matplotlib
densityBandwidth :: [Double] -> Double -> Maybe (Double, Double) -> Matplotlib
densityBandwidth [Double]
l Double
h Maybe (Double, Double)
maybeStartEnd =
  (Double -> Double) -> Double -> Double -> Double -> Matplotlib
forall b.
ToJSON b =>
(Double -> b) -> Double -> Double -> Double -> Matplotlib
plotMapLinear Double -> Double
f (case Maybe (Double, Double)
maybeStartEnd of
                    Maybe (Double, Double)
Nothing -> [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
minimum [Double]
l
                    (Just (Double
start, Double
_)) -> Double
start)
                  (case Maybe (Double, Double)
maybeStartEnd of
                    Maybe (Double, Double)
Nothing -> [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Double]
l
                    (Just (Double
_, Double
end)) -> Double
end)
                   Double
100
  where f :: Double -> Double
f Double
x = [Double] -> Double
forall (t :: * -> *) a. (Foldable t, Num a) => t a -> a
sum ((Double -> Double) -> [Double] -> [Double]
forall a b. (a -> b) -> [a] -> [b]
map (\Double
xi -> Double -> Double -> Double -> Double
forall a. Floating a => a -> a -> a -> a
gaussianPdf Double
x Double
xi Double
h) [Double]
l) Double -> Double -> Double
forall a. Fractional a => a -> a -> a
/ ((Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Double) -> Int -> Double
forall a b. (a -> b) -> a -> b
$ [Double] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Double]
l) Double -> Double -> Double
forall a. Num a => a -> a -> a
* Double
h)
        gaussianPdf :: a -> a -> a -> a
gaussianPdf a
x a
mu a
sigma = a -> a
forall a. Floating a => a -> a
exp (- a -> a
forall a. Num a => a -> a
sqr (a
x a -> a -> a
forall a. Num a => a -> a -> a
- a
mu) a -> a -> a
forall a. Fractional a => a -> a -> a
/ (a
2 a -> a -> a
forall a. Num a => a -> a -> a
* a
sigma)) a -> a -> a
forall a. Fractional a => a -> a -> a
/ a -> a
forall a. Floating a => a -> a
sqrt (a
2 a -> a -> a
forall a. Num a => a -> a -> a
* a
forall a. Floating a => a
pi a -> a -> a
forall a. Num a => a -> a -> a
* a
sigma)
        sqr :: a -> a
sqr a
x = a
x a -> a -> a
forall a. Num a => a -> a -> a
* a
x

-- | Plot cross-correlation
xcorr :: a -> b -> Matplotlib
xcorr a
x b
y = (a, b) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData (a
x, b
y) Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.xcorr(data[0], data[1]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Plot auto-correlation
acorr :: a -> Matplotlib
acorr a
x = a -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData a
x Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.acorr(data" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | A quiver plot; color is optional and can be nothing
quiver :: a -> b -> c -> d -> Maybe e -> Matplotlib
quiver a
x b
y c
u d
v Maybe e
Nothing = (a, b, c, d) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData(a
x,b
y,c
u,d
v)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"q = ax.quiver(data[0], data[1], data[2], data[3]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"
quiver a
x b
y c
u d
v (Just e
c) = (a, b, c, d, e) -> Matplotlib
forall a. ToJSON a => a -> Matplotlib
readData(a
x,b
y,c
u,d
v,e
c)
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"q = ax.quiver(data[0], data[1], data[2], data[3], data[4]" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | A key of a given size with a label for a quiver plot
quiverKey :: val -> val -> val -> val -> Matplotlib
quiverKey val
x val
y val
u val
label = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.quiverkey(q, "Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#val
xMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
", "Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#val
yMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
", "Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#val
uMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
", "Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#val
labelMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
##String
")"

-- | Plot text at a specified location
text :: val -> val -> String -> Matplotlib
text val
x val
y String
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.text(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
x Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
y Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Add a text to a figure instead of a particular plot
figText :: val -> val -> String -> Matplotlib
figText val
x val
y String
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.figtext(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
x Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
y Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Add an annotation
annotate :: String -> Matplotlib
annotate String
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.annotate(" Matplotlib -> S -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> S
str String
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- * Layout, axes, and legends

-- | Square up the aspect ratio of a plot.
setAspect :: Matplotlib
setAspect :: Matplotlib
setAspect = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_aspect(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Square up the aspect ratio of a plot.
squareAxes :: Matplotlib
squareAxes :: Matplotlib
squareAxes = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_aspect('equal')"

-- | Set the rotation of the labels on the x axis to the given number of degrees
roateAxesLabels :: MplotValue val => val -> Matplotlib
roateAxesLabels :: val -> Matplotlib
roateAxesLabels val
degrees = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"labels = ax.get_xticklabels()"
   Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"for label in labels:"
   Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"    label.set_rotation("Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#val
degreesMatplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
#String
")"

-- | Set the x labels to be vertical
verticalAxes :: Matplotlib
verticalAxes :: Matplotlib
verticalAxes = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"labels = ax.get_xticklabels()"
   Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"for label in labels:"
   Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"    label.set_rotation('vertical')"

-- | Set the x scale to be logarithmic
logX :: Matplotlib
logX :: Matplotlib
logX = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xscale('log')"

-- | Set the y scale to be logarithmic
logY :: Matplotlib
logY :: Matplotlib
logY = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_yscale('log')"

-- | Set limits on the x axis
xlim :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
xlim :: val1 -> val -> Matplotlib
xlim val1
l val
u = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xlim(" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
u Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

-- | Set limits on the y axis
ylim :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
ylim :: val1 -> val -> Matplotlib
ylim val1
l val
u = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_ylim(" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
u Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

-- | Add a horizontal line across the axis
axhline :: val -> Matplotlib
axhline val
y = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.axhline(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
y Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Insert a legend
legend :: Matplotlib
legend = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.legend(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Insert a color bar
-- TODO This refers to the plot and not an axis. Might cause trouble with subplots
colorbar :: Matplotlib
colorbar = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.colorbar(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Add a title
title :: String -> Matplotlib
title :: String -> Matplotlib
title String
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_title(" Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Show/hide grid lines
grid :: Bool -> Matplotlib
grid :: Bool -> Matplotlib
grid Bool
t = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.grid(" Matplotlib -> Bool -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# Bool
t Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

-- | Enable 3D projection
axis3DProjection :: Matplotlib
axis3DProjection :: Matplotlib
axis3DProjection = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = plot.gca() if plot.gca().name == '3d' else plot.subplot(projection='3d')"

-- | Label and set limits of a set of 3D axis
-- TODO This is a mess, does both more and less than it claims.
axis3DLabels :: t1 (t val) -> t1 (t val) -> t1 (t val) -> Matplotlib
axis3DLabels t1 (t val)
xs t1 (t val)
ys t1 (t val)
zs =
  Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xlabel('X')"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xlim3d(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
minimum2 t1 (t val)
xs Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
", " Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
xs Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_ylabel('Y')"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_ylim3d(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
minimum2 t1 (t val)
ys Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
", " Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
ys Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_zlabel('Z')"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_zlim3d(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
minimum2 t1 (t val)
zs Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
", " Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# t1 (t val) -> val
forall (t :: * -> *) a (t1 :: * -> *).
(Ord (t a), Ord a, Foldable t1, Foldable t) =>
t1 (t a) -> a
maximum2 t1 (t val)
zs Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

-- | Add a label to the x axis
xlabel :: String -> Matplotlib
xlabel :: String -> Matplotlib
xlabel String
label = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xlabel(" Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
label Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Add a label to the y axis
ylabel :: String -> Matplotlib
ylabel :: String -> Matplotlib
ylabel String
label = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_ylabel(" Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
label Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Add a label to the z axis
zlabel :: String -> Matplotlib
zlabel :: String -> Matplotlib
zlabel String
label = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_zlabel(" Matplotlib -> R -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String -> R
raw String
label Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

setSizeInches :: val -> val -> Matplotlib
setSizeInches val
w val
h = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"fig.set_size_inches(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
w Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
h Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
", forward=True)"

tightLayout :: Matplotlib
tightLayout = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"fig.tight_layout(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

xkcd :: Matplotlib
xkcd = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.xkcd()"

-- * Ticks

xticks :: val -> Matplotlib
xticks val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xticks(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
yticks :: val -> Matplotlib
yticks val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_yticks(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
zticks :: val -> Matplotlib
zticks val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_zticks(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

xtickLabels :: val -> Matplotlib
xtickLabels val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xticklabels(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
ytickLabels :: val -> Matplotlib
ytickLabels val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_yticklabels(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"
ztickLabels :: val -> Matplotlib
ztickLabels val
l = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_zticklabels(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

-- | Set the spacing of ticks on the x axis
axisXTickSpacing :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
axisXTickSpacing :: val1 -> val -> Matplotlib
axisXTickSpacing val1
nr val
width = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xticks(np.arange(" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
nr Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")+" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
width Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Set the labels on the x axis
axisXTickLabels :: MplotValue val => val -> Matplotlib
axisXTickLabels :: val -> Matplotlib
axisXTickLabels val
labels = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_xticklabels( (" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
labels Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
") " Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
" )"

-- | Set the spacing of ticks on the y axis
axisYTickSpacing :: (MplotValue val1, MplotValue val) => val1 -> val -> Matplotlib
axisYTickSpacing :: val1 -> val -> Matplotlib
axisYTickSpacing val1
nr val
width = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_yticks(np.arange(" Matplotlib -> val1 -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val1
nr Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")+" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
width Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"

-- | Set the labels on the y axis
axisYTickLabels :: MplotValue val => val -> Matplotlib
axisYTickLabels :: val -> Matplotlib
axisYTickLabels val
labels = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.set_yticklabels( (" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
labels Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
") " Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
" )"

axisXTicksPosition :: val -> Matplotlib
axisXTicksPosition val
p = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.xaxis.set_ticks_position('" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
p Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"')"
axisYTicksPosition :: val -> Matplotlib
axisYTicksPosition val
p = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax.yaxis.set_ticks_position('" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
p Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"')"

-- * Spines

spine :: val -> Matplotlib
spine val
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"spine = ax.spines['" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"']"

spineSetBounds :: val -> val -> Matplotlib
spineSetBounds val
l val
h = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"spine.set_bounds(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
l Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
h Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

spineSetVisible :: val -> Matplotlib
spineSetVisible val
b = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"spine.set_visible(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
b Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
")"

spineSetPosition :: val -> val -> Matplotlib
spineSetPosition val
s val
n = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"spine.set_position((" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
n Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"))"

-- * Subplots

setAx :: Matplotlib
setAx = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.sca(ax) "

-- | Create a subplot with the coordinates (r,c,f)
addSubplot :: val -> val -> val -> Matplotlib
addSubplot val
r val
c val
f = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = plot.gcf().add_subplot(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
r Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
c Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
f Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateAxes Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Access a subplot with the coordinates (r,c,f)
getSubplot :: val -> val -> val -> Matplotlib
getSubplot val
r val
c val
f = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = plot.subplot(" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
r Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
c Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"," Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
f Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateAxes Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Creates subplots and stores them in an internal variable
subplots :: Matplotlib
subplots = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"fig, axes = plot.subplots(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"axes = np.asarray(axes)"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"axes = axes.flatten()"
  Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateAxes Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Access a subplot
setSubplot :: val -> Matplotlib
setSubplot val
s = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = axes[" Matplotlib -> val -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# val
s Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"]" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Add axes to a plot
axes :: Matplotlib
axes = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = plot.axes(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateAxes Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Add axes to a figure
addAxes :: Matplotlib
addAxes = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"ax = fig.add_axes(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateAxes Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
setAx

-- | Creates a new figure with the given id. If the Id is already in use it
-- switches to that figure.
figure :: Matplotlib
figure = Matplotlib
mp Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
# String
"plot.figure(" Matplotlib -> String -> Matplotlib
forall val. MplotValue val => Matplotlib -> val -> Matplotlib
## String
")" Matplotlib -> Matplotlib -> Matplotlib
% Matplotlib
updateFigure