chatty-utils-0.7.3.5: Some utilities every serious chatty-based application may need.
Safe HaskellSafe
LanguageHaskell2010

Data.Chatty.Graph

Description

Provides a general graph.

Synopsis

Documentation

newtype NodeId Source #

Phantom type for a node ID

Constructors

NodeId Int 

Instances

Instances details
Eq NodeId Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

(==) :: NodeId -> NodeId -> Bool #

(/=) :: NodeId -> NodeId -> Bool #

Ord NodeId Source # 
Instance details

Defined in Data.Chatty.Graph

Show NodeId Source # 
Instance details

Defined in Data.Chatty.Graph

Indexable (Node a) NodeId (Node a) Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

indexOf :: Node a -> NodeId Source #

valueOf :: Node a -> Node a Source #

data Graph a b c Source #

A general graph

Constructors

Graph 

Fields

Instances

Instances details
None (Graph a b c) Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

none :: Graph a b c Source #

data Node a Source #

A node for the graph

Constructors

Node 

Fields

Instances

Instances details
Show a => Show (Node a) Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

showsPrec :: Int -> Node a -> ShowS #

show :: Node a -> String #

showList :: [Node a] -> ShowS #

Indexable (Node a) NodeId (Node a) Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

indexOf :: Node a -> NodeId Source #

valueOf :: Node a -> Node a Source #

data Edge b c Source #

An edge for the graph

Constructors

Edge 

Fields

Instances

Instances details
Show b => Show (Edge b c) Source # 
Instance details

Defined in Data.Chatty.Graph

Methods

showsPrec :: Int -> Edge b c -> ShowS #

show :: Edge b c -> String #

showList :: [Edge b c] -> ShowS #

incId :: NodeId -> NodeId Source #

Increment a NodeId

emptyGraph :: Graph a b c Source #

An empty graph

addNode :: a -> Graph a b c -> Graph a b c Source #

Add a node to the graph

addNode' :: a -> Graph a b c -> (NodeId, Graph a b c) Source #

Add a node to the graph and also return its ID

addNodes :: [a] -> Graph a b c -> Graph a b c Source #

Add a bunch of nodes

addNodes' :: [a] -> Graph a b c -> ([NodeId], Graph a b c) Source #

Add a bunch of nodes and also return their IDs

allNodes :: Graph a b c -> [Node a] Source #

Return all nodes

rootNode :: Graph a b c -> NodeId Source #

Return the node in the AVL tree's root

addEdge :: NodeId -> NodeId -> Int -> b -> c -> Graph a b c -> Graph a b c Source #

Add a unidirectional edge to the graph (provide both nodes, a weight and a label)

addEdge' :: Edge b c -> Graph a b c -> Graph a b c Source #

Add a unidirectional edge to the graph (provide the Edge)

addMutualEdge :: NodeId -> NodeId -> Int -> b -> c -> Graph a b c -> Graph a b c Source #

Add a bidirectional edge to the graph (provide both nodes, a weight and a label)

addEdges :: [(NodeId, NodeId, Int, b, c)] -> Graph a b c -> Graph a b c Source #

Add a bunch of edges unidirectionally (provide both nodes, a weight and a label)

addEdges' :: [Edge b c] -> Graph a b c -> Graph a b c Source #

Add a bunch of edges unidirectionally (provide the Edges)

addMutualEdges :: [(NodeId, NodeId, Int, b, c)] -> Graph a b c -> Graph a b c Source #

Add a bunch of edges bidirectionally (provide both nodes, a weight and a label)

getNode :: NodeId -> Graph a b c -> a Source #

Get the node's content from its ID

getNode' :: NodeId -> Graph a b c -> Node a Source #

Get the Node object from its ID

setNode :: NodeId -> a -> Graph a b c -> Graph a b c Source #

Set the node's content by its ID

markNode :: NodeId -> Graph a b c -> Graph a b c Source #

Mark a node by its ID

followEdge :: Eq b => NodeId -> b -> Graph a b c -> Maybe NodeId Source #

Follow an edge by its source node and label

queryEdge :: Eq b => NodeId -> b -> Graph a b c -> Maybe c Source #

Query an edge's content

listEdges :: NodeId -> Graph a b c -> [(b, c, NodeId)] Source #

List all edges from the given node