This file is indexed.

/usr/lib/ocaml/ocamlbricks/arrayExtra.mli is in libocamlbricks-ocaml-dev 0.90+bzr367-1build1.

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
(* This file is part of our reusable OCaml BRICKS library
   Copyright (C) 2009 Jean-Vincent Loddo

   This program is free software: you can redistribute it and/or modify
   it under the terms of the GNU General Public License as published by
   the Free Software Foundation, either version 2 of the License, or
   (at your option) any later version.

   This program 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.  See the
   GNU General Public License for more details.

   You should have received a copy of the GNU General Public License
   along with this program.  If not, see <http://www.gnu.org/licenses/>. *)

(** Additional features for the standard module [Array].*)

val of_known_length_list : ?reversing:bool -> int -> 'a list -> 'a array
val partition : ('a -> int) -> 'a array -> 'a array array

val int_seq   : min:int   -> max:int   -> incr:int   -> int array
val float_seq : min:float -> max:float -> incr:float -> float array

val sorted_copy      : ?compare:('a -> 'a -> int) -> 'a array -> 'a array
val fast_sorted_copy : ?compare:('a -> 'a -> int) -> 'a array -> 'a array

val for_all : (int -> 'a -> bool) -> 'a array -> bool
val exists  : (int -> 'a -> bool) -> 'a array -> bool
val lexists : (int -> 'a -> bool) -> 'a array -> int option
val rexists : (int -> 'a -> bool) -> 'a array -> int option

val search  : ('a -> bool) -> 'a array -> 'a option
val searchi : ('a -> bool) -> 'a array -> (int * 'a) option
val find    : ('a -> bool) -> 'a array -> 'a
val findi   : ('a -> bool) -> 'a array -> (int * 'a)

val search_longest_sequence : ?leftmost:unit -> ('a -> bool) -> 'a array -> (int * int) option
val shared_property : ('a -> 'b) -> 'a array -> bool

(* The call {[dichotomic_search a x]} returns a pair (b,i) that
   provides two distinct kind of helpful informations:
   1) if b=true  then x has been found at position i
   2) if b=false then x has not been found and i contains
      the *first* element y strictly greater than x or i is
      out of bounds (i>=length, that means x greater than all
      elements in the array)
   *)
val dichotomic_search : ?a:int -> ?b:int -> 'a array -> 'a -> bool * int
val dichotomic_insert : 'a array -> 'a -> 'a array
val dichotomic_index_of_first_element_gt : ?a:int -> ?b:int -> 'a -> 'a array -> int option
val dichotomic_index_of_last_element_lt  : ?a:int -> ?b:int -> 'a -> 'a array -> int option

val for_all2 : (int -> 'a -> 'b -> bool) -> 'a array -> 'b array -> bool
val exists2  : (int -> 'a -> 'b -> bool) -> 'a array -> 'b array -> bool

val iter2  : ('a -> 'b -> unit) -> 'a array -> 'b array -> unit
val iteri2 : (int -> 'a -> 'b -> unit) -> 'a array -> 'b array -> unit

val map2   : ('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
val mapi2  : (int -> 'a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array

val map_fold : ('a -> int -> 'b -> 'c * 'a) -> 'a -> 'b array -> 'c array

val fold_lefti  : (int -> 'a -> 'b -> 'a) -> 'a -> 'b array -> 'a
val fold_righti : (int -> 'a -> 'b -> 'b) -> 'a array -> 'b -> 'b

val fold_left2 : ('a -> 'b -> 'c -> 'a) -> 'a -> 'b array -> 'c array -> 'a
val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a array -> 'b array -> 'c -> 'c

val fold_lefti2 : (int -> 'a -> 'b -> 'c -> 'a) -> 'a -> 'b array -> 'c array -> 'a
val fold_righti2 : (int -> 'a -> 'b -> 'c -> 'c) -> 'a array -> 'b array -> 'c -> 'c

val init2 : int -> (int -> 'a *'b) -> 'a array * 'b array
val split : ('a * 'b) array -> 'a array * 'b array

val cut : lengths:int list -> 'a array -> 'a array list

val max  : ?gt:('a -> 'a -> bool) -> 'a array -> int * 'a
val min  : ?gt:('a -> 'a -> bool) -> 'a array -> int * 'a
val best : ?choice:('a -> 'a -> 'a) -> 'a array -> int * 'a

module Matrix : sig
 type 'a t = 'a array array
 val init : int -> int -> (int -> int -> 'a) -> 'a t
 val of_list : 'a list list -> 'a t
 val to_list : 'a t -> 'a list list
 val transpose : 'a t -> 'a t
end