module Graphics.UI.GLUT.Colormap (
colorMapEntry,
copyColormap,
numColorMapEntries,
transparentIndex
) where
import Control.Monad.IO.Class ( MonadIO(..) )
import Data.StateVar ( GettableStateVar, makeGettableStateVar, StateVar, makeStateVar )
import Foreign.C.Types ( CInt )
import Graphics.Rendering.OpenGL.GL.VertexSpec ( Index1(..), Color3(..) )
import Graphics.Rendering.OpenGL ( GLint, GLfloat )
import Graphics.UI.GLUT.QueryUtils
import Graphics.UI.GLUT.Raw
import Graphics.UI.GLUT.Types
colorMapEntry :: Index1 GLint -> StateVar (Color3 GLfloat)
colorMapEntry :: Index1 GLint -> StateVar (Color3 GLfloat)
colorMapEntry (Index1 GLint
cell) =
IO (Color3 GLfloat)
-> (Color3 GLfloat -> IO ()) -> StateVar (Color3 GLfloat)
forall a. IO a -> (a -> IO ()) -> StateVar a
makeStateVar (CInt -> IO (Color3 GLfloat)
getColorMapEntry (GLint -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral GLint
cell))
(CInt -> Color3 GLfloat -> IO ()
setColorMapEntry (GLint -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral GLint
cell))
setColorMapEntry :: CInt -> Color3 GLfloat -> IO ()
setColorMapEntry :: CInt -> Color3 GLfloat -> IO ()
setColorMapEntry CInt
cell (Color3 GLfloat
r GLfloat
g GLfloat
b) = CInt -> GLfloat -> GLfloat -> GLfloat -> IO ()
forall (m :: * -> *).
MonadIO m =>
CInt -> GLfloat -> GLfloat -> GLfloat -> m ()
glutSetColor CInt
cell GLfloat
r GLfloat
g GLfloat
b
getColorMapEntry :: CInt -> IO (Color3 GLfloat)
getColorMapEntry :: CInt -> IO (Color3 GLfloat)
getColorMapEntry CInt
cell = do
GLfloat
r <- CInt -> CInt -> IO GLfloat
forall (m :: * -> *). MonadIO m => CInt -> CInt -> m GLfloat
glutGetColor CInt
cell CInt
glut_RED
GLfloat
g <- CInt -> CInt -> IO GLfloat
forall (m :: * -> *). MonadIO m => CInt -> CInt -> m GLfloat
glutGetColor CInt
cell CInt
glut_GREEN
GLfloat
b <- CInt -> CInt -> IO GLfloat
forall (m :: * -> *). MonadIO m => CInt -> CInt -> m GLfloat
glutGetColor CInt
cell CInt
glut_BLUE
Color3 GLfloat -> IO (Color3 GLfloat)
forall (m :: * -> *) a. Monad m => a -> m a
return (Color3 GLfloat -> IO (Color3 GLfloat))
-> Color3 GLfloat -> IO (Color3 GLfloat)
forall a b. (a -> b) -> a -> b
$ GLfloat -> GLfloat -> GLfloat -> Color3 GLfloat
forall a. a -> a -> a -> Color3 a
Color3 GLfloat
r GLfloat
g GLfloat
b
copyColormap :: MonadIO m => Window -> m ()
copyColormap :: Window -> m ()
copyColormap (Window CInt
win) = CInt -> m ()
forall (m :: * -> *). MonadIO m => CInt -> m ()
glutCopyColormap CInt
win
numColorMapEntries :: GettableStateVar GLint
numColorMapEntries :: GettableStateVar GLint
numColorMapEntries =
GettableStateVar GLint -> GettableStateVar GLint
forall a. IO a -> IO a
makeGettableStateVar (GettableStateVar GLint -> GettableStateVar GLint)
-> GettableStateVar GLint -> GettableStateVar GLint
forall a b. (a -> b) -> a -> b
$ Getter GLint
forall a. Getter a
simpleGet CInt -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral GLenum
glut_WINDOW_COLORMAP_SIZE
transparentIndex :: GettableStateVar (Index1 GLint)
transparentIndex :: GettableStateVar (Index1 GLint)
transparentIndex =
GettableStateVar (Index1 GLint) -> GettableStateVar (Index1 GLint)
forall a. IO a -> IO a
makeGettableStateVar (GettableStateVar (Index1 GLint)
-> GettableStateVar (Index1 GLint))
-> GettableStateVar (Index1 GLint)
-> GettableStateVar (Index1 GLint)
forall a b. (a -> b) -> a -> b
$
Getter (Index1 GLint)
forall a. Getter a
layerGet (GLint -> Index1 GLint
forall a. a -> Index1 a
Index1 (GLint -> Index1 GLint) -> (CInt -> GLint) -> CInt -> Index1 GLint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CInt -> GLint
forall a b. (Integral a, Num b) => a -> b
fromIntegral) GLenum
glut_TRANSPARENT_INDEX