intmap-graph-1.3.0.0: A graph library that allows to explore edges after their type

Copyright(C) 2019 Tillmann Vogt
LicenseBSD-style (see the file LICENSE)
MaintainerTillmann Vogt <tillk.vogt@gmail.com>
Stabilitystable
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

Graph.IntMap

Contents

Description

The general idea of this library is that edges can put into classes. As it is faster to lookup a 32/64-bit integer in an intmap than a tuple of integers in a Data.Map-map, we construct a graph by putting a node (24 bit) and its class (8 bit) of adjacent nodes into a 32 bit integer. We need to restrict it to 32 bit, because Javascript (and therefore GHCJS) only has 32 bit integers. If you want to use this library outside of a browser, use 64 bit and set the bool arg of some functions to False. Then there are 32 bits for the node and 32 bits for the edge class.

Synopsis

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

data Graph nl el Source #

The edges are enumerated, because sometimes the edge attrs are not continuous and it is impossible to try all possible 32 bit attrs

Constructors

Graph 

Fields

Instances
(EdgeAttribute el, Eq el, Eq nl) => Eq (Graph nl el) Source # 
Instance details

Defined in Graph.IntMap

Methods

(==) :: Graph nl el -> Graph nl el -> Bool #

(/=) :: Graph nl el -> Graph nl el -> Bool #

(EdgeAttribute el, Show nl, ExtractNodeType nl, Show el, Enum nl) => Show (Graph nl el) Source # 
Instance details

Defined in Graph.IntMap

Methods

showsPrec :: Int -> Graph nl el -> ShowS #

show :: Graph nl el -> String #

showList :: [Graph nl el] -> ShowS #

Generic (Graph nl el) Source # 
Instance details

Defined in Graph.IntMap

Associated Types

type Rep (Graph nl el) :: Type -> Type #

Methods

from :: Graph nl el -> Rep (Graph nl el) x #

to :: Rep (Graph nl el) x -> Graph nl el #

type Rep (Graph nl el) Source # 
Instance details

Defined in Graph.IntMap

type Rep (Graph nl el)

class ExtractNodeType nl where Source #

if a node label is complicated, specify a short string to understand its type

Methods

extractNodeType :: nl -> String Source #

type Edge = (Node, Node) Source #

A tuple of nodes

newtype Edge8 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

Constructors

Edge8 Word8 
Instances
Show Edge8 Source # 
Instance details

Defined in Graph.IntMap

Methods

showsPrec :: Int -> Edge8 -> ShowS #

show :: Edge8 -> String #

showList :: [Edge8] -> ShowS #

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

adjustNode :: EdgeAttribute el => (nl -> nl) -> Node -> Graph nl el -> Graph nl el Source #

Adjust a node label of a specific node. When the node is not a member of the graph, the original graph is returned.

adjustEdge :: EdgeAttribute el => (el -> el) -> Edge -> Graph nl el -> Graph nl el Source #

Adjust an edge label of a specific edge. When the edge is not a member of the graph, the original graph is returned.

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

isNull :: Graph a1 a2 -> Bool Source #

Are the node-/edge-maps of the graph all empty?

nodes :: Graph a el -> [Key] Source #

The word32 keys of the node labels

edges :: Graph nl a -> [(Node, Node)] Source #

List of (Node, Node)

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

buildWord64 :: Word32 -> Word32 -> Word Source #

Concatenate two Word32 to a Word (64 bit)

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

buildWord32 :: Word32 -> Word8 -> Word32 Source #

Nodes can use 24 bits, edges 8 bits

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

Displaying in hex for debugging

showHex :: Word -> String Source #

Display a 64 bit word so that we can see the bits better

showHex32 :: Word32 -> String Source #

Display a 32 bit word so that we can see the bits better