| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell98 | 
Data.Graph.Inductive.Graph
Contents
Description
Static and Dynamic Inductive Graphs
- 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
- class Graph gr => DynGraph gr where
- 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
- prettify :: (DynGraph gr, Show a, Show b) => gr a b -> String
- prettyPrint :: (DynGraph gr, Show a, Show b) => gr a b -> IO ()
General Type Defintions
Node and Edge Types
Types Supporting Inductive Graph View
Labeled 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.
Methods
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
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
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.