fgl-5.5.1.0: Martin Erwig's Functional Graph Library

Safe HaskellSafe-Inferred
LanguageHaskell98

Data.Graph.Inductive.Graph

Contents

Description

Static and Dynamic Inductive Graphs

Synopsis

General Type Defintions

Node and Edge Types

type Node = Int Source

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 a Source

Labeled path

Constructors

LP [LNode a] 

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 where Source

Minimum implementation: empty, isEmpty, match, mkGraph, labNodes

Minimal complete definition

empty, isEmpty, match, mkGraph, labNodes

Methods

empty :: gr a b Source

An empty Graph.

isEmpty :: gr a b -> Bool Source

True if the given Graph is empty.

match :: Node -> gr a b -> Decomp gr a b Source

Decompose a Graph into the MContext found for the given node and the remaining Graph.

mkGraph :: [LNode a] -> [LEdge b] -> gr a b Source

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 b Source

Decompose a graph into the Context for an arbitrarily-chosen Node and the remaining Graph.

noNodes :: gr a b -> Int Source

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.

Instances

class Graph gr => DynGraph gr where Source

Methods

(&) :: Context a b -> gr a b -> gr a b Source

Merge the Context into the DynGraph.

Instances

Operations

Graph Folds and Maps

ufold :: Graph gr => (Context a b -> c -> c) -> c -> gr a b -> c Source

Fold a function over the graph.

gmap :: DynGraph gr => (Context a b -> Context c d) -> gr a b -> gr c d Source

Map a function over the graph.

nmap :: DynGraph gr => (a -> c) -> gr a b -> gr c b Source

Map a function over the Node labels in a graph.

emap :: DynGraph gr => (b -> c) -> gr a b -> gr a c Source

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 -> Bool Source

True if the Node is present in the Graph.

Graph Construction and Destruction

insNode :: DynGraph gr => LNode a -> gr a b -> gr a b Source

Insert a LNode into the Graph.

insEdge :: DynGraph gr => LEdge b -> gr a b -> gr a b Source

Insert a LEdge into the Graph.

delNode :: Graph gr => Node -> gr a b -> gr a b Source

Remove a Node from the Graph.

delEdge :: DynGraph gr => Edge -> gr a b -> gr a b Source

Remove an Edge from the Graph.

delLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b Source

Remove an LEdge from the Graph.

insNodes :: DynGraph gr => [LNode a] -> gr a b -> gr a b Source

Insert multiple LNodes into the Graph.

insEdges :: DynGraph gr => [LEdge b] -> gr a b -> gr a b Source

Insert multiple LEdges into the Graph.

delNodes :: Graph gr => [Node] -> gr a b -> gr a b Source

Remove multiple Nodes from the Graph.

delEdges :: DynGraph gr => [Edge] -> gr a b -> gr a b Source

Remove multiple Edges from the Graph.

buildGr :: DynGraph gr => [Context a b] -> gr a b Source

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 b Source

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 a Source

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 -> Int Source

The outward-bound degree of the Node.

indeg :: Graph gr => gr a b -> Node -> Int Source

The inward-bound degree of the Node.

deg :: Graph gr => gr a b -> Node -> Int Source

The degree of the Node.

equal :: (Eq a, Eq b, Graph gr) => gr a b -> gr a b -> Bool Source

Context Inspection

node' :: Context a b -> Node Source

The Node in a Context.

lab' :: Context a b -> a Source

The label in a Context.

labNode' :: Context a b -> LNode a Source

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 -> Int Source

The outward degree of a Context.

indeg' :: Context a b -> Int Source

The inward degree of a Context.

deg' :: Context a b -> Int Source

The degree of a Context.

Pretty-printing

prettify :: (DynGraph gr, Show a, Show b) => gr a b -> String Source

Pretty-print the graph. Note that this loses a lot of information, such as edge inverses, etc.

prettyPrint :: (DynGraph gr, Show a, Show b) => gr a b -> IO () Source

Pretty-print the graph to stdout.