{-# LANGUAGE MultiParamTypeClasses, TypeSynonymInstances #-} {-# OPTIONS -Wall #-} module IntEntry where import Graphics.UI.WX import Graphics.UI.WxGeneric.Composite type IntEntry = Composite (Inherit (TextCtrl ())) -- | Entry for integers intEntry :: Window w -> [Prop IntEntry] -> IO IntEntry intEntry = compose $ \p -> do intEn <- textEntry p [ processEnter := True , on anyKey := handleInput , text := "0" ] {- set intEn [ on mouse := \evt -> do evtHandler <- get p (on mouse) evtHandler evt ] -} return (widget intEn, Inherit intEn) where handleInput (KeyChar c) = do if c `elem` ['0'..'9'] then propagateEvent else return () handleInput _ = propagateEvent {- Valued integer entry type IntEntry = Composite () (IO Int, Int -> IO ()) -- | Entry for integers intEntry :: Window w -> [Prop IntEntry] -> IO IntEntry intEntry = compose $ \p -> do intEn <- textEntry p [ processEnter := True , on anyKey := handleInput , text := "0" ] let getter = do val <- get intEn text readIO val setter x = set intEn [ text := show x ] return (widget intEn, (), (getter, setter)) where handleInput (KeyChar c) = do if c `elem` ['0'..'9'] then propagateEvent else return () handleInput _ = propagateEvent instance ValuedWidget Int IntEntry where widgetValue = newAttr "Int attribute" getter setter where getter composite = fst (pickUser composite) setter composite = snd (pickUser composite) -}