-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | 2D and 3D plots using gnuplot -- -- This is a wrapper to gnuplot which lets you create 2D and 3D plots. -- -- Start a simple session with cabal repl. If not already -- loaded, call :module Graphics.Gnuplot.Simple in order to load -- Graphics.Gnuplot.Simple which is ready for use in GHCi. It does -- not address all fancy gnuplot features in order to stay simple. For -- more sophisticated plots, especially batch generated graphics, I -- recommend Graphics.Gnuplot.Advanced. This module contains also -- an overview of the hierarchy of objects. -- -- Examples for using this interface can be found in the Demo -- module. In order to compile this and install an example data file, use -- the Cabal flag buildExamples: -- --
--   $ cabal install -fbuildExamples gnuplot
--   
-- -- With the Cabal flags executePipe and executeShell you can switch to -- more convenient but probably less portable ways of feeding gnuplot -- with a script. -- -- Alternative packages: plot, HPlot, Chart, -- textPlot, easyplot @package gnuplot @version 0.5.7 module Graphics.Gnuplot.File data T Cons :: FilePath -> String -> T [name] :: T -> FilePath [content] :: T -> String write :: T -> IO () instance GHC.Classes.Eq Graphics.Gnuplot.File.T instance GHC.Show.Show Graphics.Gnuplot.File.T instance Graphics.Gnuplot.Private.File.C Graphics.Gnuplot.File.T -- | This class gives a uniform interface to plotting Plot, -- Frame and MultiPlot. module Graphics.Gnuplot.Display class C gfx module Graphics.Gnuplot.Frame.Option -- | Every option represents an internal state in gnuplot. It is altered -- with gnuplot's set command. The first field in T is the name of -- the option and the name of the according internal state in gnuplot. -- -- Sometimes the addressed state is not explicitly mentioned but is -- expressed by the syntax of the values. E.g. you can write set grid -- xtics and set grid noxtics, but both commands refer to -- the same internal boolean variable, that we like to call -- xtics. It is important that the gnuplot Haskell bindings know -- that these two set commands refer to the same gnuplot state, since we -- want to simulate a stateless functional interface in front of a -- stateful imperative one. -- -- In case of a such a hidden state, we manage an identifier in the -- second field of T. It is mainly used for distinguishing -- different hidden states, that are accessed by the same set -- variable. This second field may not contain valid gnuplot identifiers, -- however you might use the field for formatting boolean options using -- addBool. data T -- | Constructs a generic option from Strings for the first and second -- field of T. -- -- This is very flexible, but not very safe. Use it only as fall-back, if -- there is no specific setter function in -- Graphics.Gnuplot.Frame.OptionSet. custom :: String -> String -> T title :: T grid :: String -> T size :: String -> T key :: String -> T border :: String -> T pm3d :: String -> T view :: T xRange :: String -> T yRange :: String -> T zRange :: String -> T xLabel :: String -> T yLabel :: String -> T zLabel :: String -> T xTicks :: String -> T yTicks :: String -> T zTicks :: String -> T xLogScale :: T yLogScale :: T zLogScale :: T xData :: T yData :: T zData :: T xFormat :: T yFormat :: T zFormat :: T timeFmt :: T module Graphics.Gnuplot.Terminal class C terminal module Graphics.Gnuplot.Terminal.Default data T cons :: T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.Default.T module Graphics.Gnuplot.Time -- | Use it this way: -- --
--   import Data.Time
--   import Graphics.Gnuplot.Simple
--   
--   main =
--      plotPath [XTime, XFormat "%m-%d"] $ prepXTime $
--         (UTCTime (fromGregorian 2008 01 01)     0, 1.0) :
--         (UTCTime (fromGregorian 2008 01 05) 43200, 5.0) :
--         (UTCTime (fromGregorian 2008 01 15)     0, 2.5) :
--         []
--   
prepXTime :: (FormatTime a, Read b) => [(a, b)] -> [(b, b)] module Graphics.Gnuplot.Terminal.X11 data T cons :: T title :: String -> T -> T noTitle :: T -> T persist :: T -> T noPersist :: T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.X11.T -- | Terminal using wxwidgets. Derived from X11. module Graphics.Gnuplot.Terminal.WXT data T cons :: T title :: String -> T -> T noTitle :: T -> T persist :: T -> T noPersist :: T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.WXT.T -- | Terminal using QT. Derived from wxt. module Graphics.Gnuplot.Terminal.QT data T cons :: T title :: String -> T -> T noTitle :: T -> T persist :: T -> T noPersist :: T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.QT.T module Graphics.Gnuplot.Plot -- | Plots can be assembled using mappend or mconcat or -- several functions from Data.Foldable. data T graph module Graphics.Gnuplot.Graph class C graph module Graphics.Gnuplot.Frame.OptionSet.Style fillSolid :: C graph => T graph -> T graph fillBorder :: C graph => Bool -> T graph -> T graph fillBorderLineType :: C graph => Int -> T graph -> T graph -- | Modularized interface to gnuplot that allows complex graphics and fine -- control of their components. It is designed for non-interactive use, -- e.g. scripts for plotting statistics. -- -- The hierarchy of objects is as follows: -- -- -- -- Although the Haskell wrapper shall save you from the burden of -- learning gnuplot script syntax, it happens frequently that people ask, -- how to express a certain gnuplot script using this package. Thus let's -- annotate the gnuplot script generated by Demo.multiplot in -- order to show, what belongs to where: -- --
--   # the terminal selection is part of the 'plot' command of this module
--   set terminal x11
--   # multiplot initialization belongs to MultiPlot - of course
--   set multiplot layout 3, 5
--   # hiding the names of the temporary files is a FrameOption
--   unset key
--   set xrange [-1.0:1.0]
--   # this plot contains only one graph,
--   # but several graphs could be given separated by commas
--   plot "curve0.csv" using 1:2 with lines
--   plot "curve1.csv" using 1:2 with lines
--   plot "curve2.csv" using 1:2 with lines
--   plot "curve3.csv" using 1:2 with lines
--   plot "curve4.csv" using 1:2 with lines
--   plot "curve5.csv" using 1:2 with lines
--   plot "curve6.csv" using 1:2 with lines
--   set xrange [-2.5:2.5]
--   set yrange [-2.5:2.5]
--   # this is a plot build from a Graph3D
--   splot "curve7.csv" using 1:2:3 with pm3d
--   set xrange [-1.0:1.0]
--   set yrange [*:*]
--   plot "curve8.csv" using 1:2 with lines
--   plot "curve9.csv" using 1:2 with lines
--   plot "curve10.csv" using 1:2 with lines
--   plot "curve11.csv" using 1:2 with lines
--   plot "curve12.csv" using 1:2 with lines
--   plot "curve13.csv" using 1:2 with lines
--   plot "curve14.csv" using 1:2 with lines
--   unset multiplot
--   
module Graphics.Gnuplot.Advanced -- | The plot function returns ExitCode, which is nice for -- programming but ugly for interactive GHCi sessions. For interactive -- sessions, better use Graphics.Gnuplot.Simple. gfx must -- be one of the types Plot, Frame, MultiPlot. -- -- This function runs gnuplot asynchronously for interactive terminals -- (X11, WX) and synchronously for file terminals (PostScript, PNG, -- etc.). This emulates the behaviour of gnuplot --persist. -- However, when running asynchronous we cannot obtain a real -- ExitCode. Thus, in this case we will always return -- ExitSuccess. plot :: (C terminal, C gfx) => terminal -> gfx -> IO ExitCode -- | Plot using the default gnuplot terminal. plotDefault :: C gfx => gfx -> IO ExitCode plotSync :: (C terminal, C gfx) => terminal -> gfx -> IO ExitCode plotAsync :: (C terminal, C gfx) => terminal -> gfx -> IO ThreadId -- | Return the gnuplot script and the curve files corresponding to your -- plot data. The first parameter is the directory where the curve files -- are located. This directory is baked into the gnuplot script and the -- paths of the curve files. -- -- Don't make any assumptions about the structure of the files. Feeding -- the files to gnuplot, archiving them or study them are the intended -- uses of them. fileContents :: (C terminal, C gfx) => FilePath -> terminal -> gfx -> (String, [T]) module Graphics.Gnuplot.Terminal.SVG data T cons :: FilePath -> T -- | Setting the encoding to anything different from locale makes -- only sense if you write your gnuplot files manually using this -- encoding. encoding :: T -> T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.SVG.T module Graphics.Gnuplot.Terminal.PostScript data T cons :: FilePath -> T -- | Setting the encoding to anything different from locale makes -- only sense if you write your gnuplot files manually using this -- encoding. encoding :: T -> T -> T landscape :: T -> T portrait :: T -> T eps :: T -> T color :: T -> T monochrome :: T -> T font :: String -> Int -> T -> T -- | Embed a font file in the generated PostScript output. Each call adds a -- new font file, there is no way to remove it again. embedFont :: FilePath -> T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.PostScript.T module Graphics.Gnuplot.Terminal.PNG data T cons :: FilePath -> T -- | Setting the encoding to anything different from locale makes -- only sense if you write your gnuplot files manually using this -- encoding. encoding :: T -> T -> T transparent :: T -> T noTransparent :: T -> T interlace :: T -> T noInterlace :: T -> T trueColor :: T -> T noTrueColor :: T -> T fontTiny :: T -> T fontSmall :: T -> T fontMedium :: T -> T fontLarge :: T -> T fontGiant :: T -> T instance Graphics.Gnuplot.Private.Terminal.C Graphics.Gnuplot.Terminal.PNG.T -- | Support for special characters -- -- Gnuplot has no universal Unicode escaping mechanism, you can only work -- with encodings. However, not all terminals support all encodings, not -- all terminals even support utf-8. Some terminals seem to support only -- one encoding. E.g. WX seems to support only UTF-8, X11 seems to -- support only Latin-1. Postscript, SVG, PNG seem to support both UTF-8 -- and Latin-1. -- -- The gnuplot Haskell bindings always write using the -- system-wide default encoding. Thus it is better not to set an encoding -- other than locale explicitly. However, if you write the files -- yourself in a certain encoding you should use the encoding -- option of the according terminal. module Graphics.Gnuplot.Encoding data T locale :: T deflt :: T iso_8859_1 :: T iso_8859_15 :: T iso_8859_2 :: T iso_8859_9 :: T koi8r :: T koi8u :: T cp437 :: T cp850 :: T cp852 :: T cp950 :: T cp1250 :: T cp1251 :: T cp1254 :: T sjis :: T utf8 :: T module Graphics.Gnuplot.LineSpecification data T deflt :: T lineStyle :: Int -> T -> T lineType :: Int -> T -> T lineWidth :: Double -> T -> T lineColor :: T -> T -> T pointType :: Int -> T -> T pointSize :: Double -> T -> T title :: String -> T -> T module Graphics.Gnuplot.ColorSpecification data T -- | Color components for Red, Green, Blue, must be in the range -- [0,1]. rgb :: Double -> Double -> Double -> T rgb8 :: Word8 -> Word8 -> Word8 -> T -- | Specify a color by name. You are responsible for choosing an existing -- name in gnuplot. If your color is available as Haskell variable in -- this module, then prefer this one. name :: String -> T paletteFrac :: Double -> T white :: T black :: T gray0 :: T grey0 :: T gray10 :: T grey10 :: T gray20 :: T grey20 :: T gray30 :: T grey30 :: T gray40 :: T grey40 :: T gray50 :: T grey50 :: T gray60 :: T grey60 :: T gray70 :: T grey70 :: T gray80 :: T grey80 :: T gray90 :: T grey90 :: T gray100 :: T grey100 :: T gray :: T grey :: T lightGray :: T lightGrey :: T darkGray :: T darkGrey :: T red :: T lightRed :: T darkRed :: T yellow :: T lightYellow :: T darkYellow :: T green :: T lightGreen :: T darkGreen :: T springGreen :: T forestGreen :: T seaGreen :: T blue :: T lightBlue :: T darkBlue :: T midnightBlue :: T navy :: T mediumBlue :: T royalblue :: T skyblue :: T cyan :: T lightCyan :: T darkCyan :: T magenta :: T lightMagenta :: T darkMagenta :: T turquoise :: T lightTurquoise :: T darkTurquoise :: T pink :: T lightPink :: T darkPink :: T coral :: T lightCoral :: T orangeRed :: T salmon :: T lightSalmon :: T darkSalmon :: T aquamarine :: T khaki :: T darkKhaki :: T goldenrod :: T lightGoldenrod :: T darkGoldenrod :: T gold :: T beige :: T brown :: T orange :: T darkOrange :: T violet :: T darkViolet :: T plum :: T purple :: T module Graphics.Gnuplot.MultiPlot data T data Part partFromFrame :: C graph => T graph -> Part partFromPlot :: C graph => T graph -> Part simpleFromFrameArray :: (C graph, Ix i, Ix j) => Array (i, j) (T graph) -> T simpleFromPartArray :: (Ix i, Ix j) => Array (i, j) Part -> T title :: String -> T -> T instance Graphics.Gnuplot.Private.Display.C Graphics.Gnuplot.MultiPlot.T -- | Provide a class that restricts the range of Haskell types to the ones -- that gnuplot can process. module Graphics.Gnuplot.Value.Atom data OptionSet a OptionSet :: [String] -> [String] -> [(T, [String])] -> OptionSet a [optData] :: OptionSet a -> [String] [optFormat] :: OptionSet a -> [String] [optOthers] :: OptionSet a -> [(T, [String])] class C a options :: C a => OptionSet a instance Graphics.Gnuplot.Value.Atom.C GHC.Types.Float instance Graphics.Gnuplot.Value.Atom.C GHC.Types.Double instance Graphics.Gnuplot.Value.Atom.C GHC.Types.Int instance Graphics.Gnuplot.Value.Atom.C GHC.Integer.Type.Integer instance GHC.Real.Integral a => Graphics.Gnuplot.Value.Atom.C (GHC.Real.Ratio a) instance Graphics.Gnuplot.Value.Atom.C GHC.Int.Int8 instance Graphics.Gnuplot.Value.Atom.C GHC.Int.Int16 instance Graphics.Gnuplot.Value.Atom.C GHC.Int.Int32 instance Graphics.Gnuplot.Value.Atom.C GHC.Int.Int64 instance Graphics.Gnuplot.Value.Atom.C GHC.Word.Word8 instance Graphics.Gnuplot.Value.Atom.C GHC.Word.Word16 instance Graphics.Gnuplot.Value.Atom.C GHC.Word.Word32 instance Graphics.Gnuplot.Value.Atom.C GHC.Word.Word64 instance Graphics.Gnuplot.Value.Atom.C Data.Time.Calendar.Days.Day instance Graphics.Gnuplot.Value.Atom.C Data.Time.Clock.Internal.UTCTime.UTCTime -- | We provide a way to specify a set of columns that matches the tuple -- structure of a certain graph type. module Graphics.Gnuplot.Value.ColumnSet newtype T a Cons :: [Int] -> T a atom :: C a => Int -> T a pair :: T a -> T b -> T (a, b) triple :: T a -> T b -> T c -> T (a, b, c) quadruple :: T a -> T b -> T c -> T d -> T (a, b, c, d) -- | Provide a class that renders multiple Haskell values in a text form -- that is accessible by gnuplot. -- -- Maybe we add a method for the binary interface to gnuplot later. module Graphics.Gnuplot.Value.Tuple class C a -- | For values that are also in Atom class, text must generate a -- singleton list. text :: C a => a -> [ShowS] -- | It must hold ColumnCount (length (text x)) == columnCount. columnCount :: C a => ColumnCount a -- | Count numbers of gnuplot data columns for the respective type. -- -- Somehow a writer monad with respect to Sum monoid without material -- monadic result. -- -- Cf. ColumnSet module. newtype ColumnCount a ColumnCount :: Int -> ColumnCount a newtype Label Label :: String -> Label instance GHC.Show.Show (Graphics.Gnuplot.Value.Tuple.ColumnCount a) instance GHC.Classes.Ord (Graphics.Gnuplot.Value.Tuple.ColumnCount a) instance GHC.Classes.Eq (Graphics.Gnuplot.Value.Tuple.ColumnCount a) instance Graphics.Gnuplot.Value.Tuple.C Graphics.Gnuplot.Value.Tuple.Label instance Graphics.Gnuplot.Value.Tuple.C GHC.Types.Float instance Graphics.Gnuplot.Value.Tuple.C GHC.Types.Double instance Graphics.Gnuplot.Value.Tuple.C GHC.Types.Int instance Graphics.Gnuplot.Value.Tuple.C GHC.Integer.Type.Integer instance GHC.Real.Integral a => Graphics.Gnuplot.Value.Tuple.C (GHC.Real.Ratio a) instance Graphics.Gnuplot.Value.Tuple.C GHC.Int.Int8 instance Graphics.Gnuplot.Value.Tuple.C GHC.Int.Int16 instance Graphics.Gnuplot.Value.Tuple.C GHC.Int.Int32 instance Graphics.Gnuplot.Value.Tuple.C GHC.Int.Int64 instance Graphics.Gnuplot.Value.Tuple.C GHC.Word.Word8 instance Graphics.Gnuplot.Value.Tuple.C GHC.Word.Word16 instance Graphics.Gnuplot.Value.Tuple.C GHC.Word.Word32 instance Graphics.Gnuplot.Value.Tuple.C GHC.Word.Word64 instance Graphics.Gnuplot.Value.Tuple.C Data.Time.Calendar.Days.Day instance Graphics.Gnuplot.Value.Tuple.C Data.Time.Clock.Internal.UTCTime.UTCTime instance (Graphics.Gnuplot.Value.Tuple.C a, Graphics.Gnuplot.Value.Tuple.C b) => Graphics.Gnuplot.Value.Tuple.C (a, b) instance (Graphics.Gnuplot.Value.Tuple.C a, Graphics.Gnuplot.Value.Tuple.C b, Graphics.Gnuplot.Value.Tuple.C c) => Graphics.Gnuplot.Value.Tuple.C (a, b, c) instance (Graphics.Gnuplot.Value.Tuple.C a, Graphics.Gnuplot.Value.Tuple.C b, Graphics.Gnuplot.Value.Tuple.C c, Graphics.Gnuplot.Value.Tuple.C d) => Graphics.Gnuplot.Value.Tuple.C (a, b, c, d) module Graphics.Gnuplot.Graph.ThreeDimensional data T x y z type Type = String lineSpec :: T -> T x y z -> T x y z impulses :: (C x, C y, C z) => T x y z (x, y, z) vectors :: (C x, C y, C z) => T x y z ((x, y, z), (x, y, z)) -- | Deprecated: do not use this as graph type, use -- Graphics.Gnuplot.Plot.ThreeDimensional.surface instead pm3d :: (C x, C y, C z) => T x y z (x, y, z) lines :: (C x, C y, C z) => T x y z (x, y, z) points :: (C x, C y, C z) => T x y z (x, y, z) module Graphics.Gnuplot.Graph.TwoDimensional data T x y type Type = String -- | You can alter the line specification of graphs in a plot using -- fmap. lineSpec :: T -> T x y -> T x y listLines :: C y => T Int y y listPoints :: C y => T Int y y listLinesPoints :: C y => T Int y y listImpulses :: C y => T Int y y listDots :: C y => T Int y y histograms :: C y => T Int y y xErrorBarsRelative :: (C x, C y) => T x y ((x, y), x) yErrorBarsRelative :: (C x, C y) => T x y ((x, y), y) xyErrorBarsRelative :: (C x, C y) => T x y ((x, y), (x, y)) xErrorBarsAbsolute :: (C x, C y) => T x y ((x, y), (x, x)) yErrorBarsAbsolute :: (C x, C y) => T x y ((x, y), (y, y)) xyErrorBarsAbsolute :: (C x, C y) => T x y ((x, y), ((x, x), (y, y))) xErrorLinesRelative :: (C x, C y) => T x y ((x, y), x) yErrorLinesRelative :: (C x, C y) => T x y ((x, y), y) xyErrorLinesRelative :: (C x, C y) => T x y ((x, y), (x, y)) xErrorLinesAbsolute :: (C x, C y) => T x y ((x, y), (x, x)) yErrorLinesAbsolute :: (C x, C y) => T x y ((x, y), (y, y)) xyErrorLinesAbsolute :: (C x, C y) => T x y ((x, y), ((x, x), (y, y))) lines :: (C x, C y) => T x y (x, y) points :: (C x, C y) => T x y (x, y) linesPoints :: (C x, C y) => T x y (x, y) impulses :: (C x, C y) => T x y (x, y) dots :: (C x, C y) => T x y (x, y) steps :: (C x, C y) => T x y (x, y) fSteps :: (C x, C y) => T x y (x, y) hiSteps :: (C x, C y) => T x y (x, y) errorBars :: (C x, C y) => T x y (x, y) errorLines :: (C x, C y) => T x y (x, y) boxes :: (C x, C y) => T x y (x, y) filledCurves :: (C x, C y) => T x y (x, y) financeBars :: (C x, C y) => T x y (x, (y, y, y, y)) candleSticks :: (C x, C y) => T x y (x, (y, y, y, y)) vectors :: (C x, C y) => T x y ((x, y), (x, y)) image :: (C x, C y, C z) => T x y ((x, y), z) filledStripe :: (C x, C y) => T x y (x, (y, y)) filledStripeAbove :: (C x, C y) => T x y (x, (y, y)) filledStripeBelow :: (C x, C y) => T x y (x, (y, y)) labels :: (C x, C y) => T x y ((x, y), Label) module Graphics.Gnuplot.Frame.OptionSet.Histogram clustered :: (C x, C y) => T (T x y) -> T (T x y) clusteredGap :: (C x, C y) => Double -> T (T x y) -> T (T x y) errorbars :: (C x, C y) => T (T x y) -> T (T x y) errorbarsGap :: (C x, C y) => Double -> T (T x y) -> T (T x y) errorbarsGapLineWidth :: (C x, C y) => Double -> Double -> T (T x y) -> T (T x y) rowstacked :: (C x, C y) => T (T x y) -> T (T x y) columnstacked :: (C x, C y) => T (T x y) -> T (T x y) module Graphics.Gnuplot.Plot.TwoDimensional -- | Plots can be assembled using mappend or mconcat. You can -- alter attributes of embedded graphs using fmap. type T x y = T (T x y) -- |
--   list Type.listLines (take 30 (let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) in fibs))
--   list Type.lines (take 30 (let fibs0 = 0 : fibs1; fibs1 = 1 : zipWith (+) fibs0 fibs1 in zip fibs0 fibs1))
--   
list :: (C x, C y, C a) => T x y a -> [a] -> T x y -- |
--   function Type.line (linearScale 1000 (-10,10)) sin
--   
function :: (C x, C y, C a, C b) => T x y (a, b) -> [a] -> (a -> b) -> T x y -- |
--   functions Type.line (linearScale 1000 (-10,10)) [sin, cos]
--   
functions :: (C x, C y, C a, C b) => T x y (a, b) -> [a] -> [a -> b] -> T x y -- |
--   functionsWithLineSpec Type.line (linearScale 1000 (-10,10)) $
--      map (mapFst (flip LineSpec.title LineSpec.deflt)) [("sin", sin), ("cos", cos)]
--   
functionsWithLineSpec :: (C x, C y, C a, C b) => T x y (a, b) -> [a] -> [(T, a -> b)] -> T x y -- |
--   parameterFunction Type.line (linearScale 1000 (0,2*pi)) (\t -> (sin (2*t), cos t))
--   
parameterFunction :: (C x, C y, C a) => T x y a -> [t] -> (t -> a) -> T x y listFromFile :: (C i, C y) => T i y y -> FilePath -> Int -> T i y pathFromFile :: (C x, C y) => T x y (x, y) -> FilePath -> Int -> Int -> T x y linearScale :: Fractional a => Integer -> (a, a) -> [a] functionToGraph :: [x] -> (x -> y) -> [(x, y)] module Graphics.Gnuplot.Plot.ThreeDimensional -- | Plots can be assembled using mappend or mconcat or -- several functions from Data.Foldable. type T x y z = T (T x y z) cloud :: (C x, C y, C z, C a) => T x y z a -> [a] -> T x y z mesh :: (C x, C y, C z, C x, C y, C z) => [[(x, y, z)]] -> T x y z surface :: (C x, C y, C z, C x, C y, C z) => [x] -> [y] -> (x -> y -> z) -> T x y z linearScale :: Fractional a => Integer -> (a, a) -> [a] functionToGraph :: [x] -> (x -> y) -> [(x, y)] -- | 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. module Graphics.Gnuplot.Simple data Attribute -- | anything that is allowed after gnuplot's set command Custom :: String -> [String] -> Attribute EPS :: FilePath -> Attribute PNG :: FilePath -> Attribute -- | you cannot use this, call terminal instead Terminal :: T -> Attribute Grid :: Maybe [String] -> Attribute Key :: Maybe [String] -> Attribute Border :: Maybe [String] -> Attribute XTicks :: Maybe [String] -> Attribute YTicks :: Maybe [String] -> Attribute Size :: Size -> Attribute Aspect :: Aspect -> Attribute BoxAspect :: Aspect -> Attribute LineStyle :: Int -> [LineAttr] -> Attribute Title :: String -> Attribute XLabel :: String -> Attribute YLabel :: String -> Attribute ZLabel :: String -> Attribute XRange :: (Double, Double) -> Attribute YRange :: (Double, Double) -> Attribute ZRange :: (Double, Double) -> Attribute Palette :: [(Double, (Double, Double, Double))] -> Attribute ColorBox :: Maybe [String] -> Attribute XTime :: Attribute XFormat :: String -> Attribute data Size Scale :: Double -> Size SepScale :: Double -> Double -> Size data Aspect Ratio :: Double -> Aspect NoRatio :: Aspect -- | 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 LineAttr LineType :: Int -> LineAttr LineWidth :: Double -> LineAttr PointType :: Int -> LineAttr PointSize :: Double -> LineAttr LineTitle :: String -> LineAttr data LineSpec DefaultStyle :: Int -> LineSpec CustomStyle :: [LineAttr] -> LineSpec data PlotType Lines :: PlotType Points :: PlotType LinesPoints :: PlotType Impulses :: PlotType Dots :: PlotType Steps :: PlotType FSteps :: PlotType HiSteps :: PlotType ErrorBars :: PlotType XErrorBars :: PlotType YErrorBars :: PlotType XYErrorBars :: PlotType ErrorLines :: PlotType XErrorLines :: PlotType YErrorLines :: PlotType XYErrorLines :: PlotType Boxes :: PlotType FilledCurves :: PlotType BoxErrorBars :: PlotType BoxXYErrorBars :: PlotType FinanceBars :: PlotType CandleSticks :: PlotType Vectors :: PlotType PM3d :: PlotType data PlotStyle PlotStyle :: PlotType -> LineSpec -> PlotStyle [plotType] :: PlotStyle -> PlotType [lineSpec] :: PlotStyle -> LineSpec linearScale :: Fractional a => Integer -> (a, a) -> [a] defaultStyle :: PlotStyle terminal :: C term => term -> Attribute -- |
--   plotList [] (take 30 (let fibs = 0 : 1 : zipWith (+) fibs (tail fibs) in fibs))
--   
plotList :: C a => [Attribute] -> [a] -> IO () -- |
--   plotListStyle [] (defaultStyle{plotType = CandleSticks}) (Plot2D.functionToGraph (linearScale 32 (0,2*pi::Double)) (\t -> (-sin t, -2*sin t, 2*sin t, sin t)))
--   
plotListStyle :: C a => [Attribute] -> PlotStyle -> [a] -> IO () plotLists :: C a => [Attribute] -> [[a]] -> IO () plotListsStyle :: C a => [Attribute] -> [(PlotStyle, [a])] -> IO () -- |
--   plotFunc [] (linearScale 1000 (-10,10)) sin
--   
plotFunc :: (C a, C a) => [Attribute] -> [a] -> (a -> a) -> IO () -- |
--   plotFuncs [] (linearScale 1000 (-10,10)) [sin, cos]
--   
plotFuncs :: (C a, C a) => [Attribute] -> [a] -> [a -> a] -> IO () plotPath :: C a => [Attribute] -> [(a, a)] -> IO () plotPaths :: C a => [Attribute] -> [[(a, a)]] -> IO () plotPathStyle :: C a => [Attribute] -> PlotStyle -> [(a, a)] -> IO () plotPathsStyle :: C a => [Attribute] -> [(PlotStyle, [(a, a)])] -> IO () -- |
--   plotParamFunc [] (linearScale 1000 (0,2*pi)) (\t -> (sin (2*t), cos t))
--   
plotParamFunc :: (C a, C a) => [Attribute] -> [a] -> (a -> (a, a)) -> IO () -- |
--   plotParamFuncs [] (linearScale 1000 (0,2*pi)) [\t -> (sin (2*t), cos t), \t -> (cos t, sin (2*t))]
--   
plotParamFuncs :: (C a, C a) => [Attribute] -> [a] -> [a -> (a, a)] -> IO () plotDots :: (C a, C a) => [Attribute] -> [(a, a)] -> IO () data Plot3dType Surface :: Plot3dType ColorMap :: Plot3dType data CornersToColor Mean :: CornersToColor GeometricMean :: CornersToColor Median :: CornersToColor Corner1 :: CornersToColor Corner2 :: CornersToColor Corner3 :: CornersToColor Corner4 :: CornersToColor data Attribute3d Plot3dType :: Plot3dType -> Attribute3d CornersToColor :: CornersToColor -> Attribute3d -- |
--   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)))
--   
plotMesh3d :: (C x, C y, C z, C x, C y, C z) => [Attribute] -> [Attribute3d] -> [[(x, y, z)]] -> IO () -- |
--   let xs = [-2,-1.8..2::Double] in plotFunc3d [] [] xs xs (\x y -> exp(-(x*x+y*y)))
--   
plotFunc3d :: (C x, C y, C z, C x, C y, C z) => [Attribute] -> [Attribute3d] -> [x] -> [y] -> (x -> y -> z) -> IO () -- | Redirects the output of a plotting function to an EPS file and -- additionally converts it to PDF. epspdfPlot :: FilePath -> ([Attribute] -> IO ()) -> IO () -- | 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. inclPlot :: FilePath -> ([Attribute] -> IO ()) -> IO String module Graphics.Gnuplot.Frame.OptionSet data T graph deflt :: C graph => T graph -- | Add (set) an option with arguments as plain strings. -- -- This is very flexible, but not very safe. Use it only as fall-back, if -- there is no specific setter function in -- Graphics.Gnuplot.Frame.OptionSet. add :: T -> [String] -> T graph -> T graph -- | Remove (unset) an option. -- -- This is very flexible, but not very safe. Use it only as fall-back, if -- there is no specific setter function in -- Graphics.Gnuplot.Frame.OptionSet. remove :: T -> T graph -> T graph -- | Set or unset option according to a Bool. This is for switches -- that can be disabled using unset. -- -- This is very flexible, but not very safe. Use it only as fall-back, if -- there is no specific setter function in -- Graphics.Gnuplot.Frame.OptionSet. -- -- See also: addBool, add, remove. boolean :: T -> Bool -> T graph -> T graph -- | Add an option with boolean value that is formatted like set style -- fill border and set style fill noborder. The name of the -- internal state (i.e. border) must be stored in the second -- field of the option. -- -- This is very flexible, but not very safe. Use it only as fall-back, if -- there is no specific setter function in -- Graphics.Gnuplot.Frame.OptionSet. -- -- See also boolean. addBool :: T -> Bool -> T graph -> T graph size :: C graph => Double -> Double -> T graph -> T graph sizeRatio :: C graph => Double -> T graph -> T graph sizeSquare :: C graph => T graph -> T graph title :: C graph => String -> T graph -> T graph key :: C graph => Bool -> T graph -> T graph keyInside :: C graph => T graph -> T graph keyOutside :: C graph => T graph -> T graph xRange2d :: (C x, C y, C x) => (x, x) -> T (T x y) -> T (T x y) yRange2d :: (C x, C y, C y) => (y, y) -> T (T x y) -> T (T x y) xRange3d :: (C x, C y, C z, C x) => (x, x) -> T (T x y z) -> T (T x y z) yRange3d :: (C x, C y, C z, C y) => (y, y) -> T (T x y z) -> T (T x y z) zRange3d :: (C x, C y, C z, C z) => (z, z) -> T (T x y z) -> T (T x y z) xLabel :: C graph => String -> T graph -> T graph yLabel :: C graph => String -> T graph -> T graph zLabel :: (C x, C y, C z) => String -> T (T x y z) -> T (T x y z) xTicks2d :: (C x, C y, C x) => [(String, x)] -> T (T x y) -> T (T x y) yTicks2d :: (C x, C y, C y) => [(String, y)] -> T (T x y) -> T (T x y) xTicks3d :: (C x, C y, C z, C x) => [(String, x)] -> T (T x y z) -> T (T x y z) yTicks3d :: (C x, C y, C z, C y) => [(String, y)] -> T (T x y z) -> T (T x y z) zTicks3d :: (C x, C y, C z, C z) => [(String, z)] -> T (T x y z) -> T (T x y z) xLogScale :: C graph => T graph -> T graph yLogScale :: C graph => T graph -> T graph zLogScale :: (C x, C y, C z) => T (T x y z) -> T (T x y z) grid :: C graph => Bool -> T graph -> T graph gridXTicks :: C graph => Bool -> T graph -> T graph gridYTicks :: C graph => Bool -> T graph -> T graph gridZTicks :: (C x, C y, C z) => Bool -> T (T x y z) -> T (T x y z) xFormat :: C graph => String -> T graph -> T graph yFormat :: C graph => String -> T graph -> T graph zFormat :: (C x, C y, C z) => String -> T (T x y z) -> T (T x y z) -- | Set parameters of viewing a surface graph. See -- info:gnuplot/view view :: Double -> Double -> Double -> Double -> T (T x y z) -> T (T x y z) -- | Show flat pixel map. viewMap :: T (T x y z) -> T (T x y z) boxwidthRelative :: C graph => Double -> T graph -> T graph boxwidthAbsolute :: C graph => Double -> T graph -> T graph module Graphics.Gnuplot.Frame data T graph cons :: T graph -> T graph -> T graph simple :: C graph => T graph -> T graph empty :: T T