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.
- 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
- data Aspect
- data LineAttr
- 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 {}
- 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
- data CornersToColor
- data Attribute3d
- 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
Constructors
Custom String [String] | anything that is allowed after gnuplot's |
EPS FilePath | |
PNG FilePath | |
Terminal T | you cannot use this, call |
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 |
Constructors
DefaultStyle Int | |
CustomStyle [LineAttr] |
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))
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]
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))]
data Plot3dType Source
data CornersToColor Source
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)))
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.
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.