-----------------------------------------------------------------------------
-- |
-- Module      :  Graphics.Rendering.Plot.Gtk.UI
-- Copyright   :  (c) Sumit Sahrawat
-- License     :  GPL-2
--
-- Maintainer  :  sumit.sahrawat.apm13@iitbhu.ac.in
-- Stability   :  provisional
-- Portability :  portable
--
-- Quick plotting for functions + dynamic plotting of functions
--
-- 'plotStatic' can be used to plot functions of the form /f(x)=.../
--
-- 'plotDynamic' can be used to plot functions of the form /f(x, a, b) =
-- .../ where /a/ and /b/ are additional parameters. Sliders are
-- provided for manipulating the values of /a/ and /b/, and the plot is
-- animated in real-time.
--
--------------------------------------------------------------------------------
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TypeFamilies     #-}

module Graphics.Rendering.Plot.Gtk.UI
    ( -- * The Plotting Functions
      plotStatic
    , plotDynamic
    , plotWithArity
    ) where

--------------------------------------------------------------------------------
-- Standard Libraries

import           Data.IORef                                (newIORef)

--------------------------------------------------------------------------------
-- Other Libraries

import           Data.Vector.Fixed                         (Dim, S, Vector, Z)
import qualified Data.Vector.Fixed                         as V
import           Data.Vector.Fixed.Unboxed                 (Vec)

--------------------------------------------------------------------------------
-- Custom Modules

import           Paths_plot_gtk_ui                         (getDataFileName)
import           Graphics.Rendering.Plot.Gtk.UI.PlotWindow
import           Graphics.Rendering.Plot.Gtk.UI.Settings

--------------------------------------------------------------------------------

-- | Quickly create AdjustmentSettings
argRange :: (Double, Double)    -- ^ Lower and upper range
         -> AdjustmentSettings
argRange (x, y) = aSetRange ((x + y) / 2) x y

--------------------------------------------------------------------------------

-- | Plots functions of multiple arguments, provided all arguments
-- have specified ranges. FOR INTERNAL USE, use 'plotWithArity' instead.
plotUnsafe :: ([Double] -> Double) -- ^ Function to plot
           -> [(Double, Double)]   -- ^ Ranges for all args
           -> IO ()
plotUnsafe func ranges = do
  iofset    <- newIORef defaultFigureSettings { xRange = Just . head $ ranges }
  plotGlade <- getDataFileName "plot-window.glade"
  let f xs x = func (x:xs)
  plotWindow plotGlade iofset (map argRange (tail ranges)) f

--------------------------------------------------------------------------------

-- | Plot functions that don't depend on extra parameters
plotStatic :: (Double -> Double) -- ^ Function to plot
           -> (Double, Double)   -- ^ Range for abscissa (horizontal axis)
           -> IO ()
plotStatic func r =
  let f :: Vec (S Z) Double -> Double
      f = func . V.head
  in plotDynamic f ((V.convert . V.Only $ r) :: Vec (S Z) (Double, Double))

--------------------------------------------------------------------------------

-- | Plot functions that depend on extra parameters
plotDynamic :: (Vector u a, Vector v (a, a),
                a ~ Double, Dim u ~ Dim v, Dim v ~ S n, V.Arity n)
            => (u Double -> Double)
            -> v (Double, Double)
            -> IO ()
plotDynamic func = plotUnsafe (func . V.fromList) . V.toList

--------------------------------------------------------------------------------

-- | Possibly returns an IO action that creates a plot assuming that
-- it's executing in a GTK environment (after initGUI). Returns
-- Nothing if no. of arguments does not match.
plotWithArity :: Int                  -- ^ Arity of function to plot
              -> ([Double] -> Double) -- ^ Function to plot
              -> [(Double, Double)]   -- ^ Ranges for all args
              -> Maybe (IO ())
plotWithArity n func ranges =
  if length ranges /= n
  then Nothing
  else Just $ plotUnsafe func ranges

--------------------------------------------------------------------------------