{-# LANGUAGE UnicodeSyntax #-}
module GraphRewriting.GL.Render where

import Data.Vector.V2
import Graphics.Rendering.OpenGL (GLdouble)
import qualified Graphics.Rendering.OpenGL as GL
import qualified Graphics.UI.GLUT as GL
import Unsafe.Coerce


-- | Here the OpenGL code for rendering a node can be given. The node-size is expected to be roughly 2 (radius 1) but this is not a requirement.
class Render a where render  a  IO ()

convertDouble  Double  GLdouble
convertDouble :: GLdouble -> GLdouble
convertDouble = GLdouble -> GLdouble
forall a b. a -> b
unsafeCoerce

convertGLdouble  GLdouble  Double
convertGLdouble :: GLdouble -> GLdouble
convertGLdouble = GLdouble -> GLdouble
forall a b. a -> b
unsafeCoerce

vector  Vector2  GL.Vector3 GLdouble
vector :: Vector2 -> Vector3 GLdouble
vector Vector2
v = GLdouble -> GLdouble -> GLdouble -> Vector3 GLdouble
forall a. a -> a -> a -> Vector3 a
GL.Vector3 (GLdouble -> GLdouble
convertDouble (GLdouble -> GLdouble) -> GLdouble -> GLdouble
forall a b. (a -> b) -> a -> b
$ Vector2 -> GLdouble
v2x Vector2
v) (GLdouble -> GLdouble
convertDouble (GLdouble -> GLdouble) -> GLdouble -> GLdouble
forall a b. (a -> b) -> a -> b
$ Vector2 -> GLdouble
v2y Vector2
v) GLdouble
0

vertex  Vector2  IO ()
vertex :: Vector2 -> IO ()
vertex Vector2
v = Vertex2 GLdouble -> IO ()
forall a. Vertex a => a -> IO ()
GL.vertex (Vertex2 GLdouble -> IO ()) -> Vertex2 GLdouble -> IO ()
forall a b. (a -> b) -> a -> b
$ GLdouble -> GLdouble -> Vertex2 GLdouble
forall a. a -> a -> Vertex2 a
GL.Vertex2 (GLdouble -> GLdouble
convertDouble (GLdouble -> GLdouble) -> GLdouble -> GLdouble
forall a b. (a -> b) -> a -> b
$ Vector2 -> GLdouble
v2x Vector2
v) (GLdouble -> GLdouble
convertDouble (GLdouble -> GLdouble) -> GLdouble -> GLdouble
forall a b. (a -> b) -> a -> b
$ Vector2 -> GLdouble
v2y Vector2
v)

vector2  (Double,Double)  GL.Vector3 GLdouble
vector2 :: (GLdouble, GLdouble) -> Vector3 GLdouble
vector2 (GLdouble
x,GLdouble
y) = GLdouble -> GLdouble -> GLdouble -> Vector3 GLdouble
forall a. a -> a -> a -> Vector3 a
GL.Vector3 (GLdouble -> GLdouble
convertDouble GLdouble
x) (GLdouble -> GLdouble
convertDouble GLdouble
y) GLdouble
0

vertex2  (Double,Double)  IO ()
vertex2 :: (GLdouble, GLdouble) -> IO ()
vertex2 (GLdouble
x,GLdouble
y) = Vertex2 GLdouble -> IO ()
forall a. Vertex a => a -> IO ()
GL.vertex (Vertex2 GLdouble -> IO ()) -> Vertex2 GLdouble -> IO ()
forall a b. (a -> b) -> a -> b
$ GLdouble -> GLdouble -> Vertex2 GLdouble
forall a. a -> a -> Vertex2 a
GL.Vertex2 (GLdouble -> GLdouble
convertDouble GLdouble
x) (GLdouble -> GLdouble
convertDouble GLdouble
y)

renderString  String  IO ()
renderString :: String -> IO ()
renderString String
label = IO () -> IO ()
forall a. IO a -> IO a
GL.preservingMatrix (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
	Vector3 GLdouble -> IO ()
forall c. MatrixComponent c => Vector3 c -> IO ()
GL.translate (Vector3 GLdouble -> IO ()) -> Vector3 GLdouble -> IO ()
forall a b. (a -> b) -> a -> b
$ (GLdouble, GLdouble) -> Vector3 GLdouble
vector2 (-GLdouble
0.3,-GLdouble
0.3)
	GLdouble -> GLdouble -> GLdouble -> IO ()
forall c. MatrixComponent c => c -> c -> c -> IO ()
GL.scale GLdouble
0.007 GLdouble
0.007 (GLdouble
0  GL.GLdouble)
	StrokeFont -> String -> IO ()
forall a (m :: * -> *). (Font a, MonadIO m) => a -> String -> m ()
forall (m :: * -> *). MonadIO m => StrokeFont -> String -> m ()
GL.renderString StrokeFont
GL.MonoRoman String
label