module Graphics.UI.Gtk.Toy
( KeyInfo, KeyTable, MouseEvent, KeyEvent, InputState(..)
, Interactive(..), GtkInteractive(..)
, runToy, quitToy
, keyInfo, keyHeld, mouseHeld
, simpleTick, simpleDisplay, simpleMouse, simpleKeyboard
, quitKeyboard
) where
import Control.Monad (when)
import Data.IORef
import qualified Data.Map as M
import qualified Graphics.UI.Gtk as G
import qualified Graphics.UI.Gtk.Gdk.Events as E
type KeyInfo = (Bool, Int, [G.Modifier])
type KeyTable = M.Map String KeyInfo
data InputState = InputState
{ mousePos :: (Double, Double)
, keyTable :: KeyTable
}
type KeyEvent = (Bool, Either String Char)
type MouseEvent = Maybe (Bool, Int)
class Interactive a where
tick :: InputState -> a -> IO (a, Bool)
mouse :: MouseEvent -> InputState -> a -> IO a
keyboard :: KeyEvent -> InputState -> a -> IO a
tick _ = return . (, False)
mouse _ _ = return
keyboard _ _ = return
class Interactive a => GtkInteractive a where
display :: G.DrawWindow -> InputState -> a -> IO a
display _ _ = return
keyInfo :: String -> InputState -> Maybe KeyInfo
keyInfo name = M.lookup name . keyTable
keyHeld :: String -> InputState -> Bool
keyHeld name (keyInfo name -> Just (True, _, _)) = True
keyHeld _ _ = False
eitherHeld :: String -> InputState -> Bool
eitherHeld key inp = (keyHeld (key ++ "_L") inp || keyHeld (key ++ "_R") inp)
mouseHeld :: Int -> InputState -> Bool
mouseHeld ix = keyHeld ("Mouse" ++ show ix)
simpleTick :: (a -> a)
-> InputState -> a -> IO (a, Bool)
simpleTick f _ = return . (, True) . f
simpleDisplay :: (G.DrawWindow -> a -> a)
-> G.DrawWindow -> InputState -> a -> IO a
simpleDisplay f dw _ = return . f dw
simpleMouse :: (MouseEvent -> (Double, Double) -> a -> a)
-> (MouseEvent -> InputState -> a -> IO a)
simpleMouse f c inp = return . f c (mousePos inp)
simpleMouseClick :: ((Bool, Int) -> (Double, Double) -> a -> a)
-> (MouseEvent -> InputState -> a -> IO a)
simpleMouseClick f (Just c) inp = return . f c (mousePos inp)
simpleMouseClick _ _ _ = return
simpleMousePos :: ((Double, Double) -> a -> a)
-> (MouseEvent -> InputState -> a -> IO a)
simpleMousePos f _ inp = return . f (mousePos inp)
simpleKeyboard :: (KeyEvent -> a -> a)
-> (KeyEvent -> InputState -> a -> IO a)
simpleKeyboard f e _ = return . f e
quitKeyboard :: KeyEvent -> InputState -> a -> IO a
quitKeyboard (True, (Left "Escape")) _ x = quitToy >> return x
quitKeyboard _ _ x = return x
quitToy :: IO ()
quitToy = G.mainQuit
runToy :: GtkInteractive a => a -> IO ()
runToy toy = do
G.initGUI
window <- G.windowNew
canvas <- G.drawingAreaNew
state <- newIORef (InputState (0, 0) M.empty, toy)
let doRedraw = G.widgetQueueDraw canvas >> return True
G.windowSetDefaultSize window 640 480
G.onKeyPress window $ (>> doRedraw) . handleKey state
G.onKeyRelease window $ (>> doRedraw) . handleKey state
G.onMotionNotify window True $ (>> doRedraw) . handleMotion state
G.onButtonPress window $ (>> doRedraw) . handleButton state
G.onButtonRelease window $ (>> doRedraw) . handleButton state
G.onExposeRect canvas $ \(G.Rectangle x y w h) -> do
let r = ((x, y), (x + w, y + h))
dw <- G.widgetGetDrawWindow canvas
sz <- G.widgetGetSize canvas
(inp, x) <- readIORef state
x' <- display dw inp x
writeIORef state (inp, x')
G.set window $ [G.containerChild G.:= canvas]
G.widgetShowAll window
let tickHandler = do
st@(inp, _) <- readIORef state
(state', redraw) <- uncurry tick st
when redraw (doRedraw >> return ())
writeIORef state (inp, state')
return True
G.timeoutAddFull tickHandler G.priorityDefaultIdle 30
G.mainGUI
where
handleKey :: Interactive a => IORef (InputState, a) -> E.Event -> IO ()
handleKey st ev = do
(InputState p m, x) <- readIORef st
let inp' = InputState p (M.insert name (pres, time, mods) m)
x' <- keyboard (pres, maybe (Left name) Right char) inp' x
writeIORef st (inp', x')
where
name = E.eventKeyName ev
char = E.eventKeyChar ev
time = fromIntegral $ E.eventTime ev
mods = E.eventModifier ev
pres = not $ E.eventRelease ev
handleMotion :: Interactive a => IORef (InputState, a) -> E.Event -> IO ()
handleMotion st ev = do
(InputState p m, x) <- readIORef st
let inp' = InputState pos m
x' <- mouse Nothing inp' x
writeIORef st (inp', x')
where
pos = (E.eventX ev, E.eventY ev)
handleButton :: Interactive a => IORef (InputState, a) -> E.Event -> IO ()
handleButton st ev = do
when (click == E.SingleClick || click == E.ReleaseClick) $ do
(InputState p m, x) <- readIORef st
let m' = M.insert ("Mouse" ++ show but) (pressed, time, mods) m
inp' = InputState pos m'
x' <- mouse (Just (pressed, but)) inp' x
writeIORef st (inp', x')
where
pos = (E.eventX ev, E.eventY ev)
time = fromIntegral $ E.eventTime ev
mods = E.eventModifier ev
click = E.eventClick ev
pressed = click /= E.ReleaseClick
but = case E.eventButton ev of
E.LeftButton -> 0
E.RightButton -> 1
E.MiddleButton -> 2
E.OtherButton ix -> ix