module Main where import Graphics.SceneGraph import Graphics.SceneGraph.Reactive import Control.Concurrent.MVar import Control.Monad.State import Control.Applicative hiding ( (<*>) ) import Control.Concurrent (yield, forkIO, killThread, threadDelay, ThreadId,forkOS) import Data.Reactive import Data.IORef import Data.Monoid import Calc calc = runSceneReactive calculator sceneButtonReactive -- -- To get at the string to display we fmap register to the calculator -- sceneButtonReactive :: SGM (Event Action) sceneButtonReactive = do snk <- getNodeByLabel "txt" >>= mkText ce <- calcEvent return $ snk <$> (fmap register ce ) -- Build a Calculator event. Build up the button events and -- append these events together. calcEvent :: SGM (Event Calculator) calcEvent = do btnList <- mapM mkCalcBtn ["0","1","2","3","4","5","6","7","8","9","c", "+","=" ] return $ scanlE applyCalc newCalculator $ foldr mappend mempty btnList -- Turn passive button in the scene graph into an active one that -- provides an event that returns 'lbl' mkCalcBtn :: [Char] -> SGM (Event String) mkCalcBtn lbl = do ev <- getNodeByLabel ("btn" ++ lbl) >>= mkButton return $ fmap (const lbl) ev