module Graphics.UI.Sifflet.Window
(
getOrCreateWindow
, showWindow
, newWindowTitled
, showWorkWin
, showWorkspaceWindow
, showFedWin
, fedWindowTitle
, getOrCreateFunctionPadWindow
, showFunctionPadWindow
, newFunctionDialog
, openFilePath
, setWSCanvasCallbacks
, keyBindingsHelpText
)
where
import Control.Monad
import Data.IORef
import Data.List as List
import Data.Map as Map (fromList, keys, lookup)
import Data.Map (Map)
import Data.Maybe
import Data.Text (Text, pack)
import Data.Graph.Inductive as G
import Data.Version
import Graphics.Rendering.Cairo
import Graphics.UI.Gtk.Gdk.EventM
import System.FilePath
import Data.Sifflet.Functoid
import Data.Sifflet.Geometry
import Data.Sifflet.WGraph
import Language.Sifflet.Export.Exporter
import Language.Sifflet.Export.ToHaskell (defaultHaskellOptions, exportHaskell)
import Language.Sifflet.Export.ToPython (defaultPythonOptions, exportPython)
import Language.Sifflet.Export.ToScheme (SchemeOptions(..), exportScheme)
import Language.Sifflet.Expr
import Language.Sifflet.SiffML
import Graphics.UI.Sifflet.Frame
import Graphics.UI.Sifflet.Canvas
import Graphics.UI.Sifflet.Types
import Graphics.UI.Sifflet.Callback
import Graphics.UI.Sifflet.Tool
import Graphics.UI.Sifflet.Workspace
import Graphics.UI.Sifflet.GtkForeign
import Graphics.UI.Sifflet.GtkUtil
import Graphics.UI.Sifflet.LittleGtk
import Graphics.UI.Sifflet.RPanel
import Language.Sifflet.Util
import Paths_sifflet as Paths
showWindow :: WinId -> CBMgr
-> (VPUI -> Window -> IO VPUIWindow)
-> (VPUI -> WinId -> CBMgr -> IO ())
-> VPUI -> IO (VPUI, VPUIWindow, Bool)
showWindow winId uimgr initWin initCB vpui =
getOrCreateWindow winId uimgr initWin initCB True vpui
getOrCreateWindow :: WinId -> CBMgr
-> (VPUI -> Window -> IO VPUIWindow)
-> (VPUI -> WinId -> CBMgr -> IO ())
-> Bool
-> VPUI -> IO (VPUI, VPUIWindow, Bool)
getOrCreateWindow winId uimgr initWin initCB visible vpui = do
(vpui', vw, isNew) <-
case vpuiTryGetWindow vpui winId of
Nothing -> do
window <- newWindowTitled winId
widgetSetName window ("Sifflet-" ++ winId)
vwin <- initWin vpui window
let vpui' = vpuiInsertWindow vpui winId vwin
uimgr (OnWindowDestroy window (onWindowDestroy winId))
return (vpui', vwin, True)
Just vw ->
return (vpui, vw, False)
when isNew (initCB vpui' winId uimgr)
when visible $
let window = vpuiWindowWindow vw
in do
widgetShowAll window
windowPresent window
return (vpui', vw, isNew)
onWindowDestroy :: WinId -> IORef VPUI -> IO ()
onWindowDestroy winId uiref =
if (winId == workspaceId)
then
readIORef uiref >>=
checkForChanges "quit (by closing the workspace window)" True False
(\ vpui -> do { mainQuit; return vpui }) >>
return ()
else modifyIORef uiref (vpuiRemoveVPUIWindow winId)
initCBDefault :: VPUI -> WinId -> CBMgr -> IO ()
initCBDefault _vpui _winId _uimgr = return ()
newWindowTitled :: String -> IO Window
newWindowTitled winId = do
window <- windowNew
set window [windowTitle := winId]
widgetSetName window ("Sifflet-" ++ winId)
return window
showWorkWin :: VPUI -> WinId -> CBMgr -> IO VPUI
showWorkWin vpui winId uimgr = do
{
(vpui', _, _) <- showWorkspaceWindow winId uimgr Nothing vpui
; return vpui'
}
showWorkspaceWindow :: WinId -> CBMgr -> Maybe Function -> VPUI
-> IO (VPUI, VPUIWindow, Bool)
showWorkspaceWindow winId cbmgr mfunc =
showWindow winId cbmgr (workspaceWindowInit cbmgr winId mfunc)
setWSCanvasCallbacks
workspaceWindowInit :: CBMgr -> WinId -> Maybe Function -> VPUI -> Window
-> IO VPUIWindow
workspaceWindowInit cbmgr winId mfunc vpui window = do
{
let style = vpuiStyle vpui
env = vpuiGlobalEnv vpui
; ws <- case mfunc of
Nothing -> workspaceNewDefault style (buildMainMenu cbmgr)
Just func -> workspaceNewEditing style env func
; set window [windowTitle := winId, containerChild := wsRootWidget ws]
; widgetShowAll window
; windowPresent window
; return $ VPUIWorkWin ws window
}
buildMainMenu :: CBMgr -> VBox -> IO ()
buildMainMenu cbmgr vbox = do
{
let mspecs =
[MenuSpec "File"
[
MenuItem "Open ... (C-o)" (menuFileOpen cbmgr)
, MenuItem "Save (C-s)" menuFileSave
, MenuItem "Save as ..." menuFileSaveAs
, MenuItem "Export to Haskell ..."
menuFileExportHaskell
, MenuItem "Export to Python3 ..." menuFileExportPython
, MenuItem "Export to Scheme ..." menuFileExportScheme
, MenuItem "Save image ..." menuFileSaveImage
, MenuItem "Quit (C-q)" menuFileQuit]
, MenuSpec "Functions"
[MenuItem "New ... (n)"
(newFunctionDialog "ignore" cbmgr)
, MenuItem "Function Pad"
(showFunctionPadWindow cbmgr)]
, MenuSpec "Help"
[MenuItem "Help ..." showHelpDialog
, MenuItem "Complaints and praise ..." showBugs
, MenuItem "About ..." showAboutDialog]
]
; menubar <- createMenuBar mspecs cbmgr
; boxPackStart vbox menubar PackNatural 0
}
showFedWin :: CBMgr -> String -> [String] -> VPUI -> IO VPUI
showFedWin cbmgr funcName argNames vpui = do
{
let initEnv = vpuiGlobalEnv vpui
function = case envLookupFunction initEnv funcName of
Nothing -> newUndefinedFunction funcName argNames
Just func -> func
winId = fedWindowTitle funcName
; (vpui', vw, isNew) <- showWorkspaceWindow winId cbmgr (Just function) vpui
; if isNew
then do
{
let canvas = vpuiWindowGetCanvas vw
; canvas' <- vcAddFrame canvas (FunctoidFunc function)
Nothing EditFrame
initEnv 0 0 0 Nothing
; canvas'' <-
case vcFrames canvas' of
[] -> info "showFedWin: ERROR: no frame on canvas" >>
return canvas'
_:_:_ ->
info "showFedWin: ERROR: too many frames on canvas" >>
return canvas'
[frame] -> editFunction canvas' frame
; addFedWinButtons cbmgr winId vpui'
; return (vpuiReplaceWindow vpui' winId
(vpuiWindowSetCanvas vw canvas''))
}
else return vpui'
}
fedWindowTitle :: String -> WinId
fedWindowTitle funcName = "Edit " ++ funcName
updateFunctionPadIO :: String -> (RPanel -> IO RPanel) -> VPUI -> IO VPUI
updateFunctionPadIO padName update =
let updateWindow vw =
case vw of
FunctionPadWindow window rpAList ->
do
{
rpAList' <- adjustAListM padName update rpAList
; return (FunctionPadWindow window rpAList')
}
_ -> return vw
in vpuiUpdateWindowIO "Function Pad" updateWindow
showFunctionPadWindow :: CBMgr -> VPUI -> IO VPUI
showFunctionPadWindow cbmgr vpui = getOrCreateFunctionPadWindow cbmgr True vpui
getOrCreateFunctionPadWindow :: CBMgr -> Bool -> VPUI -> IO VPUI
getOrCreateFunctionPadWindow cbmgr visible vpui =
let initWindow _vpui window = do
vbox <- vBoxNew False 0
set window [containerChild := vbox]
let rpnames = ["Base", "Examples", "My Functions"]
rps <- mapM (makeFunctionPadPanel cbmgr vpui) rpnames
mapM_ (\ rp -> boxPackStart vbox (rpanelRoot rp) PackNatural 0)
rps
windowMove window 5 5
return $ FunctionPadWindow window (zip rpnames rps)
in do
(vpui', _, windowIsNew) <- getOrCreateWindow functionPadWinId
cbmgr initWindow initCBDefault visible vpui
if windowIsNew
then addUserFunctions cbmgr vpui'
else return vpui'
functionPadWinId :: String
functionPadWinId = "Function Pad"
addUserFunctions :: CBMgr -> VPUI -> IO VPUI
addUserFunctions cbmgr vpui =
let names = map fst (vpuiUserEnvAList vpui)
update rp = do
{
buttons <- mapM (makeToolButton cbmgr . functionTool) names
; rp' <- rpanelAddWidgets rp (zip names buttons)
; widgetShowAll (rpanelRoot rp')
; return rp'
}
in updateFunctionPadIO "My Functions" update vpui
makeFunctionPadPanel :: CBMgr -> VPUI -> String -> IO RPanel
makeFunctionPadPanel cbmgr vpui name =
let VPToolkit _ width toolrows =
case List.lookup name (vpuiToolkits vpui) of
Nothing ->
errcats ["makeFunctionPadPanel:",
"can't find toolkit definition:", name]
Just atoolkit -> atoolkit
in do
{
buttonRows <- makeToolButtonRows cbmgr toolrows
:: IO [[(String, Button)]]
; rp <- newRPanel name 3 3 width
; rpanelAddRows rp buttonRows
}
makeToolButtonRows :: CBMgr -> [[Tool]] -> IO [[(String, Button)]]
makeToolButtonRows cbmgr toolRows =
mapM2 (makeNamedToolButton cbmgr) toolRows
makeNamedToolButton :: CBMgr -> Tool -> IO (String, Button)
makeNamedToolButton cbmgr tool = do
{
button <- makeToolButton cbmgr tool
; return (toolName tool, button)
}
makeToolButton :: CBMgr -> Tool -> IO Button
makeToolButton cbmgr tool = do
{
button <- buttonNewWithLabel (toolName tool)
; cbmgr (AfterButtonClicked button
(modifyIORefIO (forallWindowsIO (vpuiWindowSetTool tool))))
; return button
}
addFunctionPadToolButton :: CBMgr -> String -> Tool -> VPUIWindow
-> IO VPUIWindow
addFunctionPadToolButton cbmgr panelId tool vw =
case vw of
FunctionPadWindow window panelAList ->
let adjustPanel :: RPanel -> IO RPanel
adjustPanel rp = do
{
button <- makeToolButton cbmgr tool
; rp' <- rpanelAddWidget rp (toolName tool) button
; widgetShowAll (rpanelRoot rp')
; return rp'
}
in do
{
panelAList' <- adjustAListM panelId adjustPanel panelAList
; return $ FunctionPadWindow window panelAList'
}
_ -> return vw
newFunctionDialog :: WinId -> CBMgr -> VPUI -> IO VPUI
newFunctionDialog _winId cbmgr vpui =
let reader :: Reader [String] (String, [String])
reader inputLines =
case inputLines of
[fname, fargs] ->
return (fname, words fargs)
_ -> fail "wrong number of lines"
in do
{
inputDialog <-
createEntryDialog "New Function"
["Function name", "Argument names (space between)"]
["", ""]
reader
(1)
; values <- runEntryDialog inputDialog
; case values of
Nothing -> return vpui
Just (name, args) -> editNewFunction cbmgr name args vpui
}
menuFileQuit :: VPUI -> IO VPUI
menuFileQuit = checkForChanges "quit" False True vpuiQuit
menuFileOpen :: CBMgr -> VPUI -> IO VPUI
menuFileOpen cbmgr =
checkForChanges "open file" True True (continueFileOpen cbmgr)
checkForChanges :: String -> Bool -> Bool -> (VPUI -> IO VPUI)
-> VPUI -> IO VPUI
checkForChanges beforeOperation acknowledge offerCancel continue vpui =
let mAckIfSaved vpui' =
when (not (vpuiFileChanged vpui') && acknowledge)
(
showInfoMessage "Changes saved"
("Your changes are now saved; " ++
"proceeding to " ++
beforeOperation ++ ".")
)
>>
return vpui'
choices = [("Save them",
menuFileSave vpui >>= mAckIfSaved >>= continue),
("Throw them away",
return vpui >>= continue)] ++
if offerCancel
then [("Cancel " ++ beforeOperation, return vpui)]
else []
labels = map fst choices
actions = map snd choices
offerSaveAndContinue = showChoicesDialog "Save changes?"
("There are unsaved changes. " ++
"Before you " ++ beforeOperation ++
", would you ...")
labels
actions
(return vpui)
in if vpuiFileChanged vpui
then offerSaveAndContinue
else continue vpui
continueFileOpen :: CBMgr -> VPUI -> IO VPUI
continueFileOpen cbmgr vpui = do
mpath <- showDialogFileOpen vpui
case mpath of
Nothing -> return vpui
Just filePath -> openFilePath cbmgr filePath vpui
openFilePath :: CBMgr -> FilePath -> VPUI -> IO VPUI
openFilePath cbmgr filePath vpui = do
loadResult <- loadFile vpui filePath
case loadResult of
Fail msg ->
showErrorMessage msg >> return vpui
Succ (vpui', functions) ->
let title = "My Functions"
updatePad rp =
let oldNames = concat (rpanelContent rp)
loadedNames = map functionName functions
newNames = loadedNames \\ oldNames
newTools = map functionTool newNames
in do
newPairs <- mapM (makeNamedToolButton cbmgr) newTools
rp' <- rpanelAddWidgets rp newPairs
widgetShowAll (rpanelRoot rp)
return rp'
in do
vpui'' <-
getOrCreateFunctionPadWindow cbmgr False vpui' >>=
updateFunctionPadIO title updatePad
setWorkspaceTitleForFile vpui'' filePath
return $ vpui'' {vpuiCurrentFile = Just filePath,
vpuiCurrentDir = takeDirectory filePath,
vpuiFileEnv = vpuiGlobalEnv vpui'}
setWorkspaceTitleForFile :: VPUI -> FilePath -> IO ()
setWorkspaceTitleForFile vpui filePath =
case vpuiTryGetWindow vpui workspaceId of
Just (VPUIWorkWin _ window) ->
set window [windowTitle :=
workspaceId ++ ": " ++ takeFileName filePath]
_ -> return ()
showDialogFileOpen :: VPUI -> IO (Maybe FilePath)
showDialogFileOpen vpui = do
chooser <- fileChooserDialogNew
(Just "Open file ...")
Nothing
FileChooserActionOpen
[("Open", ResponseOk), ("Cancel", ResponseCancel)]
_ <- fileChooserSetCurrentFolder chooser (vpuiCurrentDir vpui)
result <- runDialogM (toDialog chooser) chooser fileChooserGetFilename
return result
loadFile :: VPUI -> FilePath -> IO (SuccFail (VPUI, [Function]))
loadFile vpui filePath = do
{
functions <- consumeSiffMLFile xmlToFunctions filePath
; case functions of
[Functions fs] ->
let vpui' = foldl bindFunction vpui fs
in return (Succ (vpui', fs))
_ ->
return (Fail "file format error")
}
bindFunction :: VPUI -> Function -> VPUI
bindFunction vpui function =
let env = vpuiGlobalEnv vpui
Function (Just name) _argTypes _resType _impl = function
env' = envIns env name (VFun function)
in vpui {vpuiGlobalEnv = env'}
menuFileSave :: VPUI -> IO VPUI
menuFileSave vpui =
case vpuiCurrentFile vpui of
Nothing -> menuFileSaveAs vpui
Just filePath -> saveFile vpui filePath
menuFileSaveAs :: VPUI -> IO VPUI
menuFileSaveAs vpui = do
{
mFilePath <- chooseOutputFile "Save" vpui
; case mFilePath of
Nothing -> return vpui
Just filePath -> saveFile vpui filePath
}
saveFile :: VPUI -> FilePath -> IO VPUI
saveFile vpui filePath =
produceSiffMLFile (userFunctions vpui) filePath >>
setWorkspaceTitleForFile vpui filePath >>
return vpui {vpuiCurrentFile = Just filePath,
vpuiCurrentDir = takeDirectory filePath,
vpuiFileEnv = vpuiGlobalEnv vpui}
userFunctions :: VPUI -> Functions
userFunctions vpui =
Functions (map (valueFunction . snd)
(vpuiUserEnvAList vpui))
maybeExportUserFunctions :: VPUI -> (opts -> Exporter)
-> Maybe (FilePath, opts) -> IO VPUI
maybeExportUserFunctions vpui export mpathOptions =
case mpathOptions of
Nothing -> return vpui
Just (path, options) ->
export options (userFunctions vpui) path >>
return (vpui {vpuiCurrentDir = takeDirectory path})
menuFileExportHaskell :: VPUI -> IO VPUI
menuFileExportHaskell vpui =
chooseOutputFile "Export Haskell" vpui >>=
maybeDefaultOptions defaultHaskellOptions >>=
maybeExportUserFunctions vpui exportHaskell
menuFileExportPython :: VPUI -> IO VPUI
menuFileExportPython vpui =
chooseOutputFile "Export Python" vpui >>=
maybeDefaultOptions defaultPythonOptions >>=
maybeExportUserFunctions vpui (exportPython vpui)
menuFileExportScheme :: VPUI -> IO VPUI
menuFileExportScheme vpui =
chooseOutputFile "Export Scheme" vpui >>=
maybeRunSchemeOptionsDialog >>=
maybeExportUserFunctions vpui (exportScheme vpui)
chooseOutputFile :: String -> VPUI -> IO (Maybe FilePath)
chooseOutputFile verb vpui = do
chooser <- fileChooserDialogNew
(Just (verb ++ " to file ..."))
Nothing
FileChooserActionSave
[(verb, ResponseOk), ("Cancel", ResponseCancel)]
_ <- fileChooserSetCurrentFolder chooser (vpuiCurrentDir vpui)
result <- runDialogM (toDialog chooser) chooser fileChooserGetFilename
return result
maybeDefaultOptions :: a -> Maybe FilePath -> IO (Maybe (FilePath, a))
maybeDefaultOptions defaultOptions mpath =
case mpath of
Nothing -> return Nothing
Just path -> return $ Just (path, defaultOptions)
maybeRunSchemeOptionsDialog :: Maybe FilePath
-> IO (Maybe (FilePath, SchemeOptions))
maybeRunSchemeOptionsDialog mpath =
case mpath of
Nothing -> return Nothing
Just path ->
let result :: Bool -> IO (Maybe (FilePath, SchemeOptions))
result useLambda =
return (Just (path,
SchemeOptions {defineWithLambda = useLambda}))
in showChoicesDialog "Scheme Export Options"
"Use lambda in function definitions?"
["Yes", "No"]
[result True, result False]
(result False)
menuFileSaveImage :: VPUI -> IO VPUI
menuFileSaveImage vpui = do
mImageOptions <- chooseImageOptions vpui
case mImageOptions of
Nothing -> return vpui
Just (windowId, fileExt) -> do
mfile <- chooseOutputFile ("Save image of " ++ windowId) vpui
case mfile of
Nothing -> return vpui
Just filePath ->
saveImageFile vpui windowId filePath fileExt
chooseImageOptions :: VPUI -> IO (Maybe (WinId, String))
chooseImageOptions vpui =
let hasCanvas winId =
isJust (vpuiWindowLookupCanvas (vpuiGetWindow vpui winId))
windowChoices = filter hasCanvas (keys (vpuiWindows vpui))
windowActions = map (return . Just) windowChoices
formatChoices = ["SVG", "PS", "PDF"]
formatActions = map (return . Just) [".svg", ".ps", ".pdf"]
in do
mExt <- showChoicesDialog "Save Image" "Select image format"
formatChoices formatActions (return Nothing)
case mExt of
Nothing -> return Nothing
Just ext -> do
mWinId <-
if length windowChoices == 1
then return $ Just $ head windowChoices
else showChoicesDialog "Save Image"
"Select window to save as image"
windowChoices windowActions (return Nothing)
case mWinId of
Nothing -> return Nothing
Just winId -> return $ Just (winId, ext)
saveImageFile :: VPUI -> WinId -> FilePath -> String -> IO VPUI
saveImageFile vpui winId path ext =
let vpuiWindow = vpuiGetWindow vpui winId
canvas = vpuiWindowGetCanvas vpuiWindow
clipbox@(BBox _ _ width height) = defaultFileSaveClipBox canvas
render :: Surface -> IO ()
render surface =
renderWith surface (renderCanvas canvas clipbox True)
path' = if takeExtension path == ext
then path
else addExtension path ext
vpui' = vpui {vpuiCurrentDir = takeDirectory path}
in case ext of
".pdf" -> withPDFSurface path' width height render >> return vpui'
".ps" -> withPSSurface path' width height render >> return vpui'
".svg" -> withSVGSurface path' width height render >> return vpui'
_ -> do
showErrorMessage $
"Unable to save in this file format " ++
"(" ++ ext ++ ").\n" ++
"Please try a file extension of " ++
".svg, .ps, or .pdf."
menuFileSaveImage vpui'
helpText :: String
helpText =
unlines ["Functions menu:",
" \"New\" enters a dialog to create a new function.",
" \"Function pad\" raises the function pad window.",
"Keystroke shortcuts for the menu commands are shown " ++
"using \"C-\" for Control. For example, Quit " ++
"is C-q, meaning Control+Q.",
"",
"In a function editor, right-click for the context menu.",
"",
"For more help, please visit the Sifflet web site,",
"http://mypage.iu.edu/~gdweber/software/sifflet/",
"especially the Sifflet Tutorial:",
"http://mypage.iu.edu/~gdweber/software/sifflet/doc/tutorial.html"
]
showHelpDialog :: MenuItemAction
showHelpDialog vpui = showInfoMessage "Sifflet Help" helpText >> return vpui
bugsText :: String
bugsText =
unlines ["To report bugs, please send mail to " ++ bugReportAddress,
"and mention \"Sifflet\" in the Subject header.",
"To send praise, follow the same procedure.",
"Seriously, whether you like Sifflet or dislike it,",
"I'd like to hear from you."
]
bugReportAddress :: String
bugReportAddress = concat ["gdweber", at, "iue", punctum, "edu"]
where at = "@"
punctum = "."
showBugs :: MenuItemAction
showBugs vpui = showInfoMessage "Reporting bugs" bugsText >> return vpui
aboutText :: String
aboutText =
unlines ["Sifflet version " ++ showVersion Paths.version,
"Copyright (C) 2010-2012 Gregory D. Weber",
"",
"BSD3 License",
"",
"Sifflet home page:",
"http://mypage.iu.edu/~gdweber/software/sifflet/"
]
showAboutDialog :: MenuItemAction
showAboutDialog vpui = showInfoMessage "About Sifflet" aboutText >> return vpui
setWSCanvasCallbacks :: VPUI -> WinId -> CBMgr -> IO ()
setWSCanvasCallbacks vpui winId cbmgr = do
{
let vw = vpuiGetWindow vpui winId
window = vpuiWindowWindow vw
; case vpuiWindowLookupCanvas vw of
Nothing ->
errcats ["setWSCanvasCallbacks: VPUIWindow is not a VPUIWorkWin",
"and has no canvas"]
Just canvas ->
do
{
; cbmgr (OnWindowConfigure window (configuredCallback winId))
; cbmgr (AfterWindowKeyPress window (keyPressCallback winId cbmgr))
; let layout = vcLayout canvas
; widgetSetCanFocus layout True
; cbmgr (OnLayoutExpose layout (exposedCallback winId))
; widgetAddEvents layout [PointerMotionMask]
; cbmgr (OnLayoutMouseMove layout (mouseMoveCallback winId))
; cbmgr (OnLayoutButtonPress layout
(buttonPressCallback winId cbmgr))
; cbmgr (OnLayoutButtonRelease layout (buttonReleaseCallback winId))
}
}
editFrameFunction :: CBMgr -> CanvFrame -> VPUI -> IO VPUI
editFrameFunction cbmgr frame vpui =
let func = cfFunctoid frame
in showFedWin cbmgr (functoidName func) (functoidArgNames func) vpui
editNewFunction :: CBMgr -> String -> [String] -> VPUI -> IO VPUI
editNewFunction cbmgr name args vpui =
let updateEnv :: VPUI -> IO VPUI
updateEnv vpui' =
let env = vpuiGlobalEnv vpui'
env' = envIns env name (VFun (newUndefinedFunction name args))
in return $ vpui' {vpuiGlobalEnv = env'}
in
showFunctionPadWindow cbmgr vpui >>=
updateEnv >>=
vpuiUpdateWindowIO functionPadWinId
(addFunctionPadToolButton cbmgr "My Functions"
(functionTool name)) >>=
showFedWin cbmgr name args
configuredCallback :: WinId -> IORef VPUI -> EventM EConfigure Bool
configuredCallback winId uiref =
tryEvent $ do
{
(w, h) <- eventSize
; liftIO $ modifyIORef uiref (handleConfigured winId w h)
; stopEvent
}
handleConfigured :: WinId -> Int -> Int -> VPUI -> VPUI
handleConfigured winId width height vpui =
let vw = vpuiGetWindow vpui winId
vw' = vpuiWindowModCanvas vw
(atLeastSize (Size (fromIntegral width) (fromIntegral height)))
in vpuiReplaceWindow vpui winId vw'
exposedCallback :: WinId -> IORef VPUI -> EventM EExpose Bool
exposedCallback winId uiref =
tryEvent $ do
{
cliprect <- eventArea
; liftIO (readIORef uiref >>= handleExposed winId cliprect)
}
handleExposed :: WinId -> Rectangle -> VPUI -> IO ()
handleExposed winId cliprect vpui =
let vw = vpuiGetWindow vpui winId
in case vpuiWindowLookupCanvas vw of
Nothing -> info "handleExposed: no canvas found!"
Just canvas -> drawCanvas canvas cliprect
data KeyBinding = KeyBinding {kbGtkKeyName :: String,
kbAltKeyName :: Maybe String,
kbRequiredModifiers :: [Modifier],
kbDescription :: String,
kbAction :: KeyAction}
data KeyAction
= KeyActionST (WinId -> VPUI -> IO VPUI)
| KeyActionDG (WinId -> CBMgr -> VPUI -> IO VPUI)
| KeyActionModIO (CBMgr -> VPUI -> IO VPUI)
| KeyActionHQ (VPUI -> IO ())
keyBindingsMap :: Map Text KeyBinding
keyBindingsMap =
Map.fromList [(pack (kbGtkKeyName kb), kb) | kb <- keyBindingsList]
keyBindingsList :: [KeyBinding]
keyBindingsList =
[
KeyBinding "c" Nothing [] "connect"
(KeyActionST (vpuiSetTool ToolConnect))
, KeyBinding "d" Nothing [] "disconnect"
(KeyActionST (vpuiSetTool ToolDisconnect))
, KeyBinding "i" Nothing [] "if" (KeyActionST (vpuiSetTool ToolIf))
, KeyBinding "m" Nothing [] "move" (KeyActionST (vpuiSetTool ToolMove))
, KeyBinding "KP_Delete" (Just "Keypad-Del") [] "delete"
(KeyActionST (vpuiSetTool ToolDelete))
, KeyBinding "n" Nothing [] "new function" (KeyActionDG newFunctionDialog)
, KeyBinding "f" Nothing [] "function" (KeyActionDG showFunctionEntry)
, KeyBinding "l" Nothing [] "literal" (KeyActionDG showLiteralEntry)
, KeyBinding "question" (Just "?") [] "help" (KeyActionHQ vpuiKeyHelp)
, KeyBinding "o" (Just "Control-o") [Control] "open"
(KeyActionModIO menuFileOpen)
, KeyBinding "s" (Just "Control-s") [Control] "save"
(KeyActionModIO (\ _cbmgr -> menuFileSave))
, KeyBinding "q" (Just "Control-q") [Control] "quit"
(KeyActionHQ (\ vpui -> menuFileQuit vpui >> return ()))
]
vpuiKeyHelp :: VPUI -> IO ()
vpuiKeyHelp _vpui = putStrLn keyBindingsHelpText
keyBindingsHelpText :: String
keyBindingsHelpText =
let add :: String -> KeyBinding -> String
add result (kb@KeyBinding {kbAltKeyName = mkey}) =
concat [result, " ",
case mkey of
Nothing -> kbGtkKeyName kb
Just akey -> akey,
" = ", kbDescription kb, "\n"]
in foldl add "" keyBindingsList
keyPressCallback :: WinId -> CBMgr -> IORef VPUI -> EventM EKey Bool
keyPressCallback winId cbmgr uiref =
tryEvent $ do
{
kname <- eventKeyName
; mods <- eventModifier
; let giveUp =
stopEvent
; case Map.lookup kname keyBindingsMap of
Nothing ->
giveUp
Just keyBinding ->
if checkMods (kbRequiredModifiers keyBinding) mods
then liftIO $
case kbAction keyBinding of
KeyActionModIO f0 ->
modifyIORefIO (f0 cbmgr) uiref
KeyActionST f1 ->
modifyIORefIO (f1 winId) uiref
KeyActionDG f2 ->
modifyIORefIO (f2 winId cbmgr) uiref
KeyActionHQ f3 ->
readIORef uiref >>= f3
else giveUp
}
buttonPressCallback :: WinId -> CBMgr -> IORef VPUI -> EventM EButton Bool
buttonPressCallback winId cbmgr uiref =
tryEvent $ do
{
; (x, y) <- eventCoordinates
; mouseButton <- eventButton
; mods <- eventModifier
; timestamp <- eventTime
; let updateAction =
handleButtonPress winId cbmgr mouseButton x y mods timestamp
; liftIO (modifyIORefIO updateAction uiref)
}
mouseMoveCallback :: WinId -> IORef VPUI -> EventM EMotion Bool
mouseMoveCallback winId uiref =
tryEvent $ do
{
(x, y) <- eventCoordinates
; mods <- eventModifier
; liftIO (modifyIORefIO (handleMouseMove winId x y mods) uiref)
}
buttonReleaseCallback :: WinId -> IORef VPUI -> EventM EButton Bool
buttonReleaseCallback winId uiref =
tryEvent $ do
{
mouseButton <- eventButton
; liftIO (modifyIORefIO (handleButtonRelease winId mouseButton) uiref)
}
handleButtonPress :: WinId -> CBMgr -> MouseButton
-> Double -> Double
-> [Modifier] -> TimeStamp
-> VPUI ->IO VPUI
handleButtonPress winId cbmgr mouseButton x y mods timestamp vpui =
let vw = vpuiGetWindow vpui winId
in case vpuiWindowLookupCanvas vw of
Nothing -> info "handleButtonPress: no canvas found!" >>
return vpui
Just canvas ->
case whichFrame canvas x y of
Nothing ->
case vcTool canvas of
Nothing -> return vpui
Just tool -> toolOp tool vpui winId TCWorkspace mods x y
Just frame ->
frameButtonPressed winId cbmgr vw
frame mods (x, y)
mouseButton timestamp vpui
frameButtonPressed :: WinId -> CBMgr -> VPUIWindow -> CanvFrame
-> [Modifier] -> (Double, Double) -> MouseButton
-> TimeStamp
-> VPUI
-> IO VPUI
frameButtonPressed winId cbmgr vw frame mods (x, y) mouseButton timestamp vpui =
let retWrap :: VPUIWindow -> IO VPUI
retWrap = return . vpuiReplaceWindow vpui winId
in case mouseButton of
LeftButton ->
if cfPointInHeader frame x y
then beginFrameDrag vw frame x y >>= retWrap
else if cfPointInFooter frame x y
then leftButtonPressedInFrameFooter vw frame >>= retWrap
else frameBodyButtonPressed vpui winId frame
mouseButton mods x y
MiddleButton -> return vpui
RightButton -> do
offerContextMenu winId cbmgr frame RightButton timestamp
(vpuiDebugging vpui)
return vpui
OtherButton _ -> return vpui
frameBodyButtonPressed :: VPUI -> WinId -> CanvFrame
-> MouseButton -> [Modifier] -> Double -> Double
-> IO VPUI
frameBodyButtonPressed vpui winId frame _mb mods x y = do
{
let vw = vpuiGetWindow vpui winId
canvas = vpuiWindowGetCanvas vw
mnode = vcanvasNodeAt canvas (Position x y)
; case mnode of
Nothing ->
case vcTool canvas of
Nothing -> return vpui
Just tool -> toolOp tool vpui winId (cfContext frame) mods x y
Just node ->
do
{
vw' <- openNode vw node
; return $ vpuiReplaceWindow vpui winId vw'
}
}
leftButtonPressedInFrameFooter ::
VPUIWindow -> CanvFrame -> IO VPUIWindow
leftButtonPressedInFrameFooter vw frame =
let canvas = vpuiWindowGetCanvas vw
in case frameType frame of
CallFrame ->
if cfEvalReady frame
then do
canvas' <- vcEvalDialog canvas frame
return $ vpuiWindowSetCanvas vw canvas'
else return vw
EditFrame ->
return vw
beginFrameDrag :: VPUIWindow -> CanvFrame -> Double -> Double
-> IO VPUIWindow
beginFrameDrag vw frame x y =
let canvas = vpuiWindowGetCanvas vw
window = vpuiWindowWindow vw
dragging = Dragging {draggingNode = cfFrameNode frame,
draggingPosition = Position x y}
canvas' = canvas {vcDragging = Just dragging}
in setCursor window Fleur >>
(return $ vpuiWindowSetCanvas vw canvas')
handleMouseMove :: WinId -> Double -> Double -> [Modifier] -> VPUI -> IO VPUI
handleMouseMove winId x y mods vpui =
let vw = vpuiGetWindow vpui winId
in case vpuiWindowLookupCanvas vw of
Nothing ->
info "SQUAWK! No canvas! Shouldn't happen!" >>
return vpui
Just canvas ->
do
{
let active = vcActive canvas
active' = vcanvasNodeAt canvas (Position x y)
invalidate :: DrawWindow -> Maybe G.Node -> IO ()
invalidate win mnode =
case mnode of
Nothing -> return ()
Just node ->
drawWindowInvalidateRect win
(vcanvasNodeRect canvas node) False
; when (active /= active') $
do
{
win <- layoutGetDrawWindow (vcLayout canvas)
; invalidate win active
; invalidate win active'
}
; canvas' <- continueDrag (canvas {vcActive = active',
vcMousePos = (x, y)})
mods x y
; let vw' = vpuiWindowSetCanvas vw canvas'
; return $ vpuiReplaceWindow vpui winId vw'
}
continueDrag :: VCanvas -> [Modifier] -> Double -> Double -> IO VCanvas
continueDrag canvas mods x y =
case vcDragging canvas of
Nothing -> return canvas
Just dragging ->
let graph = vcGraph canvas
dnode = draggingNode dragging
wnode = wlab graph dnode
Position oldX oldY = draggingPosition dragging
(dx, dy) = (x oldX, y oldY)
in
case wnode of
WSimple _ ->
continueDragSimple canvas dragging dnode mods x y dx dy
WFrame frameNode ->
continueDragFrame canvas dragging frameNode x y dx dy
continueDragSimple :: VCanvas -> Dragging -> G.Node -> [Modifier]
-> Double -> Double -> Double -> Double -> IO VCanvas
continueDragSimple canvas dragging simpleNode mods x y dx dy =
let graph = vcGraph canvas
frame = nodeContainerFrame canvas graph simpleNode
dragging' = dragging {draggingPosition = Position x y}
translateSelection = if checkMods [Shift] mods
then translateTree
else translateNode
graph' = translateSelection dx dy graph simpleNode
canvas' = canvas {vcGraph = graph'}
in vcInvalidateFrameWithParent canvas graph frame >>
return (canvas' {vcDragging = Just dragging'})
continueDragFrame ::
VCanvas -> Dragging -> G.Node ->
Double -> Double -> Double -> Double -> IO VCanvas
continueDragFrame canvas dragging frameNode x y dx dy =
let graph = vcGraph canvas
frame = vcGetFrame canvas graph frameNode
frame' = translateFrame frame dx dy
graph' = grTranslateFrameNodes graph frame dx dy
canvas' = vcUpdateFrameAndGraph canvas frame' graph'
dragging' = Just dragging {draggingPosition = Position x y}
in
frameChanged canvas graph frame graph' frame' >>
mapM_ (\f -> frameChanged canvas graph f graph' f)
(vcFrameSubframes canvas frame) >>
return (canvas' {vcDragging = dragging'})
handleButtonRelease :: WinId -> MouseButton -> VPUI -> IO VPUI
handleButtonRelease winId mouseButton vpui =
case mouseButton of
LeftButton ->
let vw = vpuiGetWindow vpui winId
canvas = vpuiWindowGetCanvas vw
window = vpuiWindowWindow vw
vw' = vpuiWindowSetCanvas vw (canvas {vcDragging = Nothing})
vpui' = vpuiReplaceWindow vpui winId vw'
in setCursor window LeftPtr >>
return vpui'
_ -> return vpui
offerContextMenu :: WinId -> CBMgr -> CanvFrame
-> MouseButton -> TimeStamp -> Bool -> IO ()
offerContextMenu winId cbmgr frame button timestamp debugging = do
{
let menuSpec =
MenuSpec "Context Menu"
(contextMenuOptions winId cbmgr frame debugging)
; menu <- createMenu menuSpec cbmgr
; widgetShowAll menu
; menuPopup menu (Just (button, timestamp))
}
contextMenuOptions :: WinId -> CBMgr -> CanvFrame -> Bool -> [MenuItemSpec]
contextMenuOptions winId cbmgr frame debugging =
let typeDependentOptions :: [MenuItemSpec]
typeDependentOptions =
case frameType frame of
CallFrame ->
[MenuItem "Edit" (editFrameFunction cbmgr frame)
, MenuItem "Close" (\ vpui -> closeFrame vpui winId frame)]
EditFrame ->
[
MenuItem "CONNECT (c)" (vpuiSetTool ToolConnect winId)
, MenuItem "DISCONNECT (d)" (vpuiSetTool ToolDisconnect winId)
, MenuItem "IF (i)" (vpuiSetTool ToolIf winId)
, MenuItem "FUNCTION (f)" (showFunctionEntry winId cbmgr)
, MenuItem "LITERAL (l)" (showLiteralEntry winId cbmgr)
, MenuItem "MOVE (m)" (vpuiSetTool ToolMove winId)
, MenuItem "DELETE (KP-Del)" (vpuiSetTool ToolDelete winId)
]
in typeDependentOptions ++
if debugging
then [MenuItem "Dump frame (debug)"
(\ vpui -> dumpFrame vpui winId frame >> return vpui)
, MenuItem "Dump graph (debug)"
(\ vpui -> dumpGraph vpui winId >> return vpui)
]
else []