----------------------------------------------------------------------------- -- | -- Module : Graphics.Rendering.Plot.Gtk.UI -- Copyright : (c) Sumit Sahrawat -- License : GPL-2 -- -- Maintainer : sumit.sahrawat.apm13@iitbhu.ac.in -- Stability : provisional -- Portability : portable -- -- Functions to build and make changes to 'Figure's -- -------------------------------------------------------------------------------- module Graphics.Rendering.Plot.Gtk.UI.Figure where -------------------------------------------------------------------------------- -- Standard Libraries import Control.Monad (unless, when) import Data.IORef (IORef, readIORef) import Data.Maybe (fromJust, isJust) -------------------------------------------------------------------------------- -- Other Libraries -- import Data.Colour.SRGB (sRGB24read) import Graphics.Rendering.Plot import Graphics.UI.Gtk (Adjustment, adjustmentGetValue) import Numeric.LinearAlgebra (linspace, cmap) -------------------------------------------------------------------------------- -- Custom Modules import Graphics.Rendering.Plot.Gtk.UI.Settings -------------------------------------------------------------------------------- updateFigureText :: (Text () -> Figure ()) -> Maybe String -> Double -> Figure () updateFigureText withSomething txt size = case txt of Nothing -> return () Just str -> withSomething . unless (null str) $ do setText str setFontSize size -------------------------------------------------------------------------------- updateAxis :: AxisType -> Bool -> (AxisPosn, AxisSide) -> Maybe (Double, Double) -> Scale -> Maybe String -> FontSize -> Plot () updateAxis axis state location range scale label size = do let (position, side) = location when state $ addAxis axis position (when (isJust label) $ withAxisLabel $ do setText . fromJust $ label setFontSize size) maybe (setRangeFromData axis side scale) (uncurry (setRange axis side scale)) range -------------------------------------------------------------------------------- figurePlot :: ([Double] -> Double -> Double) -> IORef FigureSettings -> [Adjustment] -> IO (Figure ()) figurePlot g iofset adjs = do fset <- readIORef iofset vars <- mapM adjustmentGetValue adjs let rate = samplingRate fset range = fromJust $ xRange fset samples = round $ (\(x, y) -> rate * (y - x)) range domain = linspace samples range func = g vars stype = plotType fset dset = [(stype, domain, cmap func domain)] return $ buildFigure dset fset -------------------------------------------------------------------------------- buildFigure :: Dataset a => a -> FigureSettings -> Figure () buildFigure dset fset = do withTextDefaults $ setFontFamily (fontFamily fset) let str = plotTitle fset size = plotTitleSize fset in updateFigureText withTitle str size let str = subTitle fset size = subTitleSize fset in updateFigureText withSubTitle str size setPlots 1 1 withPlot (1, 1) $ do setDataset dset -- X-Axis let state = showXAxis fset label = xLabel fset size = xLabelSize fset loc = xLocation fset range = xRange fset scale = plotScaleX fset in updateAxis XAxis state loc range scale label size -- Y-Axis let state = showYAxis fset label = yLabel fset size = yLabelSize fset loc = yLocation fset range = yRange fset scale = plotScaleY fset in updateAxis YAxis state loc range scale label size --------------------------------------------------------------------------------