module Graphics.UI.Sifflet.Callback
(
CBMgr, CBMgrAction, CBMgrCmd(..), mkCBMgr
, MenuSpec(..), MenuItemSpec(..), MenuItemAction
, createMenuBar, addMenu, createMenu, createMenuItem
, modifyIORefIO
)
where
import Data.IORef
import Graphics.UI.Gtk
import Graphics.UI.Sifflet.Types
type CBMgr = CBMgrCmd -> IO ()
type CBMgrAction = IORef VPUI -> IO ()
data CBMgrCmd
=
OnWindowConfigure Window (IORef VPUI -> EventM EConfigure Bool)
| OnWindowDestroy Window CBMgrAction
| AfterWindowKeyPress Window (IORef VPUI -> EventM EKey Bool)
| OnLayoutExpose Layout (IORef VPUI -> EventM EExpose Bool)
| OnLayoutMouseMove Layout (IORef VPUI -> EventM EMotion Bool)
| OnLayoutButtonPress Layout (IORef VPUI -> EventM EButton Bool)
| OnLayoutButtonRelease Layout (IORef VPUI -> EventM EButton Bool)
| OnMenuItemActivateLeaf MenuItem (VPUI -> IO VPUI)
| OnEntryActivate Entry CBMgrAction
| AfterButtonClicked Button CBMgrAction
| WithUIRef CBMgrAction
| UMTest
mkCBMgr :: IORef VPUI -> CBMgr
mkCBMgr uiref cmd =
case cmd of
OnWindowConfigure window action ->
on window configureEvent (action uiref) >> return ()
OnWindowDestroy window action ->
onDestroy window (action uiref) >> return ()
AfterWindowKeyPress window action ->
after window keyPressEvent (action uiref) >> return ()
OnLayoutExpose layout action ->
on layout exposeEvent (action uiref) >> return ()
OnLayoutMouseMove layout action ->
on layout motionNotifyEvent (action uiref) >> return ()
OnLayoutButtonPress layout action ->
on layout buttonPressEvent (action uiref) >> return ()
OnLayoutButtonRelease layout action ->
on layout buttonReleaseEvent (action uiref) >> return ()
OnMenuItemActivateLeaf menuItem action ->
onActivateLeaf menuItem (modifyIORefIO action uiref) >> return ()
OnEntryActivate entry action ->
onEntryActivate entry (action uiref) >> return ()
AfterButtonClicked button action ->
afterClicked button (action uiref) >> return ()
WithUIRef action -> action uiref
UMTest ->
putStrLn "UMTest"
data MenuSpec = MenuSpec String [MenuItemSpec]
data MenuItemSpec = MenuItem String MenuItemAction
| SubMenu MenuSpec
type MenuItemAction = VPUI -> IO VPUI
createMenuBar :: [MenuSpec] -> CBMgr -> IO MenuBar
createMenuBar menuSpecs cbmgr = do
bar <- menuBarNew
mapM_ (addMenu bar cbmgr) menuSpecs
return bar
addMenu :: MenuBar -> CBMgr -> MenuSpec -> IO ()
addMenu mbar cbmgr mspec@(MenuSpec name _itemSpecs) = do
menuHead <- menuItemNewWithLabel name
menuShellAppend mbar menuHead
menuItemSetRightJustified menuHead (name == "Help")
menu <- createMenu mspec cbmgr
menuItemSetSubmenu menuHead menu
createMenu :: MenuSpec -> CBMgr -> IO Menu
createMenu (MenuSpec _name itemSpecs) cbmgr = do
menu <- menuNew
mapM_ (createMenuItem menu cbmgr) itemSpecs
return menu
createMenuItem :: Menu -> CBMgr -> MenuItemSpec -> IO ()
createMenuItem menu cbmgr mispec =
case mispec of
MenuItem label action ->
do
{
item <- menuItemNewWithLabel label
; cbmgr (OnMenuItemActivateLeaf item action)
; menuShellAppend menu item
}
SubMenu subspec@(MenuSpec label _itemSpecs) ->
do
{
item <- menuItemNewWithLabel label
; submenu <- createMenu subspec cbmgr
; menuItemSetSubmenu item submenu
; menuShellAppend menu item
}
modifyIORefIO :: (a -> IO a) -> IORef a -> IO ()
modifyIORefIO updateIO ref = readIORef ref >>= updateIO >>= writeIORef ref