module Graphics.UI.GLUT.State (
windowBorderWidth, windowHeaderHeight,
rgba,
BufferDepth, rgbaBufferDepths, colorBufferDepth,
doubleBuffered, stereo,
accumBufferDepths, depthBufferDepth, stencilBufferDepth,
SampleCount, sampleCount, formatID,
damaged,
elapsedTime,
screenSize, screenSizeMM,
hasKeyboard,
ButtonCount, numMouseButtons,
numSpaceballButtons,
DialCount, numDialsAndButtons,
numTabletButtons,
AxisCount, PollRate, joystickInfo,
glutVersion
) where
import Foreign.C.Types ( CInt )
import Foreign.Ptr ( nullFunPtr )
import Graphics.Rendering.OpenGL.GL.BasicTypes ( GLenum )
import Graphics.Rendering.OpenGL.GL.CoordTrans ( Size(..) )
import Graphics.Rendering.OpenGL.GL.StateVar (
GettableStateVar, makeGettableStateVar )
import Graphics.UI.GLUT.Constants (
glut_WINDOW_RGBA,
glut_WINDOW_RED_SIZE, glut_WINDOW_GREEN_SIZE, glut_WINDOW_BLUE_SIZE,
glut_WINDOW_ALPHA_SIZE, glut_WINDOW_BUFFER_SIZE,
glut_WINDOW_DOUBLEBUFFER, glut_WINDOW_STEREO,
glut_WINDOW_ACCUM_RED_SIZE, glut_WINDOW_ACCUM_GREEN_SIZE,
glut_WINDOW_ACCUM_BLUE_SIZE, glut_WINDOW_ACCUM_ALPHA_SIZE,
glut_WINDOW_DEPTH_SIZE, glut_WINDOW_STENCIL_SIZE, glut_WINDOW_NUM_SAMPLES,
glut_WINDOW_FORMAT_ID, glut_ELAPSED_TIME,
glut_NORMAL_DAMAGED, glut_OVERLAY_DAMAGED,
glut_SCREEN_WIDTH, glut_SCREEN_HEIGHT,
glut_SCREEN_WIDTH_MM, glut_SCREEN_HEIGHT_MM,
glut_HAS_KEYBOARD,
glut_HAS_MOUSE, glut_NUM_MOUSE_BUTTONS,
glut_HAS_SPACEBALL, glut_NUM_SPACEBALL_BUTTONS,
glut_HAS_DIAL_AND_BUTTON_BOX, glut_NUM_DIALS, glut_NUM_BUTTON_BOX_BUTTONS,
glut_HAS_TABLET, glut_NUM_TABLET_BUTTONS,
glut_HAS_JOYSTICK, glut_JOYSTICK_BUTTONS, glut_JOYSTICK_POLL_RATE,
glut_JOYSTICK_AXES,
glut_VERSION, glut_WINDOW_BORDER_WIDTH, glut_WINDOW_HEADER_HEIGHT )
import Graphics.UI.GLUT.Overlay ( Layer(..) )
import Graphics.UI.GLUT.QueryUtils ( simpleGet, layerGet, deviceGet )
import Graphics.UI.GLUT.Extensions ( getProcAddressInternal )
rgba :: GettableStateVar Bool
rgba = makeGettableStateVar$ simpleGet i2b glut_WINDOW_RGBA
type BufferDepth = Int
rgbaBufferDepths ::
GettableStateVar (BufferDepth, BufferDepth, BufferDepth, BufferDepth)
rgbaBufferDepths = makeGettableStateVar $ do
r <- simpleGet fromIntegral glut_WINDOW_RED_SIZE
g <- simpleGet fromIntegral glut_WINDOW_GREEN_SIZE
b <- simpleGet fromIntegral glut_WINDOW_BLUE_SIZE
a <- simpleGet fromIntegral glut_WINDOW_ALPHA_SIZE
return (r, g, b, a)
colorBufferDepth :: GettableStateVar BufferDepth
colorBufferDepth =
makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_BUFFER_SIZE
doubleBuffered :: GettableStateVar Bool
doubleBuffered = makeGettableStateVar $ simpleGet i2b glut_WINDOW_DOUBLEBUFFER
stereo :: GettableStateVar Bool
stereo = makeGettableStateVar $ simpleGet i2b glut_WINDOW_STEREO
accumBufferDepths ::
GettableStateVar (BufferDepth, BufferDepth, BufferDepth, BufferDepth)
accumBufferDepths = makeGettableStateVar $ do
r <- simpleGet fromIntegral glut_WINDOW_ACCUM_RED_SIZE
g <- simpleGet fromIntegral glut_WINDOW_ACCUM_GREEN_SIZE
b <- simpleGet fromIntegral glut_WINDOW_ACCUM_BLUE_SIZE
a <- simpleGet fromIntegral glut_WINDOW_ACCUM_ALPHA_SIZE
return (r, g, b, a)
depthBufferDepth :: GettableStateVar BufferDepth
depthBufferDepth =
makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_DEPTH_SIZE
stencilBufferDepth :: GettableStateVar BufferDepth
stencilBufferDepth =
makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_STENCIL_SIZE
type SampleCount = Int
sampleCount :: GettableStateVar SampleCount
sampleCount =
makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_NUM_SAMPLES
formatID :: GettableStateVar Int
formatID = makeGettableStateVar $ simpleGet fromIntegral glut_WINDOW_FORMAT_ID
elapsedTime :: GettableStateVar Int
elapsedTime = makeGettableStateVar $ simpleGet fromIntegral glut_ELAPSED_TIME
damaged :: Layer -> GettableStateVar Bool
damaged l = makeGettableStateVar $ layerGet isDamaged (marshalDamagedLayer l)
where isDamaged d = d /= 0 && d /= 1
marshalDamagedLayer x = case x of
Normal -> glut_NORMAL_DAMAGED
Overlay -> glut_OVERLAY_DAMAGED
screenSize :: GettableStateVar Size
screenSize =
makeGettableStateVar $ do
wpx <- simpleGet fromIntegral glut_SCREEN_WIDTH
hpx <- simpleGet fromIntegral glut_SCREEN_HEIGHT
return $ Size wpx hpx
screenSizeMM :: GettableStateVar Size
screenSizeMM =
makeGettableStateVar $ do
wmm <- simpleGet fromIntegral glut_SCREEN_WIDTH_MM
hmm <- simpleGet fromIntegral glut_SCREEN_HEIGHT_MM
return $ Size wmm hmm
hasKeyboard :: GettableStateVar Bool
hasKeyboard = makeGettableStateVar $ deviceGet i2b glut_HAS_KEYBOARD
type ButtonCount = Int
numMouseButtons :: GettableStateVar (Maybe ButtonCount)
numMouseButtons =
getDeviceInfo glut_HAS_MOUSE $
deviceGet fromIntegral glut_NUM_MOUSE_BUTTONS
numSpaceballButtons :: GettableStateVar (Maybe ButtonCount)
numSpaceballButtons =
getDeviceInfo glut_HAS_SPACEBALL $
deviceGet fromIntegral glut_NUM_SPACEBALL_BUTTONS
type DialCount = Int
numDialsAndButtons :: GettableStateVar (Maybe (DialCount, ButtonCount))
numDialsAndButtons =
getDeviceInfo glut_HAS_DIAL_AND_BUTTON_BOX $ do
d <- deviceGet fromIntegral glut_NUM_DIALS
b <- deviceGet fromIntegral glut_NUM_BUTTON_BOX_BUTTONS
return (d, b)
numTabletButtons :: GettableStateVar (Maybe ButtonCount)
numTabletButtons =
getDeviceInfo glut_HAS_TABLET $
deviceGet fromIntegral glut_NUM_TABLET_BUTTONS
type AxisCount = Int
type PollRate = Int
joystickInfo :: GettableStateVar (Maybe (ButtonCount, PollRate, AxisCount))
joystickInfo =
getDeviceInfo glut_HAS_JOYSTICK $ do
b <- deviceGet fromIntegral glut_JOYSTICK_BUTTONS
a <- deviceGet fromIntegral glut_JOYSTICK_AXES
r <- deviceGet fromIntegral glut_JOYSTICK_POLL_RATE
return (b, a, r)
i2b :: CInt -> Bool
i2b = (/= 0)
getDeviceInfo :: GLenum -> IO a -> GettableStateVar (Maybe a)
getDeviceInfo dev act =
makeGettableStateVar $ do
hasDevice <- deviceGet i2b dev
if hasDevice then fmap Just act else return Nothing
glutVersion :: GettableStateVar String
glutVersion = makeGettableStateVar $ do
let isGLUT = isUnknown "glutSetOption"
isFreeglut = isUnknown "glutSetWindowStayOnTop"
isUnknown = fmap (== nullFunPtr) . getProcAddressInternal
showVersionPart x = shows (x `mod` 100)
showVersion v = showVersionPart (v `div` 10000) . showChar '.' .
showVersionPart (v `div` 100) . showChar '.' .
showVersionPart v
g <- isGLUT
if g
then return "GLUT 3.7"
else do f <- isFreeglut
v <- simpleGet id glut_VERSION
let prefix = if f then "freeglut" else "OpenGLUT"
return $ showString prefix . showChar ' ' . showVersion v $ ""
windowBorderWidth :: GettableStateVar Int
windowBorderWidth =
makeGettableStateVar (simpleGet fromIntegral glut_WINDOW_BORDER_WIDTH)
windowHeaderHeight :: GettableStateVar Int
windowHeaderHeight =
makeGettableStateVar (simpleGet fromIntegral glut_WINDOW_HEADER_HEIGHT)