This file is indexed.

/usr/lib/ocaml/compiler-libs/utils/consistbl.mli is in ocaml-compiler-libs 3.12.1-2ubuntu2.

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
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*            Xavier Leroy, projet Cristal, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 2002 Institut National de Recherche en Informatique et   *)
(*  en Automatique.  All rights reserved.  This file is distributed    *)
(*  under the terms of the Q Public License version 1.0.               *)
(*                                                                     *)
(***********************************************************************)

(* $Id: consistbl.mli 5275 2002-11-18 10:41:26Z xleroy $ *)

(* Consistency tables: for checking consistency of module CRCs *)

type t

val create: unit -> t

val clear: t -> unit

val check: t -> string -> Digest.t -> string -> unit
      (* [check tbl name crc source]
           checks consistency of ([name], [crc]) with infos previously
           stored in [tbl].  If no CRC was previously associated with
           [name], record ([name], [crc]) in [tbl].
           [source] is the name of the file from which the information
           comes from.  This is used for error reporting. *)

val check_noadd: t -> string -> Digest.t -> string -> unit
      (* Same as [check], but raise [Not_available] if no CRC was previously
           associated with [name]. *)

val set: t -> string -> Digest.t -> string -> unit
      (* [set tbl name crc source] forcefully associates [name] with
         [crc] in [tbl], even if [name] already had a different CRC
         associated with [name] in [tbl]. *)

val source: t -> string -> string
      (* [source tbl name] returns the file name associated with [name]
         if the latter has an associated CRC in [tbl].
         Raise [Not_found] otherwise. *)

val extract: t -> (string * Digest.t) list
      (* Return all bindings ([name], [crc]) contained in the given
         table. *)

val filter: (string -> bool) -> t -> unit
      (* [filter pred tbl] removes from [tbl] table all (name, CRC) pairs
         such that [pred name] is [false]. *)

exception Inconsistency of string * string * string
      (* Raised by [check] when a CRC mismatch is detected.
         First string is the name of the compilation unit.
         Second string is the source that caused the inconsistency.
         Third string is the source that set the CRC. *)

exception Not_available of string
      (* Raised by [check_noadd] when a name doesn't have an associated CRC. *)