{-# OPTIONS_HADDOCK hide #-}
module Graphics.Gloss.Internals.Rendering.State
( State (..)
, initState
, Texture (..))
where
import Graphics.Gloss.Internals.Data.Picture
import Foreign.ForeignPtr
import System.Mem.StableName
import Data.Word
import Data.IORef
import qualified Graphics.Rendering.OpenGL.GL as GL
data State
= State
{
State -> Bool
stateColor :: !Bool
, State -> Bool
stateWireframe :: !Bool
, State -> Bool
stateBlendAlpha :: !Bool
, State -> Bool
stateLineSmooth :: !Bool
, State -> IORef [Texture]
stateTextures :: !(IORef [Texture])
}
data Texture
= Texture
{
Texture -> StableName BitmapData
texName :: StableName BitmapData
, Texture -> Int
texWidth :: Int
, Texture -> Int
texHeight :: Int
, Texture -> ForeignPtr Word8
texData :: ForeignPtr Word8
, Texture -> TextureObject
texObject :: GL.TextureObject
, Texture -> Bool
texCacheMe :: Bool }
initState :: IO State
initState :: IO State
initState
= do IORef [Texture]
textures <- [Texture] -> IO (IORef [Texture])
forall a. a -> IO (IORef a)
newIORef []
State -> IO State
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return State
{ stateColor :: Bool
stateColor = Bool
True
, stateWireframe :: Bool
stateWireframe = Bool
False
, stateBlendAlpha :: Bool
stateBlendAlpha = Bool
True
, stateLineSmooth :: Bool
stateLineSmooth = Bool
False
, stateTextures :: IORef [Texture]
stateTextures = IORef [Texture]
textures }