{-# LANGUAGE TemplateHaskell #-}
module Graphics.RedViz.Drawable
( uniforms
, u_xform
, Drawable (..)
, Uniforms (..)
) where
import Graphics.RedViz.Material
import Graphics.RedViz.Descriptor
import Graphics.Rendering.OpenGL (Program)
import Foreign.C
import Linear.Matrix
import Control.Lens
data Drawable
= Drawable
{ Drawable -> String
name :: String
, Drawable -> Uniforms
_uniforms :: Uniforms
, Drawable -> Descriptor
_descriptor :: Descriptor
, Drawable -> Program
_program :: Program
} deriving Int -> Drawable -> ShowS
[Drawable] -> ShowS
Drawable -> String
(Int -> Drawable -> ShowS)
-> (Drawable -> String) -> ([Drawable] -> ShowS) -> Show Drawable
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Drawable] -> ShowS
$cshowList :: [Drawable] -> ShowS
show :: Drawable -> String
$cshow :: Drawable -> String
showsPrec :: Int -> Drawable -> ShowS
$cshowsPrec :: Int -> Drawable -> ShowS
Show
data Uniforms
= Uniforms
{
Uniforms -> Material
_u_mats :: Material
, Uniforms -> Program
_u_prog :: Program
, Uniforms -> (Double, Double)
_u_mouse :: (Double, Double)
, Uniforms -> Double
_u_time :: Double
, Uniforms -> (CInt, CInt)
_u_res :: (CInt, CInt)
, Uniforms -> M44 Double
_u_cam :: M44 Double
, Uniforms -> Double
_u_cam_a :: Double
, Uniforms -> Double
_u_cam_f :: Double
, Uniforms -> M44 Double
_u_xform :: M44 Double
} deriving Int -> Uniforms -> ShowS
[Uniforms] -> ShowS
Uniforms -> String
(Int -> Uniforms -> ShowS)
-> (Uniforms -> String) -> ([Uniforms] -> ShowS) -> Show Uniforms
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Uniforms] -> ShowS
$cshowList :: [Uniforms] -> ShowS
show :: Uniforms -> String
$cshow :: Uniforms -> String
showsPrec :: Int -> Uniforms -> ShowS
$cshowsPrec :: Int -> Uniforms -> ShowS
Show
$(makeLenses ''Drawable)
$(makeLenses ''Uniforms)