{-# LANGUAGE FlexibleContexts, FlexibleInstances , MultiParamTypeClasses, TemplateHaskell, UndecidableInstances #-} {- This example is showing how to handle recursive updates. We do this by making two exchange rate calculators. The first is recursive, the second is not. See RecursiveObserver monad (included with AutoForms) for explanation of recursive udpates in this context. -} module RecursiveUpdates where import Graphics.UI.AF.WxFormAll euroToDollarRate :: Float euroToDollarRate = 1.4414 main = startWx "Recursive Updates" $ do addCom $ exchangeRateCalculater "Recursive" setValue addCom $ exchangeRateCalculater "Non-recursive" nonRecursiveSetValue exchangeRateCalculater :: String -> (ComH Float -> Float -> WxAct ()) -> EC Float exchangeRateCalculater label' updateFun = label label' $ builderToCom $ do euros <- addCom $ label "Euros" $ mkCom 100 dollars <- addCom $ label "Dollars" $ mkCom (100 * euroToDollarRate) addListener (do euros' <- getValue euros updateFun dollars (euros' * euroToDollarRate) ) euros addListener (do dollars' <- getValue dollars updateFun euros (dollars' / euroToDollarRate) ) dollars return euros