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

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.

Synopsis

Documentation

data Aspect Source

Constructors

Ratio Double 
NoRatio 

data PlotStyle Source

Constructors

PlotStyle 

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

terminal :: C term => term -> AttributeSource

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

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

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)))

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.