gnuplot-0.3.3: 2D and 3D plots using gnuplotSource codeContentsIndex
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
data Attribute
= Custom String [String]
| EPS FilePath
| PNG FilePath
| Terminal T
| Grid (Maybe [String])
| Key (Maybe [String])
| Border (Maybe [String])
| XTicks (Maybe [String])
| YTicks (Maybe [String])
| Size Size
| Aspect Aspect
| BoxAspect Aspect
| LineStyle Int [LineAttr]
| Title String
| XLabel String
| YLabel String
| XRange (Double, Double)
| YRange (Double, Double)
| ZRange (Double, Double)
| Palette [(Double, (Double, Double, Double))]
| ColorBox (Maybe [String])
| XTime
| XFormat String
data Size
= Scale Double
| SepScale Double Double
data Aspect
= Ratio Double
| NoRatio
data LineAttr
= LineType Int
| LineWidth Double
| PointType Int
| PointSize Double
| LineTitle String
data LineSpec
= DefaultStyle Int
| CustomStyle [LineAttr]
data PlotType
= Lines
| Points
| LinesPoints
| Impulses
| Dots
| Steps
| FSteps
| HiSteps
| ErrorBars
| XErrorBars
| YErrorBars
| XYErrorBars
| ErrorLines
| XErrorLines
| YErrorLines
| XYErrorLines
| Boxes
| FilledCurves
| BoxErrorBars
| BoxXYErrorBars
| FinanceBars
| CandleSticks
| Vectors
| PM3d
data PlotStyle = PlotStyle {
plotType :: PlotType
lineSpec :: LineSpec
}
linearScale :: Fractional a => Integer -> (a, a) -> [a]
defaultStyle :: PlotStyle
terminal :: C term => term -> Attribute
plotList :: Show a => [Attribute] -> [a] -> IO ()
plotListStyle :: Show a => [Attribute] -> PlotStyle -> [a] -> IO ()
plotLists :: Show a => [Attribute] -> [[a]] -> IO ()
plotListsStyle :: Show a => [Attribute] -> [(PlotStyle, [a])] -> IO ()
plotFunc :: Show a => [Attribute] -> [a] -> (a -> a) -> IO ()
plotFuncs :: Show a => [Attribute] -> [a] -> [a -> a] -> IO ()
plotPath :: Show a => [Attribute] -> [(a, a)] -> IO ()
plotPaths :: Show a => [Attribute] -> [[(a, a)]] -> IO ()
plotPathStyle :: Show a => [Attribute] -> PlotStyle -> [(a, a)] -> IO ()
plotPathsStyle :: Show a => [Attribute] -> [(PlotStyle, [(a, a)])] -> IO ()
plotParamFunc :: Show a => [Attribute] -> [a] -> (a -> (a, a)) -> IO ()
plotParamFuncs :: Show a => [Attribute] -> [a] -> [a -> (a, a)] -> IO ()
plotDots :: Show a => [Attribute] -> [(a, a)] -> IO ()
data Plot3dType
= Surface
| ColorMap
data CornersToColor
= Mean
| GeometricMean
| Median
| Corner1
| Corner2
| Corner3
| Corner4
data Attribute3d
= Plot3dType Plot3dType
| CornersToColor CornersToColor
plotMesh3d :: (Show a, Show b, Show c) => [Attribute] -> [Attribute3d] -> [[(a, b, c)]] -> IO ()
plotFunc3d :: (Show a, Show b, Show c) => [Attribute] -> [Attribute3d] -> [b] -> [c] -> (b -> c -> a) -> IO ()
epspdfPlot :: FilePath -> ([Attribute] -> IO ()) -> IO ()
inclPlot :: FilePath -> ([Attribute] -> IO ()) -> IO String
Documentation
data Attribute Source
Constructors
Custom String [String]anything that is allowed after gnuplot's set command
EPS FilePath
PNG FilePath
Terminal Tyou cannot use this, call terminal instead
Grid (Maybe [String])
Key (Maybe [String])
Border (Maybe [String])
XTicks (Maybe [String])
YTicks (Maybe [String])
Size Size
Aspect Aspect
BoxAspect Aspect
LineStyle Int [LineAttr]
Title String
XLabel String
YLabel String
XRange (Double, Double)
YRange (Double, Double)
ZRange (Double, Double)
Palette [(Double, (Double, Double, Double))]
ColorBox (Maybe [String])
XTime
XFormat String
data Size Source
Constructors
Scale Double
SepScale Double Double
data Aspect Source
Constructors
Ratio Double
NoRatio
data LineAttr Source
Constructors
LineType Int
LineWidth Double
PointType Int
PointSize Double
LineTitle String
data LineSpec Source
Constructors
DefaultStyle Int
CustomStyle [LineAttr]
data PlotType Source
Constructors
Lines
Points
LinesPoints
Impulses
Dots
Steps
FSteps
HiSteps
ErrorBars
XErrorBars
YErrorBars
XYErrorBars
ErrorLines
XErrorLines
YErrorLines
XYErrorLines
Boxes
FilledCurves
BoxErrorBars
BoxXYErrorBars
FinanceBars
CandleSticks
Vectors
PM3d
data PlotStyle Source
Constructors
PlotStyle
plotType :: PlotType
lineSpec :: LineSpec
linearScale :: Fractional a => Integer -> (a, a) -> [a]Source
defaultStyle :: PlotStyleSource
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))
plotListStyle :: Show a => [Attribute] -> PlotStyle -> [a] -> IO ()Source
plotLists :: Show a => [Attribute] -> [[a]] -> IO ()Source
plotListsStyle :: Show a => [Attribute] -> [(PlotStyle, [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
data CornersToColor Source
Constructors
Mean
GeometricMean
Median
Corner1
Corner2
Corner3
Corner4
data Attribute3d Source
Constructors
Plot3dType Plot3dType
CornersToColor CornersToColor
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
:: 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
:: 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.

Produced by Haddock version 2.4.2