This file is indexed.

/usr/lib/ocaml/ocamlgraph/persistent.mli is in libocamlgraph-ocaml-dev 1.8.6-1build2.

This file is owned by root:root, with mode 0o644.

The actual contents of the file can be viewed below.

 1
 2
 3
 4
 5
 6
 7
 8
 9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
(**************************************************************************)
(*                                                                        *)
(*  Ocamlgraph: a generic graph library for OCaml                         *)
(*  Copyright (C) 2004-2010                                               *)
(*  Sylvain Conchon, Jean-Christophe Filliatre and Julien Signoles        *)
(*                                                                        *)
(*  This software is free software; you can redistribute it and/or        *)
(*  modify it under the terms of the GNU Library General Public           *)
(*  License version 2.1, with the special exception on linking            *)
(*  described in file LICENSE.                                            *)
(*                                                                        *)
(*  This software is distributed in the hope that it will be useful,      *)
(*  but WITHOUT ANY WARRANTY; without even the implied warranty of        *)
(*  MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.                  *)
(*                                                                        *)
(**************************************************************************)

(** Persistent Graph Implementations. *)

open Sig

(** Signature of persistent graphs. *)
module type S = sig

  (** <b>Edges may be labeled or not</b>:
      - Unlabeled: there is no label on edges
      - Labeled: you have to provide a label implementation as a functor
      parameter.

      <b>Vertices may be concrete or abstract</b>:
      - Concrete: type of vertex labels and type of vertices are identified.
      - Abstract: type of vertices is abstract (in particular it is not equal
      to type of vertex labels

      <b>How to choose between concrete and abstract vertices for my graph
      implementation</b>?

      Usually, if you fall into one of the following cases, use abstract
      vertices:
      - you cannot provide efficient comparison/hash functions for vertices; or
      - you wish to get two different vertices with the same label.

      In other cases, it is certainly easier to use concrete vertices.  *)

  (** Persistent Unlabeled Graphs. *)
  module Concrete (V: COMPARABLE) :
    Sig.P with type V.t = V.t and type V.label = V.t and type E.t = V.t * V.t
	  and type E.label = unit

  (** Abstract Persistent Unlabeled Graphs. *)
  module Abstract(V: ANY_TYPE) : Sig.P with type V.label = V.t
				       and type E.label = unit

  (** Persistent Labeled Graphs. *)
  module ConcreteLabeled (V: COMPARABLE)(E: ORDERED_TYPE_DFT) :
    Sig.P with type V.t = V.t and type V.label = V.t
	    and type E.t = V.t * E.t * V.t and type E.label = E.t

  (** Abstract Persistent Labeled Graphs. *)
  module AbstractLabeled (V: ANY_TYPE)(E: ORDERED_TYPE_DFT) :
    Sig.P with type V.label = V.t and type E.label = E.t

end

(** Persistent Directed Graphs. *)
module Digraph : sig

  include S

  (** {2 Bidirectional graphs}

      Bidirectional graphs use more memory space (at worse the double) that
      standard concrete directional graphs. But accessing predecessors and
      removing a vertex are faster. *)

  (** Imperative Unlabeled, bidirectional graph. *)
  module ConcreteBidirectional (V: COMPARABLE) :
    Sig.P with type V.t = V.t and type V.label = V.t and type E.t = V.t * V.t
          and type E.label = unit

  (** Imperative Labeled and bidirectional graph. *)
  module ConcreteBidirectionalLabeled(V:COMPARABLE)(E:ORDERED_TYPE_DFT) :
    Sig.P with type V.t = V.t and type V.label = V.t
          and type E.t = V.t * E.t * V.t and type E.label = E.t

end

(** Persistent Undirected Graphs. *)
module Graph : S

(*
Local Variables:
compile-command: "make -C .."
End:
*)