This file is indexed.

/usr/lib/ocaml/calendar/utils.mli is in libcalendar-ocaml-dev 2.03.2-3.

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
(**************************************************************************)
(*                                                                        *)
(*  This file is part of Calendar.                                        *)
(*                                                                        *)
(*  Copyright (C) 2003-2011 Julien Signoles                               *)
(*                                                                        *)
(*  you can redistribute it and/or modify it under the terms of the GNU   *)
(*  Lesser General Public License version 2.1 as published by the         *)
(*  Free Software Foundation, with a special linking exception (usual     *)
(*  for Objective Caml libraries).                                        *)
(*                                                                        *)
(*  It 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                           *)
(*                                                                        *)
(*  See the GNU Lesser General Public Licence version 2.1 for more        *)
(*  details (enclosed in the file LGPL).                                  *)
(*                                                                        *)
(*  The special linking exception is detailled in the enclosed file       *)
(*  LICENSE.                                                              *)
(**************************************************************************)

(** Some utilities.
    @since 2.0 *)

(** Interface for comparable and hashable types.
    Modules implementing this interface can be an argument of [Map.Make],
    [Set.Make] or [Hashtbl.Make].
    @since 2.0 *)
module type Comparable = sig

  type t

  val equal: t -> t -> bool
    (** Equality over [t]. *)

  val compare: t -> t -> int
    (** Comparison over [t].
	[compare x y] returns [0] iff [equal x y = 0]. If [x] and [y] are not
	equal, it returns a negative integer iff [x] is lesser than [y] and a
	positive integer otherwise. *)

  val hash: t -> int
    (** A hash function over [t]. *)

end

(** Integer implementation.
    @since 2.0 *)
module Int: Comparable with type t = int

(** Float implementation.
    @since 2.0 *)
module Float: sig

  include Comparable with type t = float

  val set_precision: float -> unit
    (** Set the precision of [equal] and [compare] for float.
	If the precision is [p], then the floats [x] and [y] are equal iff
	[abs(x-y) < p].  By default, the precision is [1e-3] (that is one
	millisecond if floats represents seconds). *)

  val round: t -> int
    (** Round a float to the nearest integer. *)

end