sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.UI.Types
Synopsis
data VPUI = VPUI {
vpuiWindows :: Map WinId VPUIWindow
vpuiToolkits :: [(String, VPToolkit)]
vpuiFilePath :: Maybe FilePath
vpuiStyle :: Style
vpuiInitialEnv :: Env
vpuiGlobalEnv :: Env
vpuiFileEnv :: Env
}
type WinId = String
data VPUIWindow
= VPUIWorkWin Workspace Window
| FunctionPadWindow Window [(String, RPanel)]
vpuiFileChanged :: VPUI -> Bool
vpuiUserEnvAList :: VPUI -> [(String, Value)]
vpuiInsertWindow :: VPUI -> WinId -> VPUIWindow -> VPUI
vpuiTryGetWindow :: VPUI -> WinId -> Maybe VPUIWindow
vpuiGetWindow :: VPUI -> WinId -> VPUIWindow
vpuiUpdateWindow :: VPUI -> WinId -> (VPUIWindow -> VPUIWindow) -> VPUI
vpuiReplaceWindow :: VPUI -> WinId -> VPUIWindow -> VPUI
vpuiUpdateWindowIO :: WinId -> (VPUIWindow -> IO VPUIWindow) -> VPUI -> IO VPUI
vpuiRemoveVPUIWindow :: WinId -> VPUI -> VPUI
vpuiWindowLookupCanvas :: VPUIWindow -> Maybe VCanvas
vpuiWindowGetCanvas :: VPUIWindow -> VCanvas
vpuiWindowSetCanvas :: VPUIWindow -> VCanvas -> VPUIWindow
vpuiWindowModCanvas :: VPUIWindow -> (VCanvas -> VCanvas) -> VPUIWindow
vpuiWindowModCanvasIO :: VPUIWindow -> (VCanvas -> IO VCanvas) -> IO VPUIWindow
vpuiModCanvas :: VPUI -> WinId -> (VCanvas -> VCanvas) -> VPUI
vpuiModCanvasIO :: VPUI -> WinId -> (VCanvas -> IO VCanvas) -> IO VPUI
vpuiWindowWindow :: VPUIWindow -> Window
data VPToolkit = VPToolkit {
toolkitName :: String
toolkitWidth :: Int
toolkitRows :: [[Tool]]
}
data Toolbox = Toolbox {
toolboxFrame :: GtkFrame
toolboxVBox :: VBox
}
data Tool = Tool {
toolName :: String
toolActivated :: VCanvas -> IO VCanvas
toolOp :: ToolOp
}
data ToolContext
= TCWorkspace
| TCCallFrame CanvFrame
| TCEditFrame CanvFrame
| TCExprNode
type CanvasToolOp = VCanvas -> ToolContext -> [Modifier] -> Double -> Double -> IO VCanvas
type ToolOp = VPUI -> WinId -> ToolContext -> [Modifier] -> Double -> Double -> IO VPUI
toToolOpVW :: CanvasToolOp -> ToolOp
data Workspace = Workspace {
wsBox :: VBox
wsCanvas :: VCanvas
wsButtonBar :: HBox
wsStatusbar :: Statusbar
}
data FunctionEditor = FunctionEditor {
fedWindow :: Window
fedWinTitle :: String
fedFunction :: Function
fedCanvas :: VCanvas
}
fedFunctionName :: FunctionEditor -> String
data VCanvas = VCanvas {
vcLayout :: GtkLayout
vcStyle :: Style
vcGraph :: WGraph
vcFrames :: [CanvFrame]
vcSize :: Size
vcMousePos :: (Double, Double)
vcTool :: Maybe Tool
vcActive :: Maybe Node
vcSelected :: Maybe Selection
vcDragging :: Maybe Dragging
}
data Selection
= SelectionNode {
selNode :: Node
}
| SelectionInlet {
selNode :: Node
selInEdge :: WEdge
}
| SelectionOutlet {
selNode :: Node
selOutEdge :: WEdge
}
data Dragging = Dragging {
draggingNode :: Node
draggingPosition :: Position
}
Documentation
data VPUI Source
VPUI: Sifflet (formerly VisiProg) User Interface The initialEnv is apt to contain builtin functions; it's preserved here so that when writing to a file, we can skip the functions that were in the initial env.
Constructors
VPUI
vpuiWindows :: Map WinId VPUIWindowall the windows of the program
vpuiToolkits :: [(String, VPToolkit)]ordered association list, collections of tools
vpuiFilePath :: Maybe FilePaththe file opened or to save
vpuiStyle :: Stylefor windows, canvases, editors
vpuiInitialEnv :: Envinitial value of global environment
vpuiGlobalEnv :: Envthe global environment
vpuiFileEnv :: Envglobal env as of last file open or save, used to detect unsaved changes
type WinId = StringSource
data VPUIWindow Source
Constructors
VPUIWorkWin Workspace Window
FunctionPadWindow Window [(String, RPanel)]
vpuiFileChanged :: VPUI -> BoolSource
Tell whether the global environmkent has changed since the last file open or save
vpuiUserEnvAList :: VPUI -> [(String, Value)]Source
Extract from the environment the part defined by the user But you probably want to use Sifflet.UI.Window.UserFunctions instead of this.
Operations on a VPUI involving its window
vpuiInsertWindow :: VPUI -> WinId -> VPUIWindow -> VPUISource
Insert a window in the window map
vpuiTryGetWindow :: VPUI -> WinId -> Maybe VPUIWindowSource
Try to get the VPUIWindow with the given window ID, return Just result or Nothing
vpuiGetWindow :: VPUI -> WinId -> VPUIWindowSource
Get the VPUIWindow with the given window ID; it is an error if this fails.
vpuiUpdateWindow :: VPUI -> WinId -> (VPUIWindow -> VPUIWindow) -> VPUISource
Apply an update function to a VPUIWindow with given window ID; it is an error if this fails.
vpuiReplaceWindow :: VPUI -> WinId -> VPUIWindow -> VPUISource
Replace a VPUIWindow with given window ID; it is an error if this fails.
vpuiUpdateWindowIO :: WinId -> (VPUIWindow -> IO VPUIWindow) -> VPUI -> IO VPUISource
Apply an update IO action to a VPUIWindow with given window ID; it is an error if this fails.
vpuiRemoveVPUIWindow :: WinId -> VPUI -> VPUISource
Remove a window from the windows map; it has already been destroyed in the GUI
Operations on a window involving its canvas
vpuiWindowLookupCanvas :: VPUIWindow -> Maybe VCanvasSource
Try to find canvas; fail gracefully
vpuiWindowGetCanvas :: VPUIWindow -> VCanvasSource
Find canvas or fail dramatically
vpuiWindowSetCanvas :: VPUIWindow -> VCanvas -> VPUIWindowSource
vpuiWindowModCanvas :: VPUIWindow -> (VCanvas -> VCanvas) -> VPUIWindowSource
vpuiWindowModCanvasIO :: VPUIWindow -> (VCanvas -> IO VCanvas) -> IO VPUIWindowSource
Operation on a VPUI involving the canvas of its window
vpuiModCanvas :: VPUI -> WinId -> (VCanvas -> VCanvas) -> VPUISource
Update the canvas of the specified window, without IO
vpuiModCanvasIO :: VPUI -> WinId -> (VCanvas -> IO VCanvas) -> IO VPUISource
Update the canvas of the specified window, with IO
Other operations on a window
vpuiWindowWindow :: VPUIWindow -> WindowSource
data VPToolkit Source
Toolkit functions are organized in groups (rows) for presentation in a toolbox
Constructors
VPToolkit
toolkitName :: String
toolkitWidth :: Int
toolkitRows :: [[Tool]]
data Toolbox Source
A Toolbox is a framed VBox with a set of Toolbars attached
Constructors
Toolbox
toolboxFrame :: GtkFrame
toolboxVBox :: VBox
data Tool Source
Constructors
Tool
toolName :: String
toolActivated :: VCanvas -> IO VCanvas
toolOp :: ToolOp
data ToolContext Source
ToolContext: The way a tool should be applied depends on where it is being used
Constructors
TCWorkspace
TCCallFrame CanvFrame
TCEditFrame CanvFrame
TCExprNode
type CanvasToolOp = VCanvas -> ToolContext -> [Modifier] -> Double -> Double -> IO VCanvasSource
type ToolOp = VPUI -> WinId -> ToolContext -> [Modifier] -> Double -> Double -> IO VPUISource
ToolOp a is intended for a = VPUIWindow or VCanvas type ToolOp a = VPUI -> a -> ToolContext -> [Modifier] -> Double -> Double -> IO a
toToolOpVW :: CanvasToolOp -> ToolOpSource
A helper for making toolOps from actions on VCanvas
data Workspace Source
Constructors
Workspace
wsBox :: VBoxcontainer of the rest
wsCanvas :: VCanvasthe canvas
wsButtonBar :: HBox
wsStatusbar :: Statusbar
data FunctionEditor Source
Constructors
FunctionEditor
fedWindow :: Window
fedWinTitle :: String
fedFunction :: Function
fedCanvas :: VCanvas
fedFunctionName :: FunctionEditor -> StringSource
data VCanvas Source
A canvas that can display multiple boxes representing expressions or function definitions or calls
Constructors
VCanvas
vcLayout :: GtkLayout
vcStyle :: Style
vcGraph :: WGraph
vcFrames :: [CanvFrame]
vcSize :: Size
vcMousePos :: (Double, Double)
vcTool :: Maybe Tool
vcActive :: Maybe Node
vcSelected :: Maybe Selection
vcDragging :: Maybe Dragging
data Selection Source
Constructors
SelectionNode
selNode :: Node
SelectionInlet
selNode :: Node
selInEdge :: WEdge
SelectionOutlet
selNode :: Node
selOutEdge :: WEdge
show/hide Instances
data Dragging Source
A Dragging keeps track of the object (node) being dragged and the current mouse position.
Constructors
Dragging
draggingNode :: Node
draggingPosition :: Position
show/hide Instances
Produced by Haddock version 2.6.1