gnuplot-0.5.6.1: 2D and 3D plots using gnuplot

Safe HaskellSafe
LanguageHaskell98

Graphics.Gnuplot.Simple

Description

This is a simple monolithic interface to gnuplot that can be used as is in GHCi or Hugs. We do not plan to support every feature of gnuplot here, instead we provide an advanced modularized interface in Graphics.Gnuplot.Advanced.

Here is a pretty simple example:

Graphics.Gnuplot.Simple> plotFunc [] (linearScale 1000 (-10,10::Double)) sin

This was formerly part of the htam package.

Synopsis

Documentation

data Aspect Source #

Constructors

Ratio Double 
NoRatio 

data LineAttr Source #

Be careful with LineTitle which can only be used as part of gnuplot's plot command but not as part of set. That is,

plotList [LineStyle 0 [LineTitle "foobar"]] [0,5..100::Double]

will leave you with an invalid gnuplot script, whereas

plotListStyle [] (defaultStyle {lineSpec = CustomStyle [LineTitle "foobar"]}) [0,5..100::Double]

does what you want.

The Int types would be better enumerations but their interpretations depend on the gnuplot output type. :-(

data PlotStyle Source #

Constructors

PlotStyle 

linearScale :: Fractional a => Integer -> (a, a) -> [a] Source #

terminal :: C term => term -> Attribute Source #

plotList :: C a => [Attribute] -> [a] -> IO () Source #

plotList [] (take 30 (let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) in fibs))

plotListStyle :: C a => [Attribute] -> PlotStyle -> [a] -> IO () Source #

plotListStyle [] (defaultStyle{plotType = CandleSticks}) (Plot2D.functionToGraph (linearScale 32 (0,2*pi::Double)) (\t -> (-sin t, -2*sin t, 2*sin t, sin t)))

plotLists :: C a => [Attribute] -> [[a]] -> IO () Source #

plotListsStyle :: C a => [Attribute] -> [(PlotStyle, [a])] -> IO () Source #

plotFunc :: (C a, C a) => [Attribute] -> [a] -> (a -> a) -> IO () Source #

plotFunc [] (linearScale 1000 (-10,10)) sin

plotFuncs :: (C a, C a) => [Attribute] -> [a] -> [a -> a] -> IO () Source #

plotFuncs [] (linearScale 1000 (-10,10)) [sin, cos]

plotPath :: C a => [Attribute] -> [(a, a)] -> IO () Source #

plotPaths :: C a => [Attribute] -> [[(a, a)]] -> IO () Source #

plotPathStyle :: C a => [Attribute] -> PlotStyle -> [(a, a)] -> IO () Source #

plotPathsStyle :: C a => [Attribute] -> [(PlotStyle, [(a, a)])] -> IO () Source #

plotParamFunc :: (C a, C a) => [Attribute] -> [a] -> (a -> (a, a)) -> IO () Source #

plotParamFunc [] (linearScale 1000 (0,2*pi)) (\t -> (sin (2*t), cos t))

plotParamFuncs :: (C a, C a) => [Attribute] -> [a] -> [a -> (a, a)] -> IO () Source #

plotParamFuncs [] (linearScale 1000 (0,2*pi)) [\t -> (sin (2*t), cos t), \t -> (cos t, sin (2*t))]

plotDots :: (C a, C a) => [Attribute] -> [(a, a)] -> IO () Source #

data Plot3dType Source #

Constructors

Surface 
ColorMap 

plotMesh3d :: (C x, C y, C z, C x, C y, C z) => [Attribute] -> [Attribute3d] -> [[(x, y, z)]] -> IO () Source #

let xs = [-2,-1.8..2::Double] in plotMesh3d [] [] (do x <- xs; return (do y <- xs; return (x,y,cos(x*x+y*y))))
let phis = linearScale 30 (-pi, pi :: Double) in plotMesh3d [] [] (do phi <- phis; return (do psi <- phis; let r = 5 + sin psi in return (r * cos phi, r * sin phi, cos psi)))

plotFunc3d :: (C x, C y, C z, C x, C y, C z) => [Attribute] -> [Attribute3d] -> [x] -> [y] -> (x -> y -> z) -> IO () Source #

let xs = [-2,-1.8..2::Double] in plotFunc3d [] [] xs xs (\x y -> exp(-(x*x+y*y)))

epspdfPlot Source #

Arguments

:: FilePath 
-> ([Attribute] -> IO ())

Drawing function that expects some gnuplot attributes.

-> IO () 

Redirects the output of a plotting function to an EPS file and additionally converts it to PDF.

inclPlot Source #

Arguments

:: FilePath 
-> ([Attribute] -> IO ())

Drawing function that expects some gnuplot attributes.

-> IO String 

Creates an EPS and a PDF graphics and returns a string that can be inserted into a LaTeX document to include this graphic.

Different from GHCi, Hugs doesn't output a return value from an IO monad. So you must wrap it with a putStr. Nevertheless this implementation which returns the LaTeX command as string is the most flexible one.