---------------------------------------------------------------------- -- | -- Module : Examples.Applicative -- Copyright : (c) Conal Elliott 2007 -- License : BSD3 -- -- Maintainer : conal@conal.net -- Stability : experimental -- Portability : portable -- -- Applicative-style Phooey examples. Use 'runUI' ---------------------------------------------------------------------- module Examples.Applicative where import Control.Applicative import Data.Monoid import System.Time -- TypeCompose import Data.Title -- reactive import Data.Reactive -- phooey import Graphics.UI.Phooey.Applicative h :: UI String h = pure "Hello World!" sl0 :: IWidget Int sl0 = islider (0,10) uia,uib :: UI Action uia = stringDisplay <*> h uib = showDisplay <*> sl0 3 ui1 :: UI Action ui1 = title "Shopping List" $ fruit <**> total apples, bananas, fruit :: UI Int apples = title "apples" (sl0 3) bananas = title "bananas" (sl0 7) fruit = liftA2 (+) apples bananas -- With Num overloading, we could say -- fruit = apples + bananas total :: Num a => OWidget a total = title "total" showDisplay sqrt1 :: UI Action sqrt1 = (sqrt <$> i) <**> o where i = title "x" $ fslider (0,10) (3 :: Float) o = title "square root" $ fsliderDisplay (0,4) calendarTime :: Double -> UI CalendarTime calendarTime secs = timedPoll secs (getClockTime >>= toCalendarTime) clock :: UI Action clock = stringDisplay <*> (calendarTimeToString <$> calendarTime 1)