gnuplot-0.1: 2D and 3D plots using GNUPlot

Graphics.GNUPlot.Simple

Contents

Synopsis

User front-end

data Aspect Source

Constructors

Ratio Double 
NoRatio 

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

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

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

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

plotFunc :: Show a => [Attribute] -> [a] -> (a -> a) -> IO ()Source

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

plotFuncs :: Show a => [Attribute] -> [a] -> [a -> a] -> IO ()Source

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

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

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

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

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

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

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

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

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

data Plot3dType Source

Constructors

Surface 
ColorMap 

plotMesh3d :: (Show a, Show b, Show c) => [Attribute] -> [Attribute3d] -> [[(a, b, c)]] -> 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))))

plotFunc3d :: (Show a, Show b, Show c) => [Attribute] -> [Attribute3d] -> [b] -> [c] -> (b -> c -> a) -> IO ()Source

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

For inclusion of GNUPlot graphics in LaTeX documents using lhs2TeX

epspdfPlotSource

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.

inclPlotSource

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.

Internal functions

showTriplet :: (Show a, Show b, Show c) => (a, b, c) -> StringSource

storeData :: Show a => FilePath -> PlotStyle -> [(a, a)] -> IO StringSource

Writes point data to a file and returns a string containing GNUPlot.plot parameters to invoke the file.

plot2dGen :: Show a => [Attribute] -> PlotStyle -> [(a, a)] -> IO ()Source

plot2dMultiGen :: Show a => [Attribute] -> [(PlotStyle, [(a, a)])] -> IO ()Source

startGNUPlotSource

Arguments

:: String

The program that shall pipe into GNUPlot

-> String

Options for GNUPlot

-> IO ExitCode