Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- type UINode = Word32
- type CGraph n e = Graph n [e]
- type CGraphL n e = (Graph n [e], Map UINode (X, Y), YBlockLines)
- type X = Int
- type Y = Int
- type YBlock = (Y, [(UINode, X)])
- type YBlocks = (Y, [[(UINode, X)]])
- type YBlockLines = [(Y, [[(UINode, X)]])]
- data EdgeType
- type GraphMoveX = Int
- type Column = (GraphMoveX, [UINode])
- class NodeClass n where
- isDummy :: EdgeClass e => CGraph n e -> UINode -> Bool
- isCase :: EdgeClass e => CGraph n e -> UINode -> Bool
- isConnNode :: EdgeClass e => CGraph n e -> UINode -> Bool
- isFunction :: EdgeClass e => CGraph n e -> UINode -> Bool
- isMainArg :: EdgeClass e => CGraph n e -> UINode -> Bool
- isSubLabel :: n -> Bool
- isArgLabel :: n -> Bool
- subLabels :: n -> Int
- connectionNode :: n
- dummyNode :: Int -> n
- nestingFeatures :: n -> Maybe LayerFeatures
- updateLayer :: Maybe LayerFeatures -> n -> n
- verticalNumber :: n -> Maybe Int
- type ChannelNrIn = Maybe Channel
- type ChannelNrOut = Channel
- type Channel = Int
- class EdgeClass e where
- dummyEdge :: ChannelNrIn -> ChannelNrOut -> e
- standard :: EdgeType -> e
- edgeType :: e -> EdgeType
- channelNrIn :: e -> ChannelNrIn
- channelNrOut :: e -> ChannelNrOut
- vertBit :: Word8
- virtBit :: Word8
- sepBit :: Word8
- childrenNoVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32
- parentsNoVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32
- parentsNoVirtual :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32
- parentsNoVerticalOrVirtual :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32
- childrenVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32
- parentsVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32
- childrenSeparating :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32
- verticallyConnectedNodes :: EdgeClass e => CGraph n e -> UINode -> [UINode]
- type Nesting = Int
- type BoxId = Word32
- data LayerFeatures = LayerFeatures {}
- lb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- rb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- tb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- bb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- ltb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- rtb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- lbb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- rbb :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- mid :: Nesting -> Maybe BoxId -> Maybe LayerFeatures
- data Border
- myFromJust :: Int -> Maybe a -> a
- myHead :: Int -> [a] -> a
- myLast :: Int -> [a] -> a
- vHead :: Unbox a => Int -> Vector a -> a
- rmdups :: Ord a => [a] -> [a]
Documentation
Word32 is used for the node because graph drawing is most likely used in a browser with javascript and the ints there have 32 bits, and this is more than enough
type CGraphL n e = (Graph n [e], Map UINode (X, Y), YBlockLines) Source #
Layouted Graph, assign a (x,y) position to every node also returning the blocks in yCoordinateassignment, the final layouting has to be done in javascript
Nodes could be grouped into lists. But as a lof of algorithms walk through the graph, it is more convenient to see for example if a node is connected vertically than to see if it is part of a list of vertically grouped nodes. This is of course a matter of taste and there probably good arguments to put nodes in lists
NormalEdge | |
VerticalEdge | When having options, they appear continuously in one column. We mark this in the graph with vertical edges from the first option to the second and so on |
VirtualHorEdge | Virtual edges are not displayed but used to put several graphs in a row for layouting and navigation with the keyboard |
SeparatingEdge | To connect graph components that are separate |
Instances
Generic EdgeType Source # | |
Show EdgeType Source # | |
Eq EdgeType Source # | |
Ord EdgeType Source # | |
Defined in Graph.CommonGraph | |
type Rep EdgeType Source # | |
Defined in Graph.CommonGraph type Rep EdgeType = D1 ('MetaData "EdgeType" "Graph.CommonGraph" "layered-graph-drawing-0.2.0.0-LvhSsmMAZpHB0FFE60zTo3" 'False) ((C1 ('MetaCons "NormalEdge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VerticalEdge" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VirtualHorEdge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SeparatingEdge" 'PrefixI 'False) (U1 :: Type -> Type))) |
type GraphMoveX = Int Source #
type Column = (GraphMoveX, [UINode]) Source #
class NodeClass n where Source #
A type class for the node type, so that an individual node type can be used Some functions had to be introduced that are special for the original purpose. The main reason for not using grapviz was that it became clear that a binding to graphviz does not allow to adjust algorithms easily
isDummy :: EdgeClass e => CGraph n e -> UINode -> Bool Source #
isCase :: EdgeClass e => CGraph n e -> UINode -> Bool Source #
isConnNode :: EdgeClass e => CGraph n e -> UINode -> Bool Source #
isSubLabel :: n -> Bool Source #
:: n | |
-> Bool | This special for displaying function networks |
subLabels :: n -> Int Source #
connectionNode :: n Source #
dummyNode :: Int -> n Source #
nestingFeatures :: n -> Maybe LayerFeatures Source #
updateLayer :: Maybe LayerFeatures -> n -> n Source #
verticalNumber :: n -> Maybe Int Source #
type ChannelNrIn = Maybe Channel Source #
type ChannelNrOut = Channel Source #
A channel (or port) is used if a node has several subfields that are connected separately For example the nth type of a type node
class EdgeClass e where Source #
Edges can are also be implemented individually
dummyEdge :: ChannelNrIn -> ChannelNrOut -> e Source #
standard :: EdgeType -> e Source #
edgeType :: e -> EdgeType Source #
channelNrIn :: e -> ChannelNrIn Source #
channelNrOut :: e -> ChannelNrOut Source #
Grouping edges into classes with non overlapping bits,
For example vertBit = 00000001 = 1, virtBit = 00000010 = 2, sepBit = 00000100 =4, ... Up to 8 bits. This was used to have a superfast lookup with an intmap. Maybe a normal Map with a key (UINode,Word32) would have been easier, with Word32 being the edge type. But this is faster.
Querying nodes that are connected by a certain type of edge
childrenNoVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32 Source #
All children that are connected but without the vertically connected nodes
parentsNoVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32 Source #
All parents that are connected but without the vertically connected nodes
parentsNoVirtual :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32 Source #
All parents that are connected but without the virtual connected nodes
parentsNoVerticalOrVirtual :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32 Source #
All parents that are connected but without the virtual or vertically connected nodes
childrenVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32 Source #
Children that are connected vertically
parentsVertical :: EdgeClass e => Graph n [e] -> Word32 -> Vector Word32 Source #
Parents that are connected vertically
childrenSeparating :: EdgeClass e => CGraph n e -> Word32 -> Vector Word32 Source #
Children that are connected with a separating edge
verticallyConnectedNodes :: EdgeClass e => CGraph n e -> UINode -> [UINode] Source #
Find all vertically connected nodes, by exploring incoming and outgoing vertical edges
Borders of cells
data LayerFeatures Source #
LayerFeatures | |
|
Instances
LeftBorder | |
RightBorder | |
TopBorder | |
BottomBorder | |
LeftTopBorder | |
RightTopBorder | |
LeftBottomBorder | |
RightBottomBorder |
Instances
FromJSON Border Source # | |
Defined in Graph.CommonGraph | |
ToJSON Border Source # | |
Generic Border Source # | |
Show Border Source # | |
type Rep Border Source # | |
Defined in Graph.CommonGraph type Rep Border = D1 ('MetaData "Border" "Graph.CommonGraph" "layered-graph-drawing-0.2.0.0-LvhSsmMAZpHB0FFE60zTo3" 'False) (((C1 ('MetaCons "LeftBorder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightBorder" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TopBorder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BottomBorder" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "LeftTopBorder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightTopBorder" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftBottomBorder" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RightBottomBorder" 'PrefixI 'False) (U1 :: Type -> Type)))) |
Helper functions
myFromJust :: Int -> Maybe a -> a Source #