module Graphics.UI.GLUT.Callbacks.Window (
DisplayCallback, displayCallback, overlayDisplayCallback,
ReshapeCallback, reshapeCallback,
Visibility(..), VisibilityCallback, visibilityCallback,
CloseCallback, closeCallback,
Key(..), SpecialKey(..), MouseButton(..), KeyState(..), Modifiers(..),
KeyboardMouseCallback, keyboardMouseCallback,
MotionCallback, motionCallback, passiveMotionCallback,
Crossing(..), CrossingCallback, crossingCallback,
SpaceballMotion, SpaceballRotation, ButtonIndex, SpaceballInput(..),
SpaceballCallback, spaceballCallback,
DialAndButtonBoxInput(..), DialIndex,
DialAndButtonBoxCallback, dialAndButtonBoxCallback,
TabletPosition(..), TabletInput(..), TabletCallback, tabletCallback,
JoystickButtons(..), JoystickPosition(..),
JoystickCallback, joystickCallback
) where
import Data.Bits ( Bits((.&.)) )
import Data.Char ( chr )
import Data.Maybe ( fromJust )
import Foreign.C.Types ( CInt, CUInt, CUChar )
import Graphics.Rendering.OpenGL.GL.CoordTrans ( Position(..), Size(..) )
import Graphics.Rendering.OpenGL.GL.StateVar (
SettableStateVar, makeSettableStateVar )
import Graphics.UI.GLUT.Callbacks.Registration ( CallbackType(..), setCallback )
import Graphics.UI.GLUT.Constants (
glut_NOT_VISIBLE, glut_VISIBLE,
glut_KEY_F1, glut_KEY_F2, glut_KEY_F3, glut_KEY_F4, glut_KEY_F5, glut_KEY_F6,
glut_KEY_F7, glut_KEY_F8, glut_KEY_F9, glut_KEY_F10, glut_KEY_F11,
glut_KEY_F12, glut_KEY_LEFT, glut_KEY_UP, glut_KEY_RIGHT, glut_KEY_DOWN,
glut_KEY_PAGE_UP, glut_KEY_PAGE_DOWN, glut_KEY_HOME, glut_KEY_END,
glut_KEY_INSERT,
glut_DOWN, glut_UP,
glut_ACTIVE_SHIFT, glut_ACTIVE_CTRL, glut_ACTIVE_ALT,
glut_LEFT, glut_ENTERED,
glut_JOYSTICK_BUTTON_A, glut_JOYSTICK_BUTTON_B,
glut_JOYSTICK_BUTTON_C, glut_JOYSTICK_BUTTON_D )
import Graphics.UI.GLUT.State ( PollRate )
import Graphics.UI.GLUT.Types ( MouseButton(..), unmarshalMouseButton )
import Graphics.UI.GLUT.Extensions
#include "HsGLUTExt.h"
type DisplayCallback = IO ()
displayCallback :: SettableStateVar DisplayCallback
displayCallback = makeSettableStateVar $
setCallback DisplayCB glutDisplayFunc makeDisplayCallback . Just
foreign import ccall "wrapper" makeDisplayCallback ::
DisplayCallback -> IO (FunPtr DisplayCallback)
foreign import CALLCONV unsafe "glutDisplayFunc" glutDisplayFunc ::
FunPtr DisplayCallback -> IO ()
overlayDisplayCallback :: SettableStateVar (Maybe DisplayCallback)
overlayDisplayCallback = makeSettableStateVar $
setCallback OverlayDisplayCB glutOverlayDisplayFunc makeDisplayCallback
foreign import CALLCONV unsafe "glutOverlayDisplayFunc" glutOverlayDisplayFunc
:: FunPtr DisplayCallback -> IO ()
type ReshapeCallback = Size -> IO ()
type ReshapeCallback' = CInt -> CInt -> IO ()
reshapeCallback :: SettableStateVar (Maybe ReshapeCallback)
reshapeCallback = makeSettableStateVar $
setCallback ReshapeCB glutReshapeFunc (makeReshapeCallback . unmarshal)
where unmarshal cb w h = cb (Size (fromIntegral w) (fromIntegral h))
foreign import ccall "wrapper" makeReshapeCallback ::
ReshapeCallback' -> IO (FunPtr ReshapeCallback')
foreign import CALLCONV unsafe "glutReshapeFunc" glutReshapeFunc ::
FunPtr ReshapeCallback' -> IO ()
data Visibility
= NotVisible
| Visible
deriving ( Eq, Ord, Show )
unmarshalVisibility :: CInt -> Visibility
unmarshalVisibility x
| x == glut_NOT_VISIBLE = NotVisible
| x == glut_VISIBLE = Visible
| otherwise = error ("unmarshalVisibility: illegal value " ++ show x)
type VisibilityCallback = Visibility -> IO ()
type VisibilityCallback' = CInt -> IO ()
visibilityCallback :: SettableStateVar (Maybe VisibilityCallback)
visibilityCallback = makeSettableStateVar $
setCallback VisibilityCB glutVisibilityFunc
(makeVisibilityCallback . unmarshal)
where unmarshal cb = cb . unmarshalVisibility
foreign import ccall "wrapper" makeVisibilityCallback ::
VisibilityCallback' -> IO (FunPtr VisibilityCallback')
foreign import CALLCONV unsafe "glutVisibilityFunc" glutVisibilityFunc ::
FunPtr VisibilityCallback' -> IO ()
type CloseCallback = IO ()
closeCallback :: SettableStateVar (Maybe CloseCallback)
closeCallback = makeSettableStateVar $
setCallback CloseCB glutCloseFunc makeCloseCallback
foreign import ccall "wrapper"
makeCloseCallback :: CloseCallback -> IO (FunPtr CloseCallback)
EXTENSION_ENTRY(unsafe,"freeglut",glutCloseFunc,FunPtr CloseCallback -> IO ())
type KeyboardCallback = Char -> Position -> IO ()
type KeyboardCallback' = CUChar -> CInt -> CInt -> IO ()
setKeyboardCallback :: Maybe KeyboardCallback -> IO ()
setKeyboardCallback =
setCallback KeyboardCB glutKeyboardFunc (makeKeyboardCallback . unmarshal)
where unmarshal cb c x y = cb (chr (fromIntegral c))
(Position (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeKeyboardCallback ::
KeyboardCallback' -> IO (FunPtr KeyboardCallback')
foreign import CALLCONV unsafe "glutKeyboardFunc" glutKeyboardFunc ::
FunPtr KeyboardCallback' -> IO ()
setKeyboardUpCallback :: Maybe KeyboardCallback -> IO ()
setKeyboardUpCallback =
setCallback KeyboardUpCB glutKeyboardUpFunc
(makeKeyboardCallback . unmarshal)
where unmarshal cb c x y = cb (chr (fromIntegral c))
(Position (fromIntegral x) (fromIntegral y))
foreign import CALLCONV unsafe "glutKeyboardUpFunc" glutKeyboardUpFunc ::
FunPtr KeyboardCallback' -> IO ()
data SpecialKey
= KeyF1
| KeyF2
| KeyF3
| KeyF4
| KeyF5
| KeyF6
| KeyF7
| KeyF8
| KeyF9
| KeyF10
| KeyF11
| KeyF12
| KeyLeft
| KeyUp
| KeyRight
| KeyDown
| KeyPageUp
| KeyPageDown
| KeyHome
| KeyEnd
| KeyInsert
deriving ( Eq, Ord, Show )
unmarshalSpecialKey :: CInt -> SpecialKey
unmarshalSpecialKey x
| x == glut_KEY_F1 = KeyF1
| x == glut_KEY_F2 = KeyF2
| x == glut_KEY_F3 = KeyF3
| x == glut_KEY_F4 = KeyF4
| x == glut_KEY_F5 = KeyF5
| x == glut_KEY_F6 = KeyF6
| x == glut_KEY_F7 = KeyF7
| x == glut_KEY_F8 = KeyF8
| x == glut_KEY_F9 = KeyF9
| x == glut_KEY_F10 = KeyF10
| x == glut_KEY_F11 = KeyF11
| x == glut_KEY_F12 = KeyF12
| x == glut_KEY_LEFT = KeyLeft
| x == glut_KEY_UP = KeyUp
| x == glut_KEY_RIGHT = KeyRight
| x == glut_KEY_DOWN = KeyDown
| x == glut_KEY_PAGE_UP = KeyPageUp
| x == glut_KEY_PAGE_DOWN = KeyPageDown
| x == glut_KEY_HOME = KeyHome
| x == glut_KEY_END = KeyEnd
| x == glut_KEY_INSERT = KeyInsert
| otherwise = error ("unmarshalSpecialKey: illegal value " ++ show x)
type SpecialCallback = SpecialKey -> Position -> IO ()
type SpecialCallback' = CInt -> CInt -> CInt -> IO ()
setSpecialCallback :: Maybe SpecialCallback -> IO ()
setSpecialCallback =
setCallback SpecialCB glutSpecialFunc (makeSpecialCallback . unmarshal)
where unmarshal cb k x y = cb (unmarshalSpecialKey k)
(Position (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeSpecialCallback ::
SpecialCallback' -> IO (FunPtr SpecialCallback')
foreign import CALLCONV unsafe "glutSpecialFunc" glutSpecialFunc ::
FunPtr SpecialCallback' -> IO ()
setSpecialUpCallback :: Maybe SpecialCallback -> IO ()
setSpecialUpCallback =
setCallback SpecialUpCB glutSpecialUpFunc (makeSpecialCallback . unmarshal)
where unmarshal cb k x y = cb (unmarshalSpecialKey k)
(Position (fromIntegral x) (fromIntegral y))
foreign import CALLCONV unsafe "glutSpecialUpFunc" glutSpecialUpFunc ::
FunPtr SpecialCallback' -> IO ()
data KeyState
= Down
| Up
deriving ( Eq, Ord, Show )
unmarshalKeyState :: CInt -> KeyState
unmarshalKeyState x
| x == glut_DOWN = Down
| x == glut_UP = Up
| otherwise = error ("unmarshalKeyState: illegal value " ++ show x)
type MouseCallback = MouseButton -> KeyState -> Position -> IO ()
type MouseCallback' = CInt -> CInt -> CInt -> CInt -> IO ()
setMouseCallback :: Maybe MouseCallback -> IO ()
setMouseCallback =
setCallback MouseCB glutMouseFunc (makeMouseCallback . unmarshal)
where unmarshal cb b s x y = cb (unmarshalMouseButton b)
(unmarshalKeyState s)
(Position (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeMouseCallback ::
MouseCallback' -> IO (FunPtr MouseCallback')
foreign import CALLCONV unsafe "glutMouseFunc" glutMouseFunc ::
FunPtr MouseCallback' -> IO ()
data Modifiers = Modifiers { shift, ctrl, alt :: KeyState }
deriving ( Eq, Ord, Show )
unmarshalModifiers :: CInt -> Modifiers
unmarshalModifiers m = Modifiers {
shift = if (m .&. glut_ACTIVE_SHIFT) /= 0 then Down else Up,
ctrl = if (m .&. glut_ACTIVE_CTRL ) /= 0 then Down else Up,
alt = if (m .&. glut_ACTIVE_ALT ) /= 0 then Down else Up }
getModifiers :: IO Modifiers
getModifiers = fmap unmarshalModifiers glutGetModifiers
foreign import CALLCONV unsafe "glutGetModifiers" glutGetModifiers :: IO CInt
data Key
= Char Char
| SpecialKey SpecialKey
| MouseButton MouseButton
deriving ( Eq, Ord, Show )
type KeyboardMouseCallback =
Key -> KeyState -> Modifiers -> Position -> IO ()
keyboardMouseCallback :: SettableStateVar (Maybe KeyboardMouseCallback)
keyboardMouseCallback = makeSettableStateVar setKeyboardMouseCallback
setKeyboardMouseCallback :: Maybe KeyboardMouseCallback -> IO ()
setKeyboardMouseCallback Nothing = do
setKeyboardCallback Nothing
setKeyboardUpCallback Nothing
setSpecialCallback Nothing
setSpecialUpCallback Nothing
setMouseCallback Nothing
setKeyboardMouseCallback (Just cb) = do
setKeyboardCallback (Just (\c p -> do m <- getModifiers
cb (Char c) Down m p))
setKeyboardUpCallback (Just (\c p -> do m <- getModifiers
cb (Char c) Up m p))
setSpecialCallback (Just (\s p -> do m <- getModifiers
cb (SpecialKey s) Down m p))
setSpecialUpCallback (Just (\s p -> do m <- getModifiers
cb (SpecialKey s) Up m p))
setMouseCallback (Just (\b s p -> do m <- getModifiers
cb (MouseButton b) s m p))
type MotionCallback = Position -> IO ()
type MotionCallback' = CInt -> CInt -> IO ()
motionCallback :: SettableStateVar (Maybe MotionCallback)
motionCallback = makeSettableStateVar $
setCallback MotionCB glutMotionFunc (makeMotionCallback . unmarshal)
where unmarshal cb x y = cb (Position (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeMotionCallback ::
MotionCallback' -> IO (FunPtr MotionCallback')
foreign import CALLCONV unsafe "glutMotionFunc" glutMotionFunc ::
FunPtr MotionCallback' -> IO ()
passiveMotionCallback :: SettableStateVar (Maybe MotionCallback)
passiveMotionCallback = makeSettableStateVar $
setCallback PassiveMotionCB glutPassiveMotionFunc
(makeMotionCallback . unmarshal)
where unmarshal cb x y = cb (Position (fromIntegral x) (fromIntegral y))
foreign import CALLCONV unsafe "glutPassiveMotionFunc" glutPassiveMotionFunc ::
FunPtr MotionCallback' -> IO ()
data Crossing
= WindowLeft
| WindowEntered
deriving ( Eq, Ord, Show )
unmarshalCrossing :: CInt -> Crossing
unmarshalCrossing x
| x == glut_LEFT = WindowLeft
| x == glut_ENTERED = WindowEntered
| otherwise = error ("unmarshalCrossing: illegal value " ++ show x)
type CrossingCallback = Crossing -> IO ()
type CrossingCallback' = CInt -> IO ()
crossingCallback :: SettableStateVar (Maybe CrossingCallback)
crossingCallback = makeSettableStateVar $
setCallback CrossingCB glutEntryFunc (makeCrossingCallback . unmarshal)
where unmarshal cb = cb . unmarshalCrossing
foreign import ccall "wrapper" makeCrossingCallback ::
CrossingCallback' -> IO (FunPtr CrossingCallback')
foreign import CALLCONV unsafe "glutEntryFunc" glutEntryFunc ::
FunPtr CrossingCallback' -> IO ()
type SpaceballMotion = Int
type SpaceballRotation = Int
type ButtonIndex = Int
data SpaceballInput
= SpaceballMotion SpaceballMotion SpaceballMotion SpaceballMotion
| SpaceballRotation SpaceballRotation SpaceballRotation SpaceballRotation
| SpaceballButton ButtonIndex KeyState
deriving ( Eq, Ord, Show )
type SpaceballCallback = SpaceballInput -> IO ()
spaceballCallback :: SettableStateVar (Maybe SpaceballCallback)
spaceballCallback = makeSettableStateVar setSpaceballCallback
setSpaceballCallback :: Maybe SpaceballCallback -> IO ()
setSpaceballCallback Nothing = do
setSpaceballMotionCallback Nothing
setSpaceballRotationCallback Nothing
setSpaceballButtonCallback Nothing
setSpaceballCallback (Just cb) = do
setSpaceballMotionCallback (Just (\x y z -> cb (SpaceballMotion x y z)))
setSpaceballRotationCallback (Just (\x y z -> cb (SpaceballRotation x y z)))
setSpaceballButtonCallback (Just (\b s -> cb (SpaceballButton b s)))
type SpaceballMotionCallback =
SpaceballMotion -> SpaceballMotion -> SpaceballMotion -> IO ()
setSpaceballMotionCallback :: Maybe SpaceballMotionCallback -> IO ()
setSpaceballMotionCallback =
setCallback SpaceballMotionCB glutSpaceballMotionFunc
(makeSpaceballMotionCallback . unmarshal)
where unmarshal cb x y z =
cb (fromIntegral x) (fromIntegral y) (fromIntegral z)
foreign import ccall "wrapper" makeSpaceballMotionCallback ::
SpaceballMotionCallback -> IO (FunPtr SpaceballMotionCallback)
foreign import CALLCONV unsafe "glutSpaceballMotionFunc" glutSpaceballMotionFunc
:: FunPtr SpaceballMotionCallback -> IO ()
type SpaceballRotationCallback =
SpaceballRotation -> SpaceballRotation -> SpaceballRotation -> IO ()
setSpaceballRotationCallback :: Maybe SpaceballRotationCallback -> IO ()
setSpaceballRotationCallback =
setCallback SpaceballRotateCB glutSpaceballRotateFunc
(makeSpaceballRotationCallback . unmarshal)
where unmarshal cb x y z =
cb (fromIntegral x) (fromIntegral y) (fromIntegral z)
foreign import ccall "wrapper" makeSpaceballRotationCallback ::
SpaceballRotationCallback -> IO (FunPtr SpaceballRotationCallback)
foreign import CALLCONV unsafe "glutSpaceballRotateFunc" glutSpaceballRotateFunc
:: FunPtr SpaceballRotationCallback -> IO ()
type SpaceballButtonCallback = ButtonIndex -> KeyState -> IO ()
type SpaceballButtonCallback' = CInt -> CInt -> IO ()
setSpaceballButtonCallback :: Maybe SpaceballButtonCallback -> IO ()
setSpaceballButtonCallback =
setCallback SpaceballButtonCB glutSpaceballButtonFunc
(makeSpaceballButtonCallback . unmarshal)
where unmarshal cb b s = cb (fromIntegral b) (unmarshalKeyState s)
foreign import ccall "wrapper" makeSpaceballButtonCallback ::
SpaceballButtonCallback' -> IO (FunPtr SpaceballButtonCallback')
foreign import CALLCONV unsafe "glutSpaceballButtonFunc"
glutSpaceballButtonFunc :: FunPtr SpaceballButtonCallback' -> IO ()
type DialIndex = Int
data DialAndButtonBoxInput
= DialAndButtonBoxButton ButtonIndex KeyState
| DialAndButtonBoxDial DialIndex Int
deriving ( Eq, Ord, Show )
type DialAndButtonBoxCallback = DialAndButtonBoxInput -> IO ()
dialAndButtonBoxCallback :: SettableStateVar (Maybe DialAndButtonBoxCallback)
dialAndButtonBoxCallback = makeSettableStateVar setDialAndButtonBoxCallback
setDialAndButtonBoxCallback :: Maybe DialAndButtonBoxCallback -> IO ()
setDialAndButtonBoxCallback Nothing = do
setButtonBoxCallback Nothing
setDialsCallback Nothing
setDialAndButtonBoxCallback (Just cb) = do
setButtonBoxCallback (Just (\b s -> cb (DialAndButtonBoxButton b s)))
setDialsCallback (Just (\d x -> cb (DialAndButtonBoxDial d x)))
type ButtonBoxCallback = ButtonIndex -> KeyState -> IO ()
type ButtonBoxCallback' = CInt -> CInt -> IO ()
setButtonBoxCallback :: Maybe ButtonBoxCallback -> IO ()
setButtonBoxCallback =
setCallback ButtonBoxCB glutButtonBoxFunc (makeButtonBoxFunc . unmarshal)
where unmarshal cb b s = cb (fromIntegral b) (unmarshalKeyState s)
foreign import ccall "wrapper" makeButtonBoxFunc ::
ButtonBoxCallback' -> IO (FunPtr ButtonBoxCallback')
foreign import CALLCONV unsafe "glutButtonBoxFunc" glutButtonBoxFunc ::
FunPtr ButtonBoxCallback' -> IO ()
type DialsCallback = DialIndex -> Int -> IO ()
type DialsCallback' = CInt -> CInt -> IO ()
setDialsCallback :: Maybe DialsCallback -> IO ()
setDialsCallback =
setCallback DialsCB glutDialsFunc (makeDialsFunc . unmarshal)
where unmarshal cb d x = cb (fromIntegral d) (fromIntegral x)
foreign import ccall "wrapper" makeDialsFunc ::
DialsCallback -> IO (FunPtr DialsCallback')
foreign import CALLCONV unsafe "glutDialsFunc" glutDialsFunc ::
FunPtr DialsCallback' -> IO ()
data TabletPosition = TabletPosition Int Int
deriving ( Eq, Ord, Show )
data TabletInput
= TabletMotion
| TabletButton ButtonIndex KeyState
deriving ( Eq, Ord, Show )
type TabletCallback = TabletInput -> TabletPosition -> IO ()
tabletCallback :: SettableStateVar (Maybe TabletCallback)
tabletCallback = makeSettableStateVar setTabletCallback
setTabletCallback :: Maybe TabletCallback -> IO ()
setTabletCallback Nothing = do
setTabletMotionCallback Nothing
setTabletButtonCallback Nothing
setTabletCallback (Just cb) = do
setTabletMotionCallback (Just (\p -> cb TabletMotion p))
setTabletButtonCallback (Just (\b s p -> cb (TabletButton b s) p))
type TabletMotionCallback = TabletPosition -> IO ()
type TabletMotionCallback' = CInt -> CInt -> IO ()
setTabletMotionCallback :: Maybe TabletMotionCallback -> IO ()
setTabletMotionCallback =
setCallback TabletMotionCB glutTabletMotionFunc
(makeTabletMotionFunc . unmarshal)
where unmarshal cb x y =
cb (TabletPosition (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeTabletMotionFunc ::
TabletMotionCallback' -> IO (FunPtr TabletMotionCallback')
foreign import CALLCONV unsafe "glutTabletMotionFunc" glutTabletMotionFunc ::
FunPtr TabletMotionCallback' -> IO ()
type TabletButtonCallback = ButtonIndex -> KeyState -> TabletPosition -> IO ()
type TabletButtonCallback' = CInt -> CInt -> CInt -> CInt -> IO ()
setTabletButtonCallback :: Maybe TabletButtonCallback -> IO ()
setTabletButtonCallback =
setCallback TabletButtonCB glutTabletButtonFunc
(makeTabletButtonFunc . unmarshal)
where unmarshal cb b s x y =
cb (fromIntegral b) (unmarshalKeyState s)
(TabletPosition (fromIntegral x) (fromIntegral y))
foreign import ccall "wrapper" makeTabletButtonFunc ::
TabletButtonCallback' -> IO (FunPtr TabletButtonCallback')
foreign import CALLCONV unsafe "glutTabletButtonFunc" glutTabletButtonFunc ::
FunPtr TabletButtonCallback' -> IO ()
data JoystickButtons = JoystickButtons {
joystickButtonA, joystickButtonB,
joystickButtonC, joystickButtonD :: KeyState }
deriving ( Eq, Ord, Show )
unmarshalJoystickButtons :: CUInt -> JoystickButtons
unmarshalJoystickButtons m = JoystickButtons {
joystickButtonA = if (m .&. glut_JOYSTICK_BUTTON_A) /= 0 then Down else Up,
joystickButtonB = if (m .&. glut_JOYSTICK_BUTTON_B) /= 0 then Down else Up,
joystickButtonC = if (m .&. glut_JOYSTICK_BUTTON_C) /= 0 then Down else Up,
joystickButtonD = if (m .&. glut_JOYSTICK_BUTTON_D) /= 0 then Down else Up }
data JoystickPosition = JoystickPosition Int Int Int
deriving ( Eq, Ord, Show )
type JoystickCallback = JoystickButtons -> JoystickPosition -> IO ()
type JoystickCallback' = CUInt -> CInt -> CInt -> CInt -> IO ()
joystickCallback :: SettableStateVar (Maybe (JoystickCallback, PollRate))
joystickCallback =
makeSettableStateVar $ \maybeCBAndRate ->
setCallback JoystickCB
(\f -> glutJoystickFunc f (fromIntegral (snd (fromJust maybeCBAndRate))))
(makeJoystickFunc . unmarshal)
(fmap fst maybeCBAndRate)
where unmarshal cb b x y z = cb (unmarshalJoystickButtons b)
(JoystickPosition (fromIntegral x)
(fromIntegral y)
(fromIntegral z))
foreign import ccall "wrapper" makeJoystickFunc ::
JoystickCallback' -> IO (FunPtr JoystickCallback')
foreign import CALLCONV unsafe "glutJoystickFunc" glutJoystickFunc ::
FunPtr JoystickCallback' -> CInt -> IO ()