Std.Graphlib
Generic Graph Library
module Make
(Node : Regular.Std.Opaque.S)
(Edge : Core_kernel.T) :
Graph
with type node = Node.t
and type Node.label = Node.t
and type Edge.label = Edge.t
Make(Node)(Edge)
creates a module that implements Graph
interface and has unlabeled nodes of type Node.t
and edges labeled with Edge.t
module Labeled
(Node : Regular.Std.Opaque.S)
(NL : Core_kernel.T)
(EL : Core_kernel.T) :
Graph
with type node = (Node.t, NL.t) labeled
and type Node.label = (Node.t, NL.t) labeled
and type Edge.label = EL.t
Labeled(Node)(Node_label)(Edge_label)
creates a graph structure with both nodes and edges labeled with abitrary types.
val create :
(module Graph
with type t = 'c
and type Edge.label = 'b
and type Node.label = 'a) ->
?nodes:'a list ->
?edges:('a * 'a * 'b) list ->
unit ->
'c
create (module G) ~nodes ~edges ()
creates a graph using implementation provided by module G
. Example:
module G = Graphlib.String.Bool;;
let g = Graphlib.create (module G) ~edges:[
"entry", "loop", true;
"loop", "exit", false;
"loop", "loop", true] ()
union (module G) g1 g2
returns a graph g
that is a union of graphs g1
and g2
, i.e., contains all nodes and edges from this graphs.
Postcondition:
- N(g) = N(g1) ∪ N(g2). - E(g) = E(g1) ∪ E(g2).
inter (module G) g1 g2
returns a graph g
that is an intersection of graphs g1
and g2
, i.e., it contain and edges from this graphs.
Postcondition:
- N(g) = N(g1) ∩ N(g2). - E(g) = E(g1) ∩ E(g2).
val to_dot :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?graph_attrs:('c -> graph_attr list) ->
?node_attrs:('n -> node_attr list) ->
?edge_attrs:('e -> edge_attr list) ->
?string_of_node:('n -> string) ->
?string_of_edge:('e -> string) ->
?channel:Core_kernel.Out_channel.t ->
?formatter:Stdlib.Format.formatter ->
?filename:string ->
'c ->
unit
to_dot (module G) ~filename:"graph.dot" g
dumps graph g
using dot
format. This is a customizable version of printing function. For most cases it will be enough to use G.pp
or G.to_string
function. Use this function, if you really need to customize your output.
val depth_first_search :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
?start:'n ->
?start_tree:('n -> 's -> 's) ->
?enter_node:(int -> 'n -> 's -> 's) ->
?leave_node:(int -> 'n -> 's -> 's) ->
?enter_edge:(edge_kind -> 'e -> 's -> 's) ->
?leave_edge:(edge_kind -> 'e -> 's -> 's) ->
'c ->
init:'s ->
's
depth_first_search (module G) ~init g
. It is the most important algorithm of the Graphlib. It builds a forest of spanning trees of a graph, classifies graph edges and numbers nodes. It is a Swiss-army knife, that is very useful in implementing many other algorithms. You can think of this function as fold
on steroids. But unlike fold
, that accepts only one function, the depth_first_search
accepts 5 different functions, that will be called on different situations, allowing you to «fill in the blanks» of your algorithm.
Although depth_first_search
doesn't allow you to drive the walk itself, there're still ways to do this, using filtered
function. That allows you to hide nodes or edges from the walker, thus effectively erasing them from a graph, without even touching it.
val depth_first_visit :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
?start:'n ->
'c ->
init:'s ->
('n, 'e, 's) dfs_visitor ->
's
depth_first_visit (module G) ~init visitor g
allows to specify visiting functions using object. That opens space for re-usability and using open recursion.
class ['n, 'e, 's] dfs_identity_visitor : ['n, 'e, 's] dfs_visitor
base class with all methods defaults to nothing.
val reverse_postorder_traverse :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
?start:'n ->
'c ->
'n Regular.Std.seq
returns a sequence of nodes in reverse post order.
val postorder_traverse :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
?start:'n ->
'c ->
'n Regular.Std.seq
returns a sequence of nodes in post order
val dominators :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
'c ->
'n ->
'n tree
dominators (module G) g entry
builds a dominators tree for a given graph.
Definition: a walk is a sequence of alternating nodes and edges, where each edge's endpoints are the preceding and following nodes in the sequence.
Definition: a node v
is reachable if there exists a walk starting from entry
and ending with v
.
Definition: node u
dominates v
if u = v
or if all walks from entry
to v
contains u
.
Definition: node u
strictly dominates v
if it dominates v
and u <> v
.
Definition: node u
immediately dominates v
if it strictly dominates v
and there is no other node that strictly dominates v
and is dominated by u
.
Algorithm computes a dominator tree t
that has the following properties:
u
is a parent of node v
, then node u
immediately dominates node v
;u
is an ancestors of node v
, then node u
strictly dominates node v
;v
is a child of node u
, then node u
immediately dominates node v
;v
is a descendant of node u
, then node u
strictly dominates node v
.If every node of graph g
is reachable from a provided entry
node, then properties (2) - (5) are reversible, i.e., an if
statement can be read as iff
, and the tree is unique.
To get a post-dominator tree, reverse the graph by passing true
to rev
and pass exit node as a starting node.
Note: although it is not imposed by the algotihm, but it is a good idea to have an entry node, that doesn't have any predecessors. Usually, this is what is silently assumed in many program analysis textbooks, but is not true in general for control-flow graphs that are reconstructed from binaries.
Note: all nodes that are not reachable from the specified entry
node are parented by the entry
node.
val dom_frontier :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
'c ->
'n tree ->
'n frontier
dom_frontier (module G) g dom_tree
calculates dominance frontiers for all nodes in a graph g
.
The dominance frontier of a node d
is the set of all nodes n
such that d
dominates an immediate predecessor of n
, but d
does not strictly dominate n
. It is the set of nodes where d
's dominance stops.
val strong_components :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
'c ->
'n partition
strong_components (module G) g
partition graph into strongly connected components. The top of each component is a root node, i.e., a node that has the least pre-order number.
val shortest_path :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?weight:('e -> int) ->
?rev:bool ->
'c ->
'n ->
'n ->
'e path option
shortest_path (module G) ?weight ?rev g u v
Find a shortest path from node u
to node v
.
val is_reachable :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
'c ->
'n ->
'n ->
bool
is_reachable (module G) ?rev g u v
is true if node v
is reachable from node u
in graph g
. If rev is true, then it will solve the same problem but on a reversed graph.
val fold_reachable :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?rev:bool ->
init:'a ->
f:('a -> 'n -> 'a) ->
'c ->
'n ->
'a
fold_reachable (module G) ?rev ~init ~f g n
applies function f
to all nodes reachable from node g
in graph g
. If rev
is true, then the graph is reversed.
For example, the following will build a set of reachable nodes: fold_reachable (module G) ~init:G.Node.Set.empty ~f:Set.add
val compare :
(module Graph with type node = 'n and type t = 'a) ->
(module Graph with type node = 'n and type t = 'b) ->
'a ->
'b ->
int
compare (module G1) (module G2) g1 g2
compares two graphs, with different implementation but the same node type.
val filtered :
(module Graph with type edge = 'e and type node = 'n and type t = 'c) ->
?skip_node:('n -> bool) ->
?skip_edge:('e -> bool) ->
unit ->
(module Graph
with type edge = 'e
and type node = 'n
and type t = 'c)
let module G' = filtered (module G) ?skip_node ?skip_edge ()
creates a new module G'
that can be used at any place instead of G
, but that will hide nodes and edges, for which functions skip_node
and skip_edge
return true.
Example:
let killed_edges = G.Edge.Hash_set.create () in
let module G = Graphlib.filtered (module G)
~skip_edge:(Hash_set.mem killed_edges) () in
let rec loop g () =
(* use (module G) as normal *)
Hash_set.add killed_edges some_edge;
(* all edges added to [killed_edges] will no be visible *)
val view :
(module Graph
with type edge = 'e
and type node = 'n
and type t = 'c
and type Edge.label = 'b
and type Node.label = 'a) ->
node:(('n -> 'f) * ('f -> 'n)) ->
edge:(('e -> 'd) * ('d -> 'e)) ->
node_label:(('a -> 'p) * ('p -> 'a)) ->
edge_label:(('b -> 'r) * ('r -> 'b)) ->
(module Graph
with type edge = 'd
and type node = 'f
and type t = 'c
and type Edge.label = 'r
and type Node.label = 'p)
view (module G) ~node ~edge ~node_label ~edge_label
creates a proxy module, that will transform back and forward elements of graph, using corresponding functions.
module To_ocamlgraph
(G : Graph) :
Graph.Sig.P
with type t = G.t
and type V.t = G.node
and type E.t = G.edge
and type V.label = G.Node.label
and type E.label = G.Edge.label
To_ocamlgraph(G)
returns a module that implements OCamlGraph interface for a persistent graph.
module Of_ocamlgraph
(G : Graph.Sig.P) :
Graph
with type t = G.t
and type node = G.V.t
and type edge = G.E.t
and type Node.label = G.V.label
and type Edge.label = G.E.label
Of_ocamlgraph(O)
creates an adapter module, that implements Graphlib
interface on top of the module implementing OCamlGraph
interface.
module Filtered
(G : Graph)
(P : Predicate with type node = G.node and type edge = G.edge) :
Graph
with type t = G.t
and type node = G.node
and type edge = G.edge
and module Node = G.Node
and module Edge = G.Edge
functorized version of a filter
function.
module Mapper
(G : Graph)
(N : Isomorphism with type s = G.node)
(E : Isomorphism with type s = G.edge)
(NL : Isomorphism with type s = G.Node.label)
(EL : Isomorphism with type s = G.Edge.label) :
Graph
with type t = G.t
and type node = N.t
and type edge = E.t
and type Node.label = NL.t
and type Edge.label = EL.t
functorized version of Graphlib.view
function.
val fixpoint :
(module Graph with type node = 'n and type t = 'c) ->
?steps:int ->
?start:'n ->
?rev:bool ->
?step:(int -> 'n -> 'd -> 'd -> 'd) ->
init:('n, 'd) Solution.t ->
equal:('d -> 'd -> bool) ->
merge:('d -> 'd -> 'd) ->
f:('n -> 'd -> 'd) ->
'c ->
('n, 'd) Solution.t
fixpoint ~equal ~init ~merge ~f g
computes a solution for a system of equations denoted by graph g
, using the initial approximation init
(obtained either with Solution.create
or from the previous calls to fixpoint
).
The general representation of the fixpoint equation is
x(i) = f(i) (a(1,i) x(1) % ... % a(n,i) x(n)),
where
x(i)
is the value of the i
'th variable (node);a(s,d)
is 1
if there is an edge from the node s
to the node d
and 0
otherwise;%
the merge operator;f(i)
is the transfer function for the node i
.A solution is obtained through a series of iterations until the fixed point is reached, i.e., until the system stabilizes. The total number of iterations could be bound by an arbitrary number. If the maximum number of iterations is reached before the system stabilizes then the solution is not complete. An incomplete solution could be resumed later, or used as it is (for example, in case of ascending chain the solution is always a lower approximation of a real solution, so it is always safe to use it).
val create_scheme : next:(string -> string) -> string -> scheme
create_scheme ~next init
create a name generator, that will start with init
and apply next
on it infinitly.
val symbols : scheme
lower case symbols, starting from 'a' and moving up to 'z'. As 'z' is reached, all foregoing symbols will have a form of 'node_N' where 'N' is an increasing natural number.
val numbers : scheme
numbers from zero to inifinity (Sys.max_int
in fact)
empty string
val nothing : scheme
empty string
val by_given_order :
scheme ->
('a -> 'a -> int) ->
'a Core_kernel.Sequence.t ->
'a symbolizer
val by_natural_order :
scheme ->
('a -> 'a -> int) ->
'a Core_kernel.Sequence.t ->
'a symbolizer
module Dot : sig ... end
Generic dot printer.