Copyright | (C) 2019 Tillmann Vogt |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Tillmann Vogt <tillk.vogt@gmail.com> |
Stability | provisional |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class EdgeAttribute el where
- fastEdgeAttr :: el -> Word8
- edgeFromAttr :: Map Word8 el
- show_e :: Maybe el -> String
- bases :: el -> [Edge8]
- data Graph nl el = Graph {
- outgoingNodes :: IntMap (Set Node)
- incomingNodes :: IntMap (Set Node)
- nodeLabels :: IntMap nl
- edgeLabels :: Map (Node, Node) el
- is32BitInt :: Bool
- showEdge :: Map Word8 el
- class ExtractNodeType nl where
- extractNodeType :: nl -> String
- type Edge = (Node, Node)
- newtype Edge8 = Edge8 Word8
- empty :: EdgeAttribute el => Graph nl el
- fromLists :: (EdgeAttribute el, Enum nl, Show nl, Show el) => Bool -> [(Node, nl)] -> [((Node, Node), el)] -> [((Node, Node), el)] -> Graph nl el
- fromMaps :: (EdgeAttribute el, Show nl, Show el, Enum nl) => Bool -> IntMap nl -> Map (Node, Node) el -> Map (Node, Node) el -> Bool -> Graph nl el
- insertNode :: EdgeAttribute el => Node -> nl -> Graph nl el -> Graph nl el
- insertNodes :: EdgeAttribute el => [(Node, nl)] -> Graph nl el -> Graph nl el
- insertEdge :: EdgeAttribute el => Maybe Bool -> Edge -> el -> Graph nl el -> Graph nl el
- insertEdges :: EdgeAttribute el => Maybe Bool -> [(Edge, el)] -> Graph nl el -> Graph nl el
- union :: Graph nl el -> Graph nl el -> Graph nl el
- mapNode :: EdgeAttribute el => (nl0 -> nl1) -> Graph nl0 el -> Graph nl1 el
- mapNodeWithKey :: EdgeAttribute el => (Key -> nl0 -> nl1) -> Graph nl0 el -> Graph nl1 el
- deleteNode :: (EdgeAttribute el, Show nl, Show el, Enum nl) => el -> Node -> Graph nl el -> Graph nl el
- deleteNodes :: (Foldable t, EdgeAttribute el, Show nl, Show el, Enum nl) => el -> t Node -> Graph nl el -> Graph nl el
- deleteEdge :: EdgeAttribute el => Maybe Bool -> Edge -> Graph nl el -> Graph nl el
- deleteEdges :: (Foldable t, EdgeAttribute el) => Maybe Bool -> t Edge -> Graph nl el -> Graph nl el
- isNull :: Graph a1 a2 -> Bool
- nodes :: Graph a el -> [Key]
- edges :: Graph nl a -> [(Node, Node)]
- lookupNode :: (Show nl, EdgeAttribute el) => Node -> Graph nl el -> Maybe nl
- lookupEdge :: (EdgeAttribute el, Show el) => Edge -> Graph nl el -> Maybe el
- adjacentNodesByAttr :: EdgeAttribute el => Graph nl el -> Bool -> Node -> Edge8 -> Vector Node
- adjacentNodes :: EdgeAttribute el => Graph nl el -> Node -> el -> [Node]
- parents :: EdgeAttribute el => Graph nl el -> Node -> el -> Vector Node
- children :: EdgeAttribute el => Graph nl el -> Node -> el -> Vector Node
- buildWord64 :: Word32 -> Word32 -> Word
- extractFirstWord32 :: Word -> Word32
- extractSecondWord32 :: Word -> Word32
- buildWord32 :: Word32 -> Word8 -> Word32
- extractFirstWord24 :: Word32 -> Word32
- extractSecondWord8 :: Word32 -> Word8
- showHex :: Word -> String
- showHex32 :: Word32 -> String
Documentation
class EdgeAttribute el where Source #
Convert a complex edge label to an attribute with 8 bits How to do this depends on which edges have to be filtered fast
The edges are enumerated, because sometimes the edge attrs are not continuous and it is impossible to try all possible 32 bit attrs
Graph | |
|
class ExtractNodeType nl where Source #
if a node label is complicated, specify a short string to understand its type
extractNodeType :: nl -> String Source #
In Javascript there are only 32 bit integers. If we want to squeeze a node and an edge into this we use 24 bits for the node and 8 bits for the edge
Construction
empty :: EdgeAttribute el => Graph nl el Source #
Generate an empty graph with 32 bit node-edges (24 bit for the node) that can be used with code that ghcjs compiled to javascript
fromLists :: (EdgeAttribute el, Enum nl, Show nl, Show el) => Bool -> [(Node, nl)] -> [((Node, Node), el)] -> [((Node, Node), el)] -> Graph nl el Source #
Construct a graph from a list of nodes, undirected edges and directed edges, the bool has to be true it uses 32 bit integers, if false it uses 64 bit integers
fromMaps :: (EdgeAttribute el, Show nl, Show el, Enum nl) => Bool -> IntMap nl -> Map (Node, Node) el -> Map (Node, Node) el -> Bool -> Graph nl el Source #
Construct a graph from a node map, undirected edges map and directed edges map, b = True means 32 bit integers
insertNode :: EdgeAttribute el => Node -> nl -> Graph nl el -> Graph nl el Source #
Insert node with node label
insertNodes :: EdgeAttribute el => [(Node, nl)] -> Graph nl el -> Graph nl el Source #
Insert nodes with their label
insertEdge :: EdgeAttribute el => Maybe Bool -> Edge -> el -> Graph nl el -> Graph nl el Source #
Inserting an edge If maybeIsBack is Nothing only one directed is edge from n0 to n1 is inserted If maybeIsBack is Just then a second directed edge from n1 to n0 is inserted isBack = True means an opposite directed edge that can be explored in both directions isBack = False means a undirected edge that also can be explored in both directions
insertEdges :: EdgeAttribute el => Maybe Bool -> [(Edge, el)] -> Graph nl el -> Graph nl el Source #
Inserting an edge If maybeIsBack is Nothing only one directed is edge from n0 to n1 is inserted If maybeIsBack is Just then a second directed edge from n1 to n0 is inserted isBack = True means an opposite directed edge that can be explored in both directions isBack = False means a undirected edge that also can be explored in both directions
union :: Graph nl el -> Graph nl el -> Graph nl el Source #
Makes a union over all components of the graph
Traversal
mapNode :: EdgeAttribute el => (nl0 -> nl1) -> Graph nl0 el -> Graph nl1 el Source #
Mapping a function over the node labels
mapNodeWithKey :: EdgeAttribute el => (Key -> nl0 -> nl1) -> Graph nl0 el -> Graph nl1 el Source #
Mapping a function over the node labels with node key
Deletion
deleteNode :: (EdgeAttribute el, Show nl, Show el, Enum nl) => el -> Node -> Graph nl el -> Graph nl el Source #
Delete node with its nodelabel and also all outgoing and incoming edges with their edgeLabels
deleteNodes :: (Foldable t, EdgeAttribute el, Show nl, Show el, Enum nl) => el -> t Node -> Graph nl el -> Graph nl el Source #
Delete nodes with their label
deleteEdge :: EdgeAttribute el => Maybe Bool -> Edge -> Graph nl el -> Graph nl el Source #
"deleteEdge (n0, n1) graph" deletes the edgelabel of (n0,n1) and the nodeEdge that points from n0 to n1 If maybeIsBack is Just then a second directed edge from n1 to n0 is deleted isBack = True means an opposite directed edge that can be explored in both directions isBack = False means a undirected edge that also can be explored in both directions
deleteEdges :: (Foldable t, EdgeAttribute el) => Maybe Bool -> t Edge -> Graph nl el -> Graph nl el Source #
Delete a list of (Node,Node) edges from the graph
Query
lookupNode :: (Show nl, EdgeAttribute el) => Node -> Graph nl el -> Maybe nl Source #
The nodelabel of the given node
lookupEdge :: (EdgeAttribute el, Show el) => Edge -> Graph nl el -> Maybe el Source #
The edgelabel of the given edge of type (Node, Node)
adjacentNodesByAttr :: EdgeAttribute el => Graph nl el -> Bool -> Node -> Edge8 -> Vector Node Source #
The list of adjacent edges can be divided with 8 bit attributes and all edges with a certain attribute selected
adjacentNodes :: EdgeAttribute el => Graph nl el -> Node -> el -> [Node] Source #
Looking at all incoming and outgoing edges we get all adjacent nodes
parents :: EdgeAttribute el => Graph nl el -> Node -> el -> Vector Node Source #
Following the incoming edges
children :: EdgeAttribute el => Graph nl el -> Node -> el -> Vector Node Source #
Following the outgoing edges
Bit Operations
extractFirstWord32 :: Word -> Word32 Source #
Extract the first 32 bit of a 64 bit word
extractSecondWord32 :: Word -> Word32 Source #
Extract the second 32 bit of a 64 bit word
extractFirstWord24 :: Word32 -> Word32 Source #
Extract the first 24 bit of a 32 bit word
extractSecondWord8 :: Word32 -> Word8 Source #
Extract the last 8 bit of a 32 bit word