fgl-5.4.1.1: Martin Erwig's Functional Graph LibrarySource codeContentsIndex
Data.Graph.Inductive.Graph
Contents
General Type Defintions
Node and Edge Types
Types Supporting Inductive Graph View
Graph Type Classes
Operations
Graph Folds and Maps
Graph Projection
Graph Construction and Destruction
Graph Inspection
Context Inspection
Description
Static and Dynamic Inductive Graphs
Synopsis
type Node = Int
type LNode a = (Node, a)
type UNode = LNode ()
type Edge = (Node, Node)
type LEdge b = (Node, Node, b)
type UEdge = LEdge ()
type Adj b = [(b, Node)]
type Context a b = (Adj b, Node, a, Adj b)
type MContext a b = Maybe (Context a b)
type Decomp g a b = (MContext a b, g a b)
type GDecomp g a b = (Context a b, g a b)
type UContext = ([Node], Node, [Node])
type UDecomp g = (Maybe UContext, g)
type Path = [Node]
newtype LPath a = LP [LNode a]
type UPath = [UNode]
class Graph gr where
empty :: gr a b
isEmpty :: gr a b -> Bool
match :: Node -> gr a b -> Decomp gr a b
mkGraph :: [LNode a] -> [LEdge b] -> gr a b
labNodes :: gr a b -> [LNode a]
matchAny :: gr a b -> GDecomp gr a b
noNodes :: gr a b -> Int
nodeRange :: gr a b -> (Node, Node)
labEdges :: gr a b -> [LEdge b]
class Graph gr => DynGraph gr where
(&) :: Context a b -> gr a b -> gr a b
ufold :: Graph gr => (Context a b -> c -> c) -> c -> gr a b -> c
gmap :: DynGraph gr => (Context a b -> Context c d) -> gr a b -> gr c d
nmap :: DynGraph gr => (a -> c) -> gr a b -> gr c b
emap :: DynGraph gr => (b -> c) -> gr a b -> gr a c
nodes :: Graph gr => gr a b -> [Node]
edges :: Graph gr => gr a b -> [Edge]
newNodes :: Graph gr => Int -> gr a b -> [Node]
gelem :: Graph gr => Node -> gr a b -> Bool
insNode :: DynGraph gr => LNode a -> gr a b -> gr a b
insEdge :: DynGraph gr => LEdge b -> gr a b -> gr a b
delNode :: Graph gr => Node -> gr a b -> gr a b
delEdge :: DynGraph gr => Edge -> gr a b -> gr a b
delLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b
insNodes :: DynGraph gr => [LNode a] -> gr a b -> gr a b
insEdges :: DynGraph gr => [LEdge b] -> gr a b -> gr a b
delNodes :: Graph gr => [Node] -> gr a b -> gr a b
delEdges :: DynGraph gr => [Edge] -> gr a b -> gr a b
buildGr :: DynGraph gr => [Context a b] -> gr a b
mkUGraph :: Graph gr => [Node] -> [Edge] -> gr () ()
context :: Graph gr => gr a b -> Node -> Context a b
lab :: Graph gr => gr a b -> Node -> Maybe a
neighbors :: Graph gr => gr a b -> Node -> [Node]
suc :: Graph gr => gr a b -> Node -> [Node]
pre :: Graph gr => gr a b -> Node -> [Node]
lsuc :: Graph gr => gr a b -> Node -> [(Node, b)]
lpre :: Graph gr => gr a b -> Node -> [(Node, b)]
out :: Graph gr => gr a b -> Node -> [LEdge b]
inn :: Graph gr => gr a b -> Node -> [LEdge b]
outdeg :: Graph gr => gr a b -> Node -> Int
indeg :: Graph gr => gr a b -> Node -> Int
deg :: Graph gr => gr a b -> Node -> Int
equal :: (Eq a, Eq b, Graph gr) => gr a b -> gr a b -> Bool
node' :: Context a b -> Node
lab' :: Context a b -> a
labNode' :: Context a b -> LNode a
neighbors' :: Context a b -> [Node]
suc' :: Context a b -> [Node]
pre' :: Context a b -> [Node]
lpre' :: Context a b -> [(Node, b)]
lsuc' :: Context a b -> [(Node, b)]
out' :: Context a b -> [LEdge b]
inn' :: Context a b -> [LEdge b]
outdeg' :: Context a b -> Int
indeg' :: Context a b -> Int
deg' :: Context a b -> Int
General Type Defintions
Node and Edge Types
type Node = IntSource
Unlabeled node
type LNode a = (Node, a)Source
Labeled node
type UNode = LNode ()Source
Quasi-unlabeled node
type Edge = (Node, Node)Source
Unlabeled edge
type LEdge b = (Node, Node, b)Source
Labeled edge
type UEdge = LEdge ()Source
Quasi-unlabeled edge
Types Supporting Inductive Graph View
type Adj b = [(b, Node)]Source
Labeled links to or from a Node.
type Context a b = (Adj b, Node, a, Adj b)Source
Links to the Node, the Node itself, a label, links from the Node.
type MContext a b = Maybe (Context a b)Source
type Decomp g a b = (MContext a b, g a b)Source
Graph decomposition - the context removed from a Graph, and the rest of the Graph.
type GDecomp g a b = (Context a b, g a b)Source
The same as Decomp, only more sure of itself.
type UContext = ([Node], Node, [Node])Source
Unlabeled context.
type UDecomp g = (Maybe UContext, g)Source
Unlabeled decomposition.
type Path = [Node]Source
Unlabeled path
newtype LPath aSource
Labeled path
Constructors
LP [LNode a]
show/hide Instances
Eq a => Eq (LPath a)
Ord a => Ord (LPath a)
Show a => Show (LPath a)
type UPath = [UNode]Source
Quasi-unlabeled path
Graph Type Classes

We define two graph classes:

Graph: static, decomposable graphs. Static means that a graph itself cannot be changed

DynGraph: dynamic, extensible graphs. Dynamic graphs inherit all operations from static graphs but also offer operations to extend and change graphs.

Each class contains in addition to its essential operations those derived operations that might be overwritten by a more efficient implementation in an instance definition.

Note that labNodes is essentially needed because the default definition for matchAny is based on it: we need some node from the graph to define matchAny in terms of match. Alternatively, we could have made matchAny essential and have labNodes defined in terms of ufold and matchAny. However, in general, labNodes seems to be (at least) as easy to define as matchAny. We have chosen labNodes instead of the function nodes since nodes can be easily derived from labNodes, but not vice versa.

class Graph gr whereSource
Minimum implementation: empty, isEmpty, match, mkGraph, labNodes
Methods
empty :: gr a bSource
An empty Graph.
isEmpty :: gr a b -> BoolSource
True if the given Graph is empty.
match :: Node -> gr a b -> Decomp gr a bSource
Decompose a Graph into the MContext found for the given node and the remaining Graph.
mkGraph :: [LNode a] -> [LEdge b] -> gr a bSource
Create a Graph from the list of LNodes and LEdges.
labNodes :: gr a b -> [LNode a]Source
A list of all LNodes in the Graph.
matchAny :: gr a b -> GDecomp gr a bSource
Decompose a graph into the Context for an arbitrarily-chosen Node and the remaining Graph.
noNodes :: gr a b -> IntSource
The number of Nodes in a Graph.
nodeRange :: gr a b -> (Node, Node)Source
The minimum and maximum Node in a Graph.
labEdges :: gr a b -> [LEdge b]Source
A list of all LEdges in the Graph.
show/hide Instances
class Graph gr => DynGraph gr whereSource
Methods
(&) :: Context a b -> gr a b -> gr a bSource
Merge the Context into the DynGraph.
show/hide Instances
Operations
Graph Folds and Maps
ufold :: Graph gr => (Context a b -> c -> c) -> c -> gr a b -> cSource
Fold a function over the graph.
gmap :: DynGraph gr => (Context a b -> Context c d) -> gr a b -> gr c dSource
Map a function over the graph.
nmap :: DynGraph gr => (a -> c) -> gr a b -> gr c bSource
Map a function over the Node labels in a graph.
emap :: DynGraph gr => (b -> c) -> gr a b -> gr a cSource
Map a function over the Edge labels in a graph.
Graph Projection
nodes :: Graph gr => gr a b -> [Node]Source
List all Nodes in the Graph.
edges :: Graph gr => gr a b -> [Edge]Source
List all Edges in the Graph.
newNodes :: Graph gr => Int -> gr a b -> [Node]Source
List N available Nodes, i.e. Nodes that are not used in the Graph.
gelem :: Graph gr => Node -> gr a b -> BoolSource
True if the Node is present in the Graph.
Graph Construction and Destruction
insNode :: DynGraph gr => LNode a -> gr a b -> gr a bSource
Insert a LNode into the Graph.
insEdge :: DynGraph gr => LEdge b -> gr a b -> gr a bSource
Insert a LEdge into the Graph.
delNode :: Graph gr => Node -> gr a b -> gr a bSource
Remove a Node from the Graph.
delEdge :: DynGraph gr => Edge -> gr a b -> gr a bSource
Remove an Edge from the Graph.
delLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a bSource
Remove an LEdge from the Graph.
insNodes :: DynGraph gr => [LNode a] -> gr a b -> gr a bSource
Insert multiple LNodes into the Graph.
insEdges :: DynGraph gr => [LEdge b] -> gr a b -> gr a bSource
Insert multiple LEdges into the Graph.
delNodes :: Graph gr => [Node] -> gr a b -> gr a bSource
Remove multiple Nodes from the Graph.
delEdges :: DynGraph gr => [Edge] -> gr a b -> gr a bSource
Remove multiple Edges from the Graph.
buildGr :: DynGraph gr => [Context a b] -> gr a bSource
Build a Graph from a list of Contexts.
mkUGraph :: Graph gr => [Node] -> [Edge] -> gr () ()Source
Build a quasi-unlabeled Graph.
Graph Inspection
context :: Graph gr => gr a b -> Node -> Context a bSource
Find the context for the given Node. Causes an error if the Node is not present in the Graph.
lab :: Graph gr => gr a b -> Node -> Maybe aSource
Find the label for a Node.
neighbors :: Graph gr => gr a b -> Node -> [Node]Source
Find the neighbors for a Node.
suc :: Graph gr => gr a b -> Node -> [Node]Source
Find all Nodes that have a link from the given Node.
pre :: Graph gr => gr a b -> Node -> [Node]Source
Find all Nodes that link to to the given Node.
lsuc :: Graph gr => gr a b -> Node -> [(Node, b)]Source
Find all Nodes that are linked from the given Node and the label of each link.
lpre :: Graph gr => gr a b -> Node -> [(Node, b)]Source
Find all Nodes that link to the given Node and the label of each link.
out :: Graph gr => gr a b -> Node -> [LEdge b]Source
Find all outward-bound LEdges for the given Node.
inn :: Graph gr => gr a b -> Node -> [LEdge b]Source
Find all inward-bound LEdges for the given Node.
outdeg :: Graph gr => gr a b -> Node -> IntSource
The outward-bound degree of the Node.
indeg :: Graph gr => gr a b -> Node -> IntSource
The inward-bound degree of the Node.
deg :: Graph gr => gr a b -> Node -> IntSource
The degree of the Node.
equal :: (Eq a, Eq b, Graph gr) => gr a b -> gr a b -> BoolSource
Context Inspection
node' :: Context a b -> NodeSource
The Node in a Context.
lab' :: Context a b -> aSource
The label in a Context.
labNode' :: Context a b -> LNode aSource
The LNode from a Context.
neighbors' :: Context a b -> [Node]Source
All Nodes linked to or from in a Context.
suc' :: Context a b -> [Node]Source
All Nodes linked to in a Context.
pre' :: Context a b -> [Node]Source
All Nodes linked from in a Context.
lpre' :: Context a b -> [(Node, b)]Source
All Nodes linked from in a Context, and the label of the links.
lsuc' :: Context a b -> [(Node, b)]Source
All Nodes linked from in a Context, and the label of the links.
out' :: Context a b -> [LEdge b]Source
All outward-directed LEdges in a Context.
inn' :: Context a b -> [LEdge b]Source
All inward-directed LEdges in a Context.
outdeg' :: Context a b -> IntSource
The outward degree of a Context.
indeg' :: Context a b -> IntSource
The inward degree of a Context.
deg' :: Context a b -> IntSource
The degree of a Context.
Produced by Haddock version 0.8