sifflet-lib-1.0: Library of modules shared by sifflet and its tests and its exporters.Source codeContentsIndex
Sifflet.Data.WGraph
Synopsis
data WNode
= WSimple (LayoutNode ExprNode)
| WFrame Node
data WEdge = WEdge Int
type WGraph = Gr WNode WEdge
wgraphNew :: WGraph
grInsertNode :: DynGraph g => g n e -> n -> (g n e, Node)
grRemoveNode :: DynGraph g => g n e -> Node -> g n e
connectToFrame :: Node -> Node -> WGraph -> WGraph
grConnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> WGraph
grDisconnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> Bool -> WGraph
grAddGraph :: DynGraph g => g n e -> g n e -> g n e
grExtractExprTree :: WGraph -> Node -> Tree ExprNode
grExtractLayoutNode :: WGraph -> Node -> LayoutNode ExprNode
grExtractLayoutTree :: WGraph -> Node -> TreeLayout ExprNode
wlab :: WGraph -> Node -> WNode
llab :: WGraph -> Node -> LayoutNode ExprNode
nodeExprNode :: WGraph -> Node -> ExprNode
nodeText :: WGraph -> Node -> String
nodeValue :: WGraph -> Node -> EvalResult
nodeBBox :: WGraph -> Node -> BBox
nodePosition :: WGraph -> Node -> Position
nodeInputValues :: WGraph -> Node -> EvalResult
nodeAllChildren :: WGraph -> Node -> [Node]
nodeSimpleChildren :: WGraph -> Node -> [Node]
nodeFrameChildren :: WGraph -> Node -> [Node]
nodeAllSimpleDescendants :: WGraph -> Node -> [Node]
nodeProperSimpleDescendants :: WGraph -> Node -> [Node]
nodeIsSimple :: WGraph -> Node -> Bool
nodeIsOpen :: WGraph -> Node -> Bool
nodeContainerFrameNode :: WGraph -> Node -> Node
nodeParent :: WGraph -> Node -> Maybe Node
grUpdateFLayout :: WGraph -> [Node] -> FunctoidLayout -> WGraph
grUpdateTreeLayout :: WGraph -> Node -> TreeLayout ExprNode -> WGraph
translateNodes :: Double -> Double -> WGraph -> [Node] -> WGraph
translateNode :: Double -> Double -> WGraph -> Node -> WGraph
grRelabelNode :: DynGraph g => g a b -> Node -> a -> g a b
translateTree :: Double -> Double -> WGraph -> Node -> WGraph
functoidParts :: Functoid -> WGraph -> Node -> Functoid
functionToParts :: Function -> WGraph -> Node -> Functoid
Documentation
data WNode Source
Two kinds of WNodes: A WSimple node represents a node in an expression tree, e.g., if, + A WFrame node represents a panel or frame that displays an expression tree, function call, or something similar.
Constructors
WSimple (LayoutNode ExprNode)
WFrame Node
show/hide Instances
data WEdge Source
Constructors
WEdge Int
show/hide Instances
type WGraph = Gr WNode WEdgeSource
A WGraph consists of WNodes with (sort of) Int-labled edges; the edge labels serve to order the children of a node.
wgraphNew :: WGraphSource
grInsertNode :: DynGraph g => g n e -> n -> (g n e, Node)Source
Insert new node with given label into graph, without any new edges; return the new graph and the new node (number)
grRemoveNode :: DynGraph g => g n e -> Node -> g n eSource
Remove a node from the graph; return the updated graph.
connectToFrame :: Node -> Node -> WGraph -> WGraphSource
grConnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> WGraphSource

Connect parent to child, using inlet as the order of the child (0, 1, ...). outlet is ignored, since there is only outlet 0. As rendered, the parent's inlet-th inlet will have a line to the child's outlet-th outlet. This is achieved by inserting a labeled edge (parent, child, inlet) and clearing any incompatible edge. The incompatibles are: a. from same parent on same inlet to a different child. b. from the same parent on a different inlet to the same child. c. from same child (on same outlet) to a different parent.

NOTE: This is confusing, because, from the data flow perspective, data flows OUT of the child INTO the parent, but from the tree in graph perspective, links are directed OUT of the parent INTO the child. So beware!

grDisconnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> Bool -> WGraphSource
Removes a link between parent and child where the edge was labeled inlet (order of child). Ignores outlet, which should always be 0. If child is not the inlet-th child of parent, well, this is an error, but grDisconnect ignores it. If toFrameP is true, the child node is reconnected as a child to its frame
grAddGraph :: DynGraph g => g n e -> g n e -> g n eSource
grExtractExprTree :: WGraph -> Node -> Tree ExprNodeSource
Extract from a graph the expression with root node n, returning a Tree of ExprNode. Use only the WSimple nodes of the graph (and n had better be one).
grExtractLayoutNode :: WGraph -> Node -> LayoutNode ExprNodeSource
Extract just the single tree layout node of the given graph node
grExtractLayoutTree :: WGraph -> Node -> TreeLayout ExprNodeSource
Extract the tree layout (tree) descended from the given root node
wlab :: WGraph -> Node -> WNodeSource

Finding characteristics of the WNodes in a graph It is an implicit error if there is no label for the node

wlab is like lab with no Maybe: the node *must* have a label

llab :: WGraph -> Node -> LayoutNode ExprNodeSource
llab is the tree layout node of a WSimple node
nodeExprNode :: WGraph -> Node -> ExprNodeSource
The ExprNode represented by the graph node
nodeText :: WGraph -> Node -> StringSource
The repr of the node's value
nodeValue :: WGraph -> Node -> EvalResultSource
The result of an evaluated node in an expression tree
nodeBBox :: WGraph -> Node -> BBoxSource
The node's BBox
nodePosition :: WGraph -> Node -> PositionSource
nodeInputValues :: WGraph -> Node -> EvalResultSource
nodeAllChildren :: WGraph -> Node -> [Node]Source
Finding the children (nodes, numbers) of a node in a graph : all children, only WSimple-labeled children, only WFrame-labeled children When constructing the graph, ordered children of a tree node get graph node numbers in ascending order; therefore, sorting the graph nodes gives back the original order of children in the tree (plus WFrames that are added later, and those should always be after the simple children)
nodeSimpleChildren :: WGraph -> Node -> [Node]Source
nodeFrameChildren :: WGraph -> Node -> [Node]Source
nodeAllSimpleDescendants :: WGraph -> Node -> [Node]Source
nodeProperSimpleDescendants :: WGraph -> Node -> [Node]Source
nodeIsSimple :: WGraph -> Node -> BoolSource
nodeIsOpen :: WGraph -> Node -> BoolSource
An open node has a WFrame-labeled child
nodeContainerFrameNode :: WGraph -> Node -> NodeSource
The graph node of the frame that contains the given node
nodeParent :: WGraph -> Node -> Maybe NodeSource
The parent (if any) of a node
grUpdateFLayout :: WGraph -> [Node] -> FunctoidLayout -> WGraphSource
grUpdateTreeLayout :: WGraph -> Node -> TreeLayout ExprNode -> WGraphSource
Replace the tree embedded in graph g with root n, with a new tree.
translateNodes :: Double -> Double -> WGraph -> [Node] -> WGraphSource
translateNode :: Double -> Double -> WGraph -> Node -> WGraphSource
grRelabelNode :: DynGraph g => g a b -> Node -> a -> g a bSource
Replace the label of a node in a graph
translateTree :: Double -> Double -> WGraph -> Node -> WGraphSource
Translate the nodes forming a tree with the given root
functoidParts :: Functoid -> WGraph -> Node -> FunctoidSource
Get the parts of a Functoid. See note on functionToParts (just below). Seems to be unused ***
functionToParts :: Function -> WGraph -> Node -> FunctoidSource
Convert a function to its parts. COULDN'T THIS BE DONE USING the function's implementation, and not need to use the graph? Then this could go in Functoid.hs without circular import between it and WGraph
Produced by Haddock version 2.6.1