plot-gtk-0.1.0.10: GTK plots and interaction with GHCi

Portabilityportable
Stabilityprovisional
Maintainerhaskell.vivian.mcphail <at> gmail <dot> com
Safe HaskellSafe-Infered

Graphics.Rendering.Plot.Gtk

Contents

Description

Enables the display of Figures interactively through GHCi

Synopsis

Interface

display :: Figure () -> IO PlotHandleSource

create a new figure and display the plot click on the window to save

destroy :: PlotHandle -> IO ()Source

close a plot

withPlotHandle :: PlotHandle -> Figure () -> IO ()Source

perform some actions on the supplied PlotHandle

writePlotHandle :: PlotHandle -> OutputType -> FilePath -> (Int, Int) -> IO ()Source

write the Figure to disk

Example

We can create a figure:

 import Data.Colour.Names
 
 import qualified Data.Array.IArray as A
 
 import Numeric.Vector
 import Numeric.Matrix
 
 import Numeric.GSL.Statistics
 
 import Graphics.Rendering.Plot
 import Graphics.Rendering.Plot.Gtk
 
 ln = 25
 ts = linspace ln (0,1)
 rs = randomVector 0 Gaussian ln
 
 ss = sin (15*2*pi*ts)
 ds = 0.25*rs + ss
 es = constant (0.25*(stddev rs)) ln
 
 fs :: Double -> Double
 fs = sin . (15*2*pi*)
 
 ms :: Matrix Double
 ms = buildMatrix 64 64 (\(x,y) -> sin (2*2*pi*(fromIntegral x)/64) * cos (5*2*pi*(fromIntegral y)/64))
 
 figure = do
         withTextDefaults $ setFontFamily "OpenSymbol"
         withTitle $ setText "Testing plot package:"
         withSubTitle $ do
                        setText "with 1 second of a 15Hz sine wave"
                        setFontSize 10
         setPlots 1 2
         withPlot (1,1) $ do
                          setDataset (ts,[point (ds,es,"Sampled data") (Bullet,green)
                                        ,line (fs,"15 Hz sinusoid") blue])
                          addAxis XAxis (Side Lower) $ do
                                                       setGridlines Major True
                                                       withAxisLabel $ setText "time (s)"
                          addAxis YAxis (Side Lower) $ do
                                                       setGridlines Major True
                                                       withAxisLabel $ setText "amplitude"
                          addAxis XAxis (Value 0) $ return ()
                          setRangeFromData XAxis Lower
                          setRange YAxis Lower (-1.25) 1.25
                          setLegend True NorthEast Inside
                          withLegendFormat $ setFontSize 6

observe the results:

>>> figure1 <- display figure

and then update the figure

>>> withPlotHandle figure1 $ withPlot (1,2) $ setDataset ms

and update again

>>> withPlotHandle figure1 $ withPlot (1,2) $ do { addAxis XAxis (Side Lower) $ setTickLabelFormat "%.0f" }
>>> let withfig1_12 = \d -> withPlotHandle figure1 $ withPlot (1,2) d
>>> withfig1_12 $ addAxis YAxis (Side Lower) $ setTickLabelFormat "%.0f"
>>> withfig1_12 $ setRangeFromData XAxis Lower
>>> withfig1_12 $ setRangeFromData YAxis Lower

with the multiline feature

>>> :set +m
>>> withPlotHandle figure1 $ withPlot (1,2) $ do
>>> addAxis XAxis (Side Lower) $ setTickLabelFormat "%.0f"
>>> setRangeFromData XAxis Lower
>>> setRangeFromData YAxis Lower