-- | This module provides an easy-to-use interface to create an interactive, graphical front-end for you graph rewriting system. The controls of the GUI are:
--
-- - left-click on a menu entry: rule selection. At all times for each redex (according to the selected rule) one node of the redex (the first node that is matched) is marked red in the graph.
--
-- - right-click on a menu entry: applies the rule once for each redex currently existing in the graph. No contractions take place for redexes deleted or arisen during this process.
--
-- - right-click on a (red) node: applies the selected rule to the redex containing the node.
--
-- - drag a node: by this you can manually help out the graph drawing mechanism to find a better layout.
--
-- - drag outside of a node: scroll around.
--
-- - mouse wheel: zoom
--
-- - @z@: autozoom
--
-- - @space@: pause/resume layouting
--
-- Please have a look the graph-rewriting-ski package for an example application that makes use of this library.
module GraphRewriting.GL.UI (module GraphRewriting.GL.UI, LabeledTree (..)) where

import qualified Graphics.UI.GLUT as GL
import Graphics.UI.GLUT (($=), get)
import GraphRewriting.Graph
import GraphRewriting.Graph.Read
import GraphRewriting.Rule
import Data.IORef
import GraphRewriting.GL.Render
import GraphRewriting.GL.Global
import GraphRewriting.GL.HyperEdge
import GraphRewriting.GL.Canvas
import GraphRewriting.GL.Menu
import GraphRewriting.Layout.RotPortSpec
import Data.Set as Set
import Control.Monad

-- | Initialises GLUT. Returns program name and command line arguments.
initialise  IO (String, [String])
initialise = GL.getArgsAndInitialize

-- | After initialisation 'run' can be used to start the GUI
run  (View [Port] n, Render n, View Position n, PortSpec n, View Rotation n)
     Int                  -- ^ The number of layout steps to apply before displaying the graph
     (Graph n  Graph n)  -- ^ A projection function that is applied just before displaying the graph
     Rewrite n a          -- ^ The monadic graph transformation code for a layout step
     Graph n
     LabeledTree (Rule n) -- ^ The rule menu given as a tree of named rules
     IO ()
run initSteps project layoutStep g rules = do
	globalVars  newIORef $ GlobalVars
		{graph        = execGraph (replicateM_ initSteps layoutStep) g,
		 paused       = False,
		 selectedRule = fail "none",
		 highlighted  = Set.empty,
		 layoutStep   = layoutStep >> return (),
		 canvas       = undefined}
--	print =<< get GL.sampleBuffers
--	print =<< get GL.samples
--	print =<< get GL.subpixelBits

--	GL.initialDisplayCapabilities $= [GL.With GL.DisplayDouble, GL.With GL.DisplaySamples]
--	GL.multisample $= GL.Enabled
	GL.initialDisplayMode $= [GL.DoubleBuffered, GL.Multisampling]
	p  get GL.displayModePossible
	when (not p) $ do
		GL.initialDisplayMode $= [GL.DoubleBuffered]
		p  get GL.displayModePossible
		when (not p) $ GL.initialDisplayMode $= []
	c  setupCanvas project star globalVars
	modifyIORef globalVars $ \v  v {canvas = c}
	setupMenu rules globalVars
	layoutLoop globalVars
	GL.mainLoop
	GL.exit