layered-graph-drawing-0.2.0.0: Layered Graph Drawing after Sugiyama
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graph.CommonGraph

Synopsis

Documentation

type UINode = Word32 Source #

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 CGraph n e = Graph n [e] Source #

A shorthand for multiple edges

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

type X = Int Source #

type Y = Int Source #

type YBlock = (Y, [(UINode, X)]) Source #

type YBlocks = (Y, [[(UINode, X)]]) Source #

type YBlockLines = [(Y, [[(UINode, X)]])] Source #

data EdgeType Source #

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

Constructors

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

Instances details
Generic EdgeType Source # 
Instance details

Defined in Graph.CommonGraph

Associated Types

type Rep EdgeType :: Type -> Type #

Methods

from :: EdgeType -> Rep EdgeType x #

to :: Rep EdgeType x -> EdgeType #

Show EdgeType Source # 
Instance details

Defined in Graph.CommonGraph

Eq EdgeType Source # 
Instance details

Defined in Graph.CommonGraph

Ord EdgeType Source # 
Instance details

Defined in Graph.CommonGraph

type Rep EdgeType Source # 
Instance details

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)))

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

Methods

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 #

isFunction Source #

Arguments

:: EdgeClass e 
=> CGraph n e 
-> UINode 
-> Bool

This special for displaying function networks

isMainArg Source #

Arguments

:: EdgeClass e 
=> CGraph n e 
-> UINode 
-> Bool

This special for displaying function networks

isSubLabel :: n -> Bool Source #

isArgLabel Source #

Arguments

:: 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 Channel = Int 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

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

type BoxId Source #

Arguments

 = Word32

I use the node of the function that is exploded as the box id

data LayerFeatures Source #

Constructors

LayerFeatures 

Fields

  • layer :: Nesting

    Graphs that are inside graphs get a higher nesting value (I use this to make every new layer a little bit darker). This is used to calculate the subgraph windows

  • boxId :: Maybe BoxId

    There can be several subgraphs in a graph, that are surrounded by a box. This value has to be unique for every box

  • border :: Maybe Border

    Set the css values (border, boxshadow)

Instances

Instances details
FromJSON LayerFeatures Source # 
Instance details

Defined in Graph.CommonGraph

ToJSON LayerFeatures Source # 
Instance details

Defined in Graph.CommonGraph

Generic LayerFeatures Source # 
Instance details

Defined in Graph.CommonGraph

Associated Types

type Rep LayerFeatures :: Type -> Type #

Show LayerFeatures Source # 
Instance details

Defined in Graph.CommonGraph

type Rep LayerFeatures Source # 
Instance details

Defined in Graph.CommonGraph

type Rep LayerFeatures = D1 ('MetaData "LayerFeatures" "Graph.CommonGraph" "layered-graph-drawing-0.2.0.0-LvhSsmMAZpHB0FFE60zTo3" 'False) (C1 ('MetaCons "LayerFeatures" 'PrefixI 'True) (S1 ('MetaSel ('Just "layer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Nesting) :*: (S1 ('MetaSel ('Just "boxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe BoxId)) :*: S1 ('MetaSel ('Just "border") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Border)))))

data Border Source #

Instances

Instances details
FromJSON Border Source # 
Instance details

Defined in Graph.CommonGraph

ToJSON Border Source # 
Instance details

Defined in Graph.CommonGraph

Generic Border Source # 
Instance details

Defined in Graph.CommonGraph

Associated Types

type Rep Border :: Type -> Type #

Methods

from :: Border -> Rep Border x #

to :: Rep Border x -> Border #

Show Border Source # 
Instance details

Defined in Graph.CommonGraph

type Rep Border Source # 
Instance details

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 #

myHead :: Int -> [a] -> a Source #

myLast :: Int -> [a] -> a Source #

vHead :: Unbox a => Int -> Vector a -> a Source #

rmdups :: Ord a => [a] -> [a] Source #

Orphan instances

EdgeClass e => EdgeAttribute [e] Source # 
Instance details

Methods

fastEdgeAttr :: [e] -> Word8 #

edgeFromAttr :: Map Word8 [e] #

show_e :: Maybe [e] -> String #

bases :: [e] -> [Edge8] #