Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Static and Dynamic Inductive Graphs
Code is from Hackage fgl
package version 5.7.0.3
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 {}
- type UPath = [UNode]
- class Graph gr where
- class Graph gr => DynGraph gr where
- order :: Graph gr => gr a b -> Int
- size :: Graph gr => gr a b -> Int
- 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
- nemap :: DynGraph gr => (a -> c) -> (b -> d) -> gr a b -> gr c d
- nodes :: Graph gr => gr a b -> [Node]
- edges :: Graph gr => gr a b -> [Edge]
- toEdge :: LEdge b -> Edge
- edgeLabel :: LEdge b -> b
- toLEdge :: Edge -> b -> LEdge b
- 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
- delAllLEdge :: (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 () ()
- gfiltermap :: DynGraph gr => (Context a b -> MContext c d) -> gr a b -> gr c d
- nfilter :: DynGraph gr => (Node -> Bool) -> gr a b -> gr a b
- labnfilter :: Graph gr => (LNode a -> Bool) -> gr a b -> gr a b
- labfilter :: DynGraph gr => (a -> Bool) -> gr a b -> gr a b
- subgraph :: DynGraph gr => [Node] -> gr a b -> gr a b
- 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]
- lneighbors :: Graph gr => gr a b -> Node -> Adj b
- 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
- hasEdge :: Graph gr => gr a b -> Edge -> Bool
- hasNeighbor :: Graph gr => gr a b -> Node -> Node -> Bool
- hasLEdge :: (Graph gr, Eq b) => gr a b -> LEdge b -> Bool
- hasNeighborAdj :: (Graph gr, Eq b) => gr a b -> Node -> (b, Node) -> Bool
- 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]
- lneighbors' :: Context a b -> Adj b
- 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 ()
- newtype OrdGr gr a b = OrdGr {
- unOrdGr :: gr a b
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.
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 #
Create a Graph
from the list of LNode
s and LEdge
s.
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 #
matchAny :: gr a b -> GDecomp gr a b Source #
noNodes :: gr a b -> Int Source #
Instances
Graph Gr Source # | |
Defined in GHC.Data.Graph.Inductive.PatriciaTree |
Operations
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.
Graph Projection
Graph Construction and Destruction
delAllLEdge :: (DynGraph gr, Eq b) => LEdge b -> gr a b -> gr a b Source #
Remove all edges equal to the one specified.
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
lneighbors :: Graph gr => gr a b -> Node -> Adj b Source #
Find the labelled links coming into or going from a Context
.
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.
Context Inspection
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
OrdGr comes equipped with an Ord instance, so that graphs can be used as e.g. Map keys.
Instances
Read (gr a b) => Read (OrdGr gr a b) Source # | |
Show (gr a b) => Show (OrdGr gr a b) Source # | |
(Graph gr, Ord a, Ord b) => Eq (OrdGr gr a b) Source # | |
(Graph gr, Ord a, Ord b) => Ord (OrdGr gr a b) Source # | |
Defined in GHC.Data.Graph.Inductive.Graph |