Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data WNode
- = WSimple (LayoutNode ExprNode)
- | WFrame Node
- newtype WEdge = WEdge Int
- type WGraph = Gr WNode WEdge
- type WContext = Context WNode WEdge
- wgraphNew :: WGraph
- isWSimple :: WNode -> Bool
- isWFrame :: WNode -> Bool
- 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
- grInletIsConnected :: WGraph -> Node -> WEdge -> Bool
- 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
- graphOrphans :: Graph graph => graph a b -> [Node]
- adoptChildren :: WGraph -> Node -> [Node] -> WGraph
- nextNode :: DynGraph g => g n e -> Node
- nodeAllChildren :: WGraph -> Node -> [Node]
- nodeSimpleChildren :: WGraph -> Node -> [Node]
- allDescendants :: Graph graph => graph a b -> 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
- printWGraph :: WGraph -> IO ()
- 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
- nfilter :: (Node -> Bool) -> Gr v e -> Gr v e
Documentation
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.
type WGraph = Gr WNode WEdge Source
A WGraph consists of WNodes with (sort of) Int-labled edges; the edge labels serve to order the children of a node.
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 e Source
Remove a node from the graph; return the updated graph.
grConnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> WGraph Source
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!
grInletIsConnected :: WGraph -> Node -> WEdge -> Bool Source
Tell whether a parent node already has a child connected on the given inlet.
grDisconnect :: WGraph -> Node -> WEdge -> Node -> WEdge -> Bool -> WGraph Source
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 e Source
grExtractExprTree :: WGraph -> Node -> Tree ExprNode Source
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 ExprNode Source
Extract just the single tree layout node of the given graph node
grExtractLayoutTree :: WGraph -> Node -> TreeLayout ExprNode Source
Extract the tree layout (tree) descended from the given root node
wlab :: WGraph -> Node -> WNode Source
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
nodeExprNode :: WGraph -> Node -> ExprNode Source
The ExprNode represented by the graph node
nodeValue :: WGraph -> Node -> EvalResult Source
The result of an evaluated node in an expression tree
nodePosition :: WGraph -> Node -> Position Source
nodeInputValues :: WGraph -> Node -> EvalResult Source
graphOrphans :: Graph graph => graph a b -> [Node] Source
Find all parentless nodes in a graph
adoptChildren :: WGraph -> Node -> [Node] -> WGraph Source
Connect the given children to a new parent
nextNode :: DynGraph g => g n e -> Node Source
Next node number which may be used in a graph. For an empty graph, this is 0. Otherwise it is 1 + the maximum node in the graph.
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
allDescendants :: Graph graph => graph a b -> Node -> [Node] Source
All (proper and improper) descendants of a node in a graph
nodeFrameChildren :: WGraph -> Node -> [Node] Source
nodeAllSimpleDescendants :: WGraph -> Node -> [Node] Source
nodeProperSimpleDescendants :: WGraph -> Node -> [Node] Source
nodeIsSimple :: WGraph -> Node -> Bool Source
nodeIsOpen :: WGraph -> Node -> Bool Source
An open node has a WFrame-labeled child
nodeContainerFrameNode :: WGraph -> Node -> Node Source
The graph node of the frame that contains the given node
grUpdateFLayout :: WGraph -> [Node] -> FunctoidLayout -> WGraph Source
grUpdateTreeLayout :: WGraph -> Node -> TreeLayout ExprNode -> WGraph Source
Replace the tree embedded in graph g with root n, with a new tree.
printWGraph :: WGraph -> IO () Source
Print a description of the WGraph
grRelabelNode :: DynGraph g => g a b -> Node -> a -> g a b Source
Replace the label of a node in a graph
translateTree :: Double -> Double -> WGraph -> Node -> WGraph Source
Translate the nodes forming a tree with the given root
functoidParts :: Functoid -> WGraph -> Node -> Functoid Source
Get the parts of a Functoid. See note on functionToParts (just below). Seems to be unused ***