-- | An interactive scene graph library for Cairo -- -- [@Author@] Jeff Heard -- -- [@Copyright@] © 2008 Renaissance Computing Institute -- module Graphics.Rendering.Thingie.Interactive where import Graphics.Rendering.Thingie.Primitives import Graphics.Rendering.Thingie.Cairo import Graphics.Rendering.Thingie.UIState import qualified Graphics.UI.Gtk.Cairo as Gtk import qualified Graphics.Rendering.Cairo as Cairo import qualified Graphics.UI.Gtk as Gtk import Data.List import Data.Maybe import Control.Monad import Control.Concurrent.MVar -- | A scene element. This is the basic building block of your interactive app. data SceneElement a = StaticElement Object Rect2D -- ^ An unreactive element in the scene. Not modified by program state. | BoundedElement (a -> Object) Rect2D -- ^ A reactive, but bounded element in the scene. The element reacts to a UIState instance, but is confined within a particular rectangle. | UnboundedElement (a -> Object) -- ^ An unbounded reactive element in the scene. The element reacts to a UIState instance, but can go anywhere in the scene. | ElementGroup [SceneElement a] -- ^ A group of scene elements. -- | The scene itself type Scene a = [SceneElement a] -- | Applies the current UIState instance to a single scene element, returning an Object -- FIXME: Should do bounds checking. renderSceneElement :: UIState a => a -> SceneElement a -> Object renderSceneElement _ (StaticElement obj _) = obj renderSceneElement uistate (BoundedElement obj _) = obj uistate renderSceneElement uistate (UnboundedElement obj) = obj uistate renderSceneElement uistate (ElementGroup elts) = Group . map (renderSceneElement uistate) $ elts -- | @renderScene state scene applies the current UIState to the entire scene renderScene :: UIState a => a -> Scene a -> Object renderScene state = Group . map (renderSceneElement state) -- | Gets the keyboard state from Gtk and changes the UIState. You do not need -- to call this in your own code keyboardHandler :: UIState a => MVar a -> Scene a ->Gtk.Event -> IO Bool keyboardHandler uistate_mvar scene event = do let k = case Gtk.eventKeyName event of "Insert" -> Insert "Delete" -> Delete "Enter" -> Enter "F1" -> PF1 "F2" -> PF2 "F3" -> PF3 "F4" -> PF4 "F5" -> PF5 "F6" -> PF6 "F7" -> PF7 "F8" -> PF8 "F9" -> PF9 "F10" -> PF10 "F11" -> PF11 "F12" -> PF12 "Home" -> Home "End" -> End "PageUp" -> PgUp "PageDown" -> PgDown [x] -> Character x _ -> Character '\0' modifyMVar_ uistate_mvar $ return . setKey k withMVar uistate_mvar $ \s -> do dwin <- Gtk.widgetGetDrawWindow . fromJust . drawing $ s Gtk.drawWindowInvalidateRect dwin (Gtk.Rectangle 0 0 (round . sizeX $ s) (round . sizeY $ s)) False return False -- | Gets the mouse position and changes the UIState to reflect it. YOu do not need this in your own code. mouseMotionHandler :: UIState a => MVar a -> Gtk.Event -> IO Bool mouseMotionHandler uistate_mvar event = do state <- takeMVar uistate_mvar putMVar uistate_mvar $ setMousePosition (Point2D (Gtk.eventX event) (Gtk.eventY event)) state dwin <- Gtk.widgetGetDrawWindow . fromJust . drawing $ state Gtk.drawWindowGetPointer dwin Gtk.drawWindowInvalidateRect dwin (Gtk.Rectangle 0 0 (round . sizeX $ state) (round . sizeY $ state)) False return False -- | Gets the mouse button state and changes the UIState to reflect it. You do not need this in your own code. mouseButtonHandler :: UIState a => MVar a -> Scene a -> Gtk.Event -> IO Bool mouseButtonHandler uistate_mvar scene event = do let x = Gtk.eventX event y = Gtk.eventY event button = Gtk.eventButton event modifiers = Gtk.eventModifier event shift = elem Gtk.Shift modifiers alt = elem Gtk.Alt modifiers ctrl = elem Gtk.Control modifiers modifyMVar_ uistate_mvar $ return . setMousePosition (Point2D x y) . setKeyShift shift . setKeyAlt alt . setKeyCtrl ctrl . (case button of Gtk.LeftButton -> setMouseLeftButtonDown True . setMouseRightButtonDown False . setMouseMiddleButtonDown False . setMouseWheel 0 Gtk.RightButton -> setMouseLeftButtonDown False . setMouseRightButtonDown True . setMouseMiddleButtonDown False . setMouseWheel 0 Gtk.MiddleButton -> setMouseLeftButtonDown False . setMouseRightButtonDown False . setMouseRightButtonDown True . setMouseWheel 0) withMVar uistate_mvar $ \s -> do dwin <- Gtk.widgetGetDrawWindow . fromJust . drawing $ s Gtk.drawWindowInvalidateRect dwin (Gtk.Rectangle 0 0 (round . sizeX $ s) (round . sizeY $ s)) False return True -- | Window resize handler. Changes the UIState to reflect the new sizing. You do not need this in your own code. resize state scene event = do let sizex = Gtk.eventWidth event sizey = Gtk.eventHeight event modifyMVar_ state $ return . setSizeX (fromIntegral sizex) . setSizeY (fromIntegral sizey) withMVar state $ \s -> do dwin <- Gtk.widgetGetDrawWindow . fromJust . drawing $ s Gtk.drawWindowInvalidateRect dwin (Gtk.Rectangle 0 0 sizex sizey) False return False -- | Render function. All Cairo is called through here. You do not need to call this in your own code. renderer :: UIState a => MVar a -> Scene a -> IO () renderer state scene = withMVar state $ \st -> do dwin <- Gtk.widgetGetDrawWindow . fromJust . drawing $ st Gtk.renderWithDrawable dwin $ (renderObject . renderScene st $ scene) -- | A lowish level funtion for creating a GUI. Does not set the size of the -- window or expose any windows. guiInit :: UIState a => MVar a -- ^ The current UIState -> Scene a -- ^ The scene graph to render -> String -- ^ The name of the window -> Bool -- ^ Whether or not to make this GUI motion sensitive -> IO Gtk.Window -- ^ Returns the window that was created guiInit state scene name motionSensitive = do Gtk.unsafeInitGUIForThreadedRTS window <- Gtk.windowNew canvas <- Gtk.drawingAreaNew Gtk.windowSetTitle window name Gtk.containerAdd window canvas modifyMVar_ state $ return . setDrawing (Just . Gtk.castToWidget $ canvas) Gtk.onExpose canvas $ \evt -> renderer state scene >> return True Gtk.onConfigure window $ resize state scene Gtk.onButtonPress canvas $ mouseButtonHandler state scene Gtk.onKeyPress window $ keyboardHandler state scene when motionSensitive $ (Gtk.onMotionNotify canvas True $ mouseMotionHandler state) >> return () return window -- | A higher level function for creating a GUI. Does not set the size of the -- window or expose any windows, but does kill the app if this window is -- closed guiConstruct :: UIState a => a -- ^ The default UIState -> Scene a -- ^ The scene to render -> String -- ^ The name of the scene -> Bool -- ^ Whether or not this GUI is motion sensitive -> IO Gtk.Window guiConstruct state scene name motionSensitive = do mvar <- newMVar state window <- guiInit mvar scene name motionSensitive Gtk.onDestroy window Gtk.mainQuit return window -- | A high level function for creating a GUI. Just specify a default -- state, the name of the scene, and the scene, and you get an 800 by -- 600 motion insensitive GUI. simpleGui :: UIState a => a -> Scene a -> String -> IO () simpleGui state scene name = do win <- guiConstruct state scene name False Gtk.windowSetDefaultSize win 800 600 Gtk.widgetShowAll win Gtk.mainGUI -- | A high level function for creating a GUI. Just specify the default -- state, the name of the scene, and the scene, and you get an 800 by -- 600 motion sensitive GUI simpleMotionSensitiveGui state scene name = do win <- guiConstruct state scene name True Gtk.windowSetDefaultSize win 800 600 Gtk.widgetShowAll win Gtk.mainGUI