module Main where import Graphics.UI.Gtk import Graphics.UI.Gtk.Gdk.EventM import Graphics.Rendering.Cairo import Graphics.UI.Gtk.Layout.Rpn import Data.Monoid title :: String -> [AttrOp Window] title s = [windowTitle := s] pressed :: Signal Widget (EventM EButton Bool) pressed = buttonPressEvent main = do initGUI -- Create a new operator ('line') that takes a label -- ('cLBL') and a button ('cBTNL') and pack then ('pBPED') -- in a horizontal box ('cHBX'). let line s = mconcat [ cLBL (Just $ s ++ ":"), cBTNL s, cHBX True 0, pBPED, pBPED] -- Create a new operator ('column') that packs many 'line' -- in a vertical box ('cVBX'). let column = mconcat $ [ line "One Button", line "Another Button", line "Yet Another Button", line "Last Button", cVBX True 0] ++ replicate 4 pBPED -- Take two copies of 'column' and add ('pNAP') then -- to a notebook ('cNBK'). Then create a stock button -- ('cBTNSTK') and attach a action to an event ('tON'). Then -- join the notebook and that button in a vertical box. -- Insert everything in a main window ('cWND, pCA'), and -- finally make everything into widgets ('widgetsFromRpn'). [mainWindow] <- widgetsFromRpn $ mconcat $ [ column, column, cNBK, pNAP "First Page", pNAP "Second Page", cBTNSTK stockQuit, tON pressed (liftIO mainQuit >> return True), cVBX False 0, pBPE PackNatural 0, pBPED, cWND, pCA, tSET (title "Layout.RPN Example")] widgetShowAll mainWindow mainGUI