-- | Interface functions to the "gnuplot" package for generating plots. module Test.SBench.Plot.Gnuplot ( series2plot , series2scaledPlot , series2plotWith , series2scaledPlotWith , series2plotWithLinestyle , series2scaledPlotWithLinestyle , sbench2plot , sbench2scaledPlot , sbench2plotWithLinestyle , sbench2scaledPlotWithLinestyle , sbench2plotWith , sbench2scaledPlotWith , toDiagram , toDiagramWith ) where import qualified Graphics.Gnuplot.Plot.TwoDimensional as Plot2D import qualified Graphics.Gnuplot.Graph.TwoDimensional as Graph2D import qualified Graphics.Gnuplot.Frame.OptionSet as Opts import qualified Graphics.Gnuplot.LineSpecification as LineSpec import qualified Graphics.Gnuplot.Advanced as GPlot ( plot ) import qualified Graphics.Gnuplot.Frame as Frame import qualified Graphics.Gnuplot.Terminal.PostScript as PostScript import qualified Graphics.Gnuplot.Value.Tuple as TVal import qualified Graphics.Gnuplot.Value.Atom as AVal import qualified Graphics.Gnuplot.Graph as Graph import Data.Monoid ( mappend, mempty ) import System.FilePath ( (<.>) ) import System.Process ( system ) import Test.SBench.Options ( Title ) import Test.SBench.File.FileOps ( sbench2series ) import Test.SBench.File.Types ( MetaInfo(..) ) -- * Plot from a data series series2plot :: (TVal.C a, AVal.C a, TVal.C b, AVal.C b) => Title -- ^ Title of the graph. -> [(a, b)] -- ^ Data to plot. -> Plot2D.T a b -- ^ The plot. series2plot = series2scaledPlot id id series2scaledPlot :: (TVal.C c, AVal.C c, TVal.C d, AVal.C d) => (a -> c) -- ^ scale x-axis -> (b -> d) -- ^ scale y-axis -> Title -- ^ Title of the graph. -> [(a, b)] -- ^ Data to plot. -> Plot2D.T c d -- ^ The plot. series2scaledPlot xscaler yscaler t s = let s' = scaleSeries xscaler yscaler s in Graph2D.lineSpec (LineSpec.title t $ LineSpec.deflt) `fmap` Plot2D.list Graph2D.lines s' series2plotWithLinestyle :: (TVal.C a, AVal.C a, TVal.C b, AVal.C b) => Int -- ^ Linestyle. See 'gnuplot' manual. -> Title -- ^ Title of the graph. -> [(a, b)] -- ^ Data to plot -> Plot2D.T a b -- ^ the plot. series2plotWithLinestyle linestyle = series2scaledPlotWithLinestyle linestyle id id series2scaledPlotWithLinestyle :: (TVal.C c, AVal.C c, TVal.C d, AVal.C d) => Int -- ^ Linestyle. See 'gnuplot' manual. -> (a -> c) -- ^ scale x-axis -> (b -> d) -- ^ scale y-axis -> Title -- ^ Title of the graph. -> [(a, b)] -- ^ Data to plot -> Plot2D.T c d -- ^ the plot. series2scaledPlotWithLinestyle linestyle xscaler yscaler title = series2scaledPlotWith [LineSpec.title title, LineSpec.lineStyle linestyle] xscaler yscaler series2plotWith :: (TVal.C a, AVal.C a, TVal.C b, AVal.C b) => [LineSpec.T -> LineSpec.T] -- ^ Line specification, see "Graphics.Gnuplot.LineSpecification". -> [(a, b)] -- ^ Data to plot -> Plot2D.T a b -- ^ the plot. series2plotWith opts = series2scaledPlotWith opts id id series2scaledPlotWith :: (TVal.C c, AVal.C c, TVal.C d, AVal.C d) => [LineSpec.T -> LineSpec.T] -- ^ Line specification, see "Graphics.Gnuplot.LineSpecification". -> (a -> c) -- ^ scale x-axis -> (b -> d) -- ^ scale y-axis -> [(a, b)] -- ^ Data to plot -> Plot2D.T c d -- ^ the plot. series2scaledPlotWith opts xscaler yscaler s = let s' = scaleSeries xscaler yscaler s in Graph2D.lineSpec (makeGraphOpts opts) `fmap` Plot2D.list Graph2D.lines s' -- * Plot from a .sbench data file sbench2plot :: FilePath -> IO (Plot2D.T Double Double) sbench2plot = sbench2scaledPlot id id sbench2scaledPlot :: (Double -> Double) -- ^ scale x-axis -> (Double -> Double) -- ^ scale y-axis -> FilePath -- ^ data file -> IO (Plot2D.T Double Double) -- ^ produced plot sbench2scaledPlot xscaler yscaler file = do (mi, s) <- sbench2series file return $ series2scaledPlot xscaler yscaler (miGraphTitle mi) s sbench2plotWithLinestyle :: Int -- ^ Linestyle. See 'gnuplot' manual. -> FilePath -- ^ data file -> IO (Plot2D.T Double Double) -- ^ produced plot sbench2plotWithLinestyle linestyle = sbench2scaledPlotWithLinestyle linestyle id id sbench2scaledPlotWithLinestyle :: Int -- ^ Linestyle. See 'gnuplot' manual. -> (Double -> Double) -- ^ scale x-axis -> (Double -> Double) -- ^ scale y-axis -> FilePath -- ^ data file -> IO (Plot2D.T Double Double) -- ^ produced plot sbench2scaledPlotWithLinestyle linestyle xscaler yscaler file = do (mi, s) <- sbench2series file return $ series2scaledPlotWith [LineSpec.title (miGraphTitle mi), LineSpec.lineStyle linestyle] xscaler yscaler s sbench2plotWith :: [LineSpec.T -> LineSpec.T] -- ^ Line specifications. See "Graphics.Gnuplot.LineSpecification" -> FilePath -- ^ data file -> IO (Plot2D.T Double Double) -- ^ produced plot sbench2plotWith lineOpts = sbench2scaledPlotWith lineOpts id id sbench2scaledPlotWith :: [LineSpec.T -> LineSpec.T] -- ^ Line specifications. See "Graphics.Gnuplot.LineSpecification" -> (Double -> Double) -- ^ scale x-axis -> (Double -> Double) -- ^ scale y-axis -> FilePath -- ^ data file -> IO (Plot2D.T Double Double) -- ^ produced plot sbench2scaledPlotWith lineOpts xscaler yscaler file = do (mi, s) <- sbench2series file return $ series2scaledPlotWith lineOpts xscaler yscaler s -- * Combine plots to a diagram -- | Produces a diagram with several plots inside. -- -- The parameters are as follows -- [@terminal@] Choose the output terminal. See "Graphics.Gnuplot.Terminal" -- [@opts@] Frame options, e.g. title. See "Graphics.Gnuplot.Frame.OptionSet" -- [@plots@] List of plots to be shown in the diagram. toDiagramWith terminal opts plots = GPlot.plot terminal gr where gr = Frame.cons (makeFrameOpts opts) $ combinePlots plots -- | Compared to 'toDiagramWith', the output terminal is fixed to -- "Graphics.Gnuplot.Terminal.PostScript" and the resulting -- .eps file is transformed to a .pdf via a call to 'epstopdf'. -- -- The parameters are as follows -- [@name@] Choose the output terminal. See "Graphics.Gnuplot.Terminal" -- [@topts@] Frame options, e.g. title. See "Graphics.Gnuplot.Frame.OptionSet" -- [@opts@] List of plots to be shown in the diagram. -- [@plots@] List of plots to be shown in the diagram. toDiagram name topts opts plots = let file = name <.> "eps" plt = (Frame.cons (makeFrameOpts opts) (combinePlots plots)) in GPlot.plot (foldr ($) (PostScript.cons file) topts) plt >> system ("epstopdf " ++ file) >> return (name <.> "pdf") -- * Auxiliar functions --scaleSeries :: (a -> b) -> (c -> d) -> [(a, c)] -> [(b, d)] scaleSeries xscaler yscaler = map (\(x,y) -> (xscaler x, yscaler y)) makeGraphOpts :: [LineSpec.T -> LineSpec.T] -> LineSpec.T makeGraphOpts = foldr ($) LineSpec.deflt makeFrameOpts :: Graph.C graph => [Opts.T graph -> Opts.T graph] -> Opts.T graph makeFrameOpts = foldr ($) Opts.deflt combinePlots :: (TVal.C a, AVal.C a, TVal.C b, AVal.C b) => [Plot2D.T a b] -> Plot2D.T a b combinePlots = foldr mappend mempty