{-# LANGUAGE FlexibleContexts #-} {-# OPTIONS -fno-warn-orphans #-} module Graphics.UI.AF.WxForm.WxMaybe () where import Graphics.UI.AF.WxForm.WxFormImplementation import Maybe import Char import Control.Monad(liftM) import qualified Graphics.UI.AF.WxForm.EditorComponent as EC import qualified Graphics.UI.AF.General as AF import Graphics.UI.AF.WxForm.GenericEC instance (ECCreator a, Show a, AF.GInstanceCreator a) => ECCreator (Maybe a) where makeEC maybeX = case (maybeX, AF.createInstance) of (Just x, _) -> makeMaybe x maybeX (_, Just x) -> makeMaybe x maybeX _ -> makeGUIlessEC msg maybeX where msg = "Maybe's GUI could not be made as the subtype did not have a GUI." makeMaybe :: (Show (Maybe a), ECCreator a) => a -> MakeEC (Maybe a) makeMaybe subX x = layoutAs (reverseGuis singleRow) $ AF.builderToCom $ do val <- AF.builderCom subX let lbl = case labelString (guiLabel val) of "" -> "Has ..." (l:ls) -> "Has " ++ [toLower l] ++ ls justVal <- AF.addCom $ AF.label lbl $ AF.mkCom (isJust x) AF.enabledWhen justVal (== True) val liftM (AF.mapValue oldToNew newToOld) $ merge (justVal, val) where oldToNew (True, y) = Just y oldToNew (False, _) = Nothing newToOld _ (Just y) = (True, y) newToOld (_, y) Nothing = (False, y)