fgl-5.5.3.1: Martin Erwig's Functional Graph Library

Safe HaskellSafe
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.

In other words, this captures all information regarding the specified Node within a graph.

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 

Fields

Instances

Eq a => Eq (LPath a) Source # 

Methods

(==) :: LPath a -> LPath a -> Bool #

(/=) :: LPath a -> LPath a -> Bool #

Ord a => Ord (LPath a) Source # 

Methods

compare :: LPath a -> LPath a -> Ordering #

(<) :: LPath a -> LPath a -> Bool #

(<=) :: LPath a -> LPath a -> Bool #

(>) :: LPath a -> LPath a -> Bool #

(>=) :: LPath a -> LPath a -> Bool #

max :: LPath a -> LPath a -> LPath a #

min :: LPath a -> LPath a -> LPath a #

Show a => Show (LPath a) Source # 

Methods

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

show :: LPath a -> String #

showList :: [LPath a] -> ShowS #

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.

For graphs that are also instances of DynGraph, mkGraph ns es should be equivalent to (insEdges es . insNodes ns) empty.

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

Graph Gr Source # 

Methods

empty :: Gr a b Source #

isEmpty :: Gr a b -> Bool Source #

match :: Node -> Gr a b -> Decomp Gr a b Source #

mkGraph :: [LNode a] -> [LEdge b] -> Gr a b Source #

labNodes :: Gr a b -> [LNode a] Source #

matchAny :: Gr a b -> GDecomp Gr a b Source #

noNodes :: Gr a b -> Int Source #

nodeRange :: Gr a b -> (Node, Node) Source #

labEdges :: Gr a b -> [LEdge b] Source #

Graph Gr Source # 

Methods

empty :: Gr a b Source #

isEmpty :: Gr a b -> Bool Source #

match :: Node -> Gr a b -> Decomp Gr a b Source #

mkGraph :: [LNode a] -> [LEdge b] -> Gr a b Source #

labNodes :: Gr a b -> [LNode a] Source #

matchAny :: Gr a b -> GDecomp Gr a b Source #

noNodes :: Gr a b -> Int Source #

nodeRange :: Gr a b -> (Node, Node) Source #

labEdges :: Gr a b -> [LEdge b] Source #

class Graph gr => DynGraph gr where Source #

Minimal complete definition

(&)

Methods

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

Merge the Context into the DynGraph.

Context adjacencies should only refer to either a Node already in a graph or the node in the Context itself (for loops).

Behaviour is undefined if the specified Node already exists in the graph.

Instances

DynGraph Gr Source # 

Methods

(&) :: Context a b -> Gr a b -> Gr a b Source #

DynGraph Gr Source # 

Methods

(&) :: Context a b -> Gr a b -> Gr a b Source #

Operations

order :: Graph gr => gr a b -> Int Source #

The number of nodes in the graph. An alias for noNodes.

size :: Graph gr => gr a b -> Int Source #

The number of edges in the graph.

Note that this counts every edge found, so if you are representing an unordered graph by having each edge mirrored this will be incorrect.

If you created an unordered graph by either mirroring every edge (including loops!) or using the undir function in Data.Graph.Inductive.Basic then you can safely halve the value returned by this.

Graph Folds and Maps

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

Fold a function over the graph by recursively calling match.

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

Map a function over the graph by recursively calling match.

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.

nemap :: DynGraph gr => (a -> c) -> (b -> d) -> gr a b -> gr c d Source #

Map functions over both the Node and 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.

toEdge :: LEdge b -> Edge Source #

Drop the label component of an edge.

edgeLabel :: LEdge b -> b Source #

The label in an edge.

toLEdge :: Edge -> b -> LEdge b Source #

Add a label to an edge.

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.

NOTE: in the case of multiple edges, this will delete all such edges from the graph as there is no way to distinguish between them. If you need to delete only a single such edge, please use delLEdge.

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

Remove an LEdge from the Graph.

NOTE: in the case of multiple edges with the same label, this will only delete the first such edge. To delete all such edges, please use delAllLedge.

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

Remove all edges equal to the one specified.

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.

The list should be in the order such that earlier Contexts depend upon later ones (i.e. as produced by ufold (:) []).

mkUGraph :: Graph gr => [Node] -> [Edge] -> gr () () Source #

Build a quasi-unlabeled Graph.

Subgraphs

gfiltermap :: DynGraph gr => (Context a b -> MContext c d) -> gr a b -> gr c d Source #

Build a graph out of the contexts for which the predicate is satisfied by recursively calling match.

nfilter :: DynGraph gr => (Node -> Bool) -> gr a b -> gr a b Source #

Returns the subgraph only containing the nodes which satisfy the given predicate.

labnfilter :: Graph gr => (LNode a -> Bool) -> gr a b -> gr a b Source #

Returns the subgraph only containing the labelled nodes which satisfy the given predicate.

labfilter :: DynGraph gr => (a -> Bool) -> gr a b -> gr a b Source #

Returns the subgraph only containing the nodes whose labels satisfy the given predicate.

subgraph :: DynGraph gr => [Node] -> gr a b -> gr a b Source #

Returns the subgraph induced by the supplied nodes.

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.

lneighbors :: Graph gr => gr a b -> Node -> Adj b Source #

Find the labelled links coming into or going from a Context.

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.

hasEdge :: Graph gr => gr a b -> Edge -> Bool Source #

Checks if there is a directed edge between two nodes.

hasNeighbor :: Graph gr => gr a b -> Node -> Node -> Bool Source #

Checks if there is an undirected edge between two nodes.

hasLEdge :: (Graph gr, Eq b) => gr a b -> LEdge b -> Bool Source #

Checks if there is a labelled edge between two nodes.

hasNeighborAdj :: (Graph gr, Eq b) => gr a b -> Node -> (b, Node) -> Bool Source #

Checks if there is an undirected labelled edge between two nodes.

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.

lneighbors' :: Context a b -> Adj b Source #

All labelled links coming into or going from 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.

Ordering of Graphs

newtype OrdGr gr a b Source #

OrdGr comes equipped with an Ord instance, so that graphs can be used as e.g. Map keys.

Constructors

OrdGr 

Fields

Instances

(Graph gr, Ord a, Ord b) => Eq (OrdGr gr a b) Source # 

Methods

(==) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

(/=) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

(Graph gr, Ord a, Ord b) => Ord (OrdGr gr a b) Source # 

Methods

compare :: OrdGr gr a b -> OrdGr gr a b -> Ordering #

(<) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

(<=) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

(>) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

(>=) :: OrdGr gr a b -> OrdGr gr a b -> Bool #

max :: OrdGr gr a b -> OrdGr gr a b -> OrdGr gr a b #

min :: OrdGr gr a b -> OrdGr gr a b -> OrdGr gr a b #

Read (gr a b) => Read (OrdGr gr a b) Source # 

Methods

readsPrec :: Int -> ReadS (OrdGr gr a b) #

readList :: ReadS [OrdGr gr a b] #

readPrec :: ReadPrec (OrdGr gr a b) #

readListPrec :: ReadPrec [OrdGr gr a b] #

Show (gr a b) => Show (OrdGr gr a b) Source # 

Methods

showsPrec :: Int -> OrdGr gr a b -> ShowS #

show :: OrdGr gr a b -> String #

showList :: [OrdGr gr a b] -> ShowS #