module Gamgine.State.RenderState where
#include "Gamgine/Utils.cpp"
import Control.Applicative ((<$>))
import qualified Data.List as L
import qualified Graphics.GL as GL
import qualified Gamgine.Font.GLF as GLF
IMPORT_LENS_AS_LE
newtype TextureName = TextureName Int deriving (Int -> TextureName -> ShowS
[TextureName] -> ShowS
TextureName -> String
(Int -> TextureName -> ShowS)
-> (TextureName -> String)
-> ([TextureName] -> ShowS)
-> Show TextureName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> TextureName -> ShowS
showsPrec :: Int -> TextureName -> ShowS
$cshow :: TextureName -> String
show :: TextureName -> String
$cshowList :: [TextureName] -> ShowS
showList :: [TextureName] -> ShowS
Show, TextureName -> TextureName -> Bool
(TextureName -> TextureName -> Bool)
-> (TextureName -> TextureName -> Bool) -> Eq TextureName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TextureName -> TextureName -> Bool
== :: TextureName -> TextureName -> Bool
$c/= :: TextureName -> TextureName -> Bool
/= :: TextureName -> TextureName -> Bool
Eq)
newtype FontName = FontName Int deriving (Int -> FontName -> ShowS
[FontName] -> ShowS
FontName -> String
(Int -> FontName -> ShowS)
-> (FontName -> String) -> ([FontName] -> ShowS) -> Show FontName
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FontName -> ShowS
showsPrec :: Int -> FontName -> ShowS
$cshow :: FontName -> String
show :: FontName -> String
$cshowList :: [FontName] -> ShowS
showList :: [FontName] -> ShowS
Show, FontName -> FontName -> Bool
(FontName -> FontName -> Bool)
-> (FontName -> FontName -> Bool) -> Eq FontName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FontName -> FontName -> Bool
== :: FontName -> FontName -> Bool
$c/= :: FontName -> FontName -> Bool
/= :: FontName -> FontName -> Bool
Eq)
type TextureIds = [(TextureName, GL.GLuint)]
type FontIds = [(FontName , GLF.FontId)]
data Ressources = Ressources {
Ressources -> TextureIds
textureIds :: TextureIds,
Ressources -> FontIds
fontIds :: FontIds
} deriving Int -> Ressources -> ShowS
[Ressources] -> ShowS
Ressources -> String
(Int -> Ressources -> ShowS)
-> (Ressources -> String)
-> ([Ressources] -> ShowS)
-> Show Ressources
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ressources -> ShowS
showsPrec :: Int -> Ressources -> ShowS
$cshow :: Ressources -> String
show :: Ressources -> String
$cshowList :: [Ressources] -> ShowS
showList :: [Ressources] -> ShowS
Show
emptyRessources :: Ressources
emptyRessources :: Ressources
emptyRessources = TextureIds -> FontIds -> Ressources
Ressources [] []
textureId :: TextureName -> Ressources -> Maybe GL.GLuint
textureId :: TextureName -> Ressources -> Maybe GLuint
textureId TextureName
name Ressources
res = TextureName -> TextureIds -> Maybe GLuint
forall a b. Eq a => a -> [(a, b)] -> Maybe b
L.lookup TextureName
name (TextureIds -> Maybe GLuint) -> TextureIds -> Maybe GLuint
forall a b. (a -> b) -> a -> b
$ Ressources -> TextureIds
textureIds Ressources
res
fontId :: FontName -> Ressources -> Maybe GLF.FontId
fontId :: FontName -> Ressources -> Maybe FontId
fontId FontName
name Ressources
res = FontName -> FontIds -> Maybe FontId
forall a b. Eq a => a -> [(a, b)] -> Maybe b
L.lookup FontName
name (FontIds -> Maybe FontId) -> FontIds -> Maybe FontId
forall a b. (a -> b) -> a -> b
$ Ressources -> FontIds
fontIds Ressources
res
LENS(textureIds)
LENS(fontIds)
data RenderState = RenderState {
RenderState -> Double
nextFrameFraction :: Double,
RenderState -> Ressources
ressources :: Ressources,
RenderState -> (Double, Double)
frustumSize :: (Double, Double)
} deriving Int -> RenderState -> ShowS
[RenderState] -> ShowS
RenderState -> String
(Int -> RenderState -> ShowS)
-> (RenderState -> String)
-> ([RenderState] -> ShowS)
-> Show RenderState
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RenderState -> ShowS
showsPrec :: Int -> RenderState -> ShowS
$cshow :: RenderState -> String
show :: RenderState -> String
$cshowList :: [RenderState] -> ShowS
showList :: [RenderState] -> ShowS
Show
LENS(nextFrameFraction)
LENS(ressources)
LENS(frustumSize)