module Graphics.UI.Sifflet.GtkUtil
(suppressScimBridge
, showChoicesDialog, defaultDialogPosition
, runDialogM, runDialogS
, showInputErrorMessage, showErrorMessage
, showInfoMessage
, showMessage
, EntryDialog, Reader
, createEntryDialog, runEntryDialog
, addEntryWithLabel
)
where
import Control.Monad
#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
import System.Posix.Env
#endif
import Graphics.UI.Sifflet.LittleGtk
import Language.Sifflet.Util
suppressScimBridge :: IO ()
suppressScimBridge =
#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
return ()
#else
putEnv "GTK_IM_MODULE=gtk-im-context-simple"
#endif
showChoicesDialog :: String -> String -> [String] -> [IO a] -> IO a -> IO a
showChoicesDialog title message options actions cancelAction = do
dialog <- dialogNew
windowSetTitle dialog title
widgetSetName dialog ("Sifflet-" ++ title)
vbox <- dialogGetUpper dialog
label <- labelNew (Just message)
boxPackStartDefaults vbox label
widgetShowAll vbox
let allActions = actions ++ [cancelAction]
allOptions = options ++ ["Cancel"]
indexOptions = zip [1..] allOptions
addButton (i, option) =
dialogAddButton dialog option (ResponseUser i)
forM_ indexOptions addButton
dialogGetActionArea dialog >>= widgetShowAll
response <- dialogRun dialog
widgetDestroy dialog
case response of
ResponseUser i ->
let j = i 1
in if j >= 0 && j < length allActions
then allActions !! j
else errcats ["showChoicesDialog: response index",
show j, "is out of range for actions"]
_ -> cancelAction
createDialog :: String -> (VBox -> IO a) -> IO (Dialog, a)
createDialog title addContent = do
dialog <- dialogNew
windowSetTitle dialog title
widgetSetName dialog ("Sifflet-" ++ title)
vbox <- dialogGetUpper dialog
content <- addContent vbox
_ <- dialogAddButton dialog "OK" ResponseOk
_ <- dialogAddButton dialog "Cancel" ResponseCancel
dialogSetDefaultResponse dialog ResponseOk
return (dialog, content)
defaultDialogPosition :: WindowPosition
defaultDialogPosition = WinPosMouse
runDialogS :: Dialog -> a -> (a -> IO (SuccFail b)) -> IO (Maybe b)
runDialogS dialog inputs processInputs =
runDialogHelper dialog inputs processInputs True
runDialogM :: Dialog -> a -> (a -> IO (Maybe b)) -> IO (Maybe b)
runDialogM dialog inputs processInputs =
let process' inputs' = do
result <- processInputs inputs'
case result of
Nothing -> return $ Fail "_Nothing_"
Just value -> return $ Succ value
in runDialogHelper dialog inputs process' False
runDialogHelper :: Dialog -> a -> (a -> IO (SuccFail b)) -> Bool -> IO (Maybe b)
runDialogHelper dialog inputs processInputs retryOnError = do
windowSetPosition dialog defaultDialogPosition
widgetShowAll dialog
windowPresent dialog
let run = do
respId <- dialogRun dialog
case respId of
ResponseOk ->
do
result <- processInputs inputs
case result of
Fail msg ->
if retryOnError
then do
showErrorMessage msg
run
else finish Nothing
Succ value -> finish (Just value)
_ -> finish Nothing
finish result = do
widgetDestroy dialog
return result
run
showInputErrorMessage :: String -> IO ()
showInputErrorMessage message =
showErrorMessage ("Input Error:\n" ++ message)
showErrorMessage :: String -> IO ()
showErrorMessage = showMessage (Just "Error") MessageError ButtonsClose
showInfoMessage :: String -> String -> IO ()
showInfoMessage title = showMessage (Just title) MessageInfo ButtonsClose
showMessage :: Maybe String -> MessageType -> ButtonsType -> String -> IO ()
showMessage mtitle messagetype buttonstype message = do
{
msgDialog <-
messageDialogNew
Nothing
[]
messagetype
buttonstype
message
; case mtitle of
Nothing -> widgetSetName msgDialog "Sifflet-dialog"
Just title -> windowSetTitle msgDialog title >>
widgetSetName msgDialog ("Sifflet-" ++ title)
; windowSetPosition msgDialog defaultDialogPosition
; windowPresent msgDialog
; _ <- dialogRun msgDialog
; widgetDestroy msgDialog
}
type Reader a b = (a -> SuccFail b)
data EntryDialog a = EntryDialog Dialog [Entry] (Reader [String] a)
createEntryDialog ::
String -> [String] -> [String] -> (Reader [String] a) -> Int ->
IO (EntryDialog a)
createEntryDialog title labels defaults reader width = do
(dialog, entries) <-
createDialog title (addEntries labels defaults)
windowSetDefaultSize dialog width (1)
return $ EntryDialog dialog entries reader
runEntryDialog :: (Show a) => EntryDialog a -> IO (Maybe a)
runEntryDialog (EntryDialog dialog entries reader) =
let
processInputs entries' = do
inputs <- mapM entryGetText entries'
return (reader inputs)
in runDialogS dialog entries processInputs
addEntries :: [String] -> [String] -> VBox -> IO [Entry]
addEntries labels defaults vbox = do
entries <- mapM (const entryNew) labels
mapM_ (addEntryWithLabel vbox) (zip3 labels entries defaults)
return entries
addEntryWithLabel :: VBox -> (String, Entry, String) -> IO ()
addEntryWithLabel vbox (name, entry, defaultValue) = do
label <- labelNew (Just name)
entrySetText entry defaultValue
boxPackStartDefaults vbox label
boxPackStartDefaults vbox entry