{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses , TemplateHaskell, UndecidableInstances #-} module Alarm where import Graphics.UI.WxGeneric import Graphics.UI.SybWidget.MySYB import Graphics.UI.WX import Graphics.UI.WXCore data Minutes = Minutes Int deriving (Show, Eq) data Alarm = Alarm { name :: String , timeOfDay :: Minutes } deriving (Show, Eq) $(derive [''Minutes,''Alarm]) instance WxGen Alarm instance WxGen Minutes main :: IO () main = start $ do f <- frame [ text := "Alarm Example" ] p <- panel f [] en <- genericWidget p (Alarm "My alarm" $ Minutes 117) b <- button p [ text := "&Print alarm" , on command := get en widgetValue >>= print ] set f [ layout := container p $ row 10 [ widget en, widget b ] ]