This file is indexed.

/usr/lib/ocaml/facile/fcl_misc.mli is in libfacile-ocaml-dev 1.1.1-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
(***********************************************************************)
(*                                                                     *)
(*                           FaCiLe                                    *)
(*                 A Functional Constraint Library                     *)
(*                                                                     *)
(*            Nicolas Barnier, Pascal Brisset, LOG, CENA               *)
(*                                                                     *)
(* Copyright 2004 CENA. All rights reserved. This file is distributed  *)
(* under the terms of the GNU Lesser General Public License.           *)
(***********************************************************************)
(* $Id: fcl_misc.mli,v 1.12 2004/05/10 12:51:19 barnier Exp $ *)

(* Module [Misc]: straightforwardly eponymous *)

val last_and_length : 'a list -> 'a * int
(* _Undocumented_
   Returns the last element as well as the size of a list. Used by
   [Fcl_domain.make]. *)
val gen_int_fun : unit -> (unit -> int)
(* _Undocumented_
   Returns a function generating unique integers (modulo [max_int - min_int]).
   Used to generate identification keys (increasing from 0). *)
val arg_min_array : ('a -> 'b) -> 'a array -> (int * 'b)
val arg_max_array : ('a -> 'b) -> 'a array -> (int * 'b)
(* _Undocumented_
   [arg_min_array f a] (resp. [arg_max_array f a]) returns the index of
   the first element of [a] that minimizes (resp. maximizes) [f] and
   the corresponding optimal value. *)
val int_overflow : float -> bool
  (*  _Undocumented_
     [int_overflow x] returns [true] iff [float max_int < x] or
     [float min_int > x], [false] otherwise. Used in Operators and
     [Fcl_arith.expn_int]. *)

module Operators : sig
  val (=+) : int ref -> int -> unit
  val (=+.) : float ref -> float -> unit
(*  _Undocumented_
   [x =+ n] C-like increment operator. Equivalent to [x := !x+n]. *)
  val min : int -> int -> int
(* _Undocumented_
   Non-polymorphic [min] over integers. For optimization purpose. *)
  val max : int -> int -> int
(* _Undocumented_
   Non-polymorphic [max] over integers. For optimization purpose. *)

  val ( * ) : int -> int -> int
  val (+) : int -> int -> int
  val (-) : int -> int -> int
  (* _Undocumented_
     Standard integer arithmetic operators with overflow checking raising an
     assert failure. Disabled if compiled with the -noassert flag. Used
     in [Fcl_arith]. *)

  val sign : int -> int
  val ( /+ ) : int -> int -> int
  val ( /- ) : int -> int -> int
  (* _Undocumented_
     Used within arithmetic modules *)
end

val iter : ('a -> 'a) -> int -> 'a -> 'a
  (* _Undocumented_
     [iter f n z] computes [(f (f ... n] times [... (f z)))]. Used in
     Fcl_arith.( **~). *)
val goedel : (int -> 'a -> 'a) -> int -> 'a -> 'a
  (* _Undocumented_
     [godel f n z] computes [(f (n-1) (f (n-2) ... n] times [... (f 0 z)))].
     Used in [Fcl_gcc]. *)

val protect : string -> (unit -> 'a) -> 'a
  (* _Undocumented_
     [protect name f] calls [f] and controls that it is
     not called inside itself. Raises an exception using [name] if it is
     the case. Example: let my_fun my_arg = protect "my_fun" (fun () -> ...).
  *)