This file is indexed.

/usr/lib/ocaml/perl/perl.mli is in libperl4caml-ocaml-dev 0.9.5-4build5.

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
 96
 97
 98
 99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
(** Interface to Perl from OCaml. *)
(*  Copyright (C) 2003 Merjis Ltd.

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

    This library 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
    Library General Public License for more details.

    You should have received a copy of the GNU General Public License
    along with this library; see the file COPYING.  If not, write to
    the Free Software Foundation, Inc., 59 Temple Place - Suite 330,
    Boston, MA 02111-1307, USA.

    $Id: perl.mli,v 1.16 2008-03-01 13:02:21 rich Exp $
  *)

type sv
(** Perl scalar value. *)

type av
(** Perl array value. *)

type hv
(** Perl hash value. *)

exception Perl_failure of string
(** [die] in Perl code is translated automatically into this exception. *)

val int_of_sv : sv -> int
(** Convert a Perl [SV] into an integer. Note that OCaml [int]s aren't
  * large enough to store the full 32 (or 64) bits from a Perl integer,
  * so you may get a silent overflow.
  *)
val sv_of_int : int -> sv
(** Convert an [int] into a Perl [SV]. *)
val float_of_sv : sv -> float
(** Convert a Perl [SV] into a float. *)
val sv_of_float : float -> sv
(** Convert a [float] into a Perl [SV]. *)
val string_of_sv : sv -> string
(** Convert a Perl [SV] into a string. *)
val sv_of_string : string -> sv
(** Convert a [string] into a Perl [SV]. *)
val bool_of_sv : sv -> bool
(** Convert an [SV] into a boolean. *)
val sv_of_bool : bool -> sv
(** Convert a boolean into an [SV]. *)

val sv_is_true : sv -> bool
(** Return [true] if the [SV] is "true" (in the Perl sense of truth). *)
val sv_is_undef : sv -> bool
(** Return [true] if the [SV] is undefined (is [undef]). *)
val sv_undef : unit -> sv
(** Returns [undef]. *)
val sv_true : unit -> sv
(** Returns an [SV] which is true. *)
val sv_false : unit -> sv
(** Returns an [SV] which is false. *)
val sv_yes : unit -> sv
(** Returns Perl's internal [PL_sv_yes]. (There are some unresolved issues
  * with using this, so use {!Perl.sv_true} instead). *)
val sv_no : unit -> sv
(** Returns Perl's internal [PL_sv_no]. (There are some unresolved issues
  * with using this, so use {!Perl.sv_false} instead). *)

(* Actually there are many more types defined than this ... *)
type sv_t    = SVt_NULL
             | SVt_IV	     (** Integer scalar.  *)
	     | SVt_NV	     (** Floating point scalar. *)
	     | SVt_PV	     (** String scalar. *)
	     | SVt_RV	     (** Reference. *)
	     | SVt_PVAV	     (** Array. *)
	     | SVt_PVHV	     (** Hash. *)
	     | SVt_PVCV      (** Code. *)
	     | SVt_PVGV	     (** Glob (possibly a file handle). *)
	     | SVt_PVMG	     (** Blessed or magical scalar. *)
val sv_type : sv -> sv_t
(** Return the type of data contained in an [SV]. Somewhat equivalent to
  * calling Perl's [ref] function.
  *)
val string_of_sv_t : sv_t -> string
(** Return a printable string for an [sv_t] ([SV] type). *)

val reftype : sv -> sv_t
(** The parameter [sv] must be a reference.  This convenience function
 * works out what it is a reference to, either a scalar, array, hash,
 * code or glob.  If the parameter is not a reference, or is a reference
 * to an unknown type, then this will throw [Invalid_argument].  *)

val address_of_sv : sv -> Nativeint.t
(** Returns the address of the SV.  Useful for debugging since
  * Perl also prints out addresses on internal errors.
  *)
val address_of_av : av -> Nativeint.t
(** Returns the address of the AV.  Useful for debugging since
  * Perl also prints out addresses on internal errors.
  *)
val address_of_hv : hv -> Nativeint.t
(** Returns the address of the HV.  Useful for debugging since
  * Perl also prints out addresses on internal errors.
  *)

val scalarref : sv -> sv
(** Given a scalar, this returns a reference to the scalar. Note that
  * because references are [SV]s, this returns [sv].
  *)
val arrayref : av -> sv
(** Given an array, this returns a reference to the array. Note that
  * because references are [SV]s, this returns [sv].
  *)
val hashref : hv -> sv
(** Given a hash, this returns a reference to the hash. Note that
  * because references are [SV]s, this returns [sv].
  *)

val deref : sv -> sv
(** The input is a reference to a scalar. This returns the underlying
  * scalar [SV]. If the input is not a reference to a scalar, throws
  * [Invalid_argument].
  *)
val deref_array : sv -> av
(** The input is a reference to an array. This returns the underlying
  * array [AV]. If the input is not a reference to an array, throws
  * [Invalid_argument].
  *)
val deref_hash : sv -> hv
(** The input is a reference to a hash. This returns the underlying
  * hash [HV]. If the input is not a reference to a hash, throws
  * [Invalid_argument].
  *)

val av_empty : unit -> av
(** Create an empty [AV] (array). *)
val av_of_sv_list : sv list -> av
(** Create an array from a list of [SVs]. *)
val av_push : av -> sv -> unit
(** Append the [SV] to the end of the array. Same as Perl
  * [push \@av, $sv]. *)
val av_pop : av -> sv
(** Remove the [SV] at the end of the array and return it. Same as
  * Perl [$sv = pop \@av]. *)
val av_shift : av -> sv
(** Remove the [SV] at the beginning of the array and return it. Same as
  * Perl [$sv = shift \@av]. *)
val av_unshift : av -> sv -> unit
(** Prepend the [SV] to the start of the array. Same as Perl
  * [unshift \@av, $sv]. *)
val av_length : av -> int
(** Return the length of the [AV]. *)
val av_set : av -> int -> sv -> unit
(** Replace the i'th element of the [AV] with [SV]. *)
val av_get : av -> int -> sv
(** Get the i'th element of the [AV]. *)
val av_clear : av -> unit
(** Remove all elements from the [AV]. Same as Perl [\@av = ()]. *)
val av_undef : av -> unit
(** Delete the [AV] (and all elements in it). Same as Perl [undef \@av]. *)
val av_extend : av -> int -> unit
(** Extend the [AV] so it contains at least [n+1] elements.  Note that
  * this apparently just changes the amount of allocated storage.  The
  * extra elements are not visible until you store something in them.
  *)
val av_map : (sv -> 'a) -> av -> 'a list
(** Map a function over the elements in the [AV], return a list of the
  * results. *)
val list_of_av : av -> sv list
(** Convert an [AV] into a simple list of [SV]s. *)
val av_of_string_list : string list -> av
(** Build an [AV] from a list of strings. *)

val hv_empty : unit -> hv
(** Create an empty [HV] (hash). *)
val hv_set : hv -> string -> sv -> unit
(** Store the given [SV] in the named key in the hash. *)
val hv_get : hv -> string -> sv
(** Return the [SV] at the key in the hash. Throws [Not_found] if no key. *)
val hv_exists : hv -> string -> bool
(** Return true if the hash contains the given key. Same as Perl [exists]. *)
val hv_delete : hv -> string -> unit
(** Delete the given key from the hash. Same as Perl [delete]. *)
val hv_clear : hv -> unit
(** Remove all elements from the [HV]. Same as Perl [%av = ()]. *)
val hv_undef : hv -> unit
(** Delete the [HV] (and all elements in it). Same as Perl [undef %hv]. *)
val hv_of_assoc : (string * sv) list -> hv
(** Create an [HV] directly from an assoc list.  Perl hashes cannot
  * support multiple values attached to the same key, so if you try
  * to provide an assoc list with multiple identical keys, the results
  * will be undefined.
  *)
val assoc_of_hv : hv -> (string * sv) list
(** Take an [HV] and return an assoc list. *)
val hv_keys : hv -> string list
(** Return all the keys of an [HV]. *)
val hv_values : hv -> sv list
(** Return all the values of an [HV]. *)

(* The following are the low-level iteration interface to hashes,
 * which you probably shouldn't use directly.  Use {!hv_keys},
 * {!assoc_of_hv}, etc. instead.  See [perlguts(3)] if you really
 * want to use this interface.
 *)
type he
val hv_iterinit : hv -> Int32.t
val hv_iternext : hv -> he
val hv_iterkey : he -> string
val hv_iterval : hv -> he -> sv
val hv_iternextsv : hv -> string * sv

val get_sv : ?create:bool -> string -> sv
  (** Return a scalar value by name. For example, if you have a symbol
    * called [$a] in Perl, then [get_sv "a"] will return its value.
    *
    * If the symbol does not exist, this throws [Not_found].
    *
    * If the optional [?create] argument is set to true and the symbol does
    * not exist, then Perl will create the symbol (with value [undef]) and
    * this function will return the [SV] for [undef].
  *)
val get_av : ?create:bool -> string -> av
(** Same as {!Perl.get_sv} except will return and/or create [\@a]. *)
val get_hv : ?create:bool -> string -> hv
(** Same as {!Perl.get_sv} except will return and/or create [%a]. *)

val call : ?sv:sv -> ?fn:string -> sv list -> sv
(** Call a Perl function in a scalar context, either by name (using the [?fn]
  * parameter) or by calling a string/CODEREF (using the [?sv] parameter).
  *
  * Returns the Perl [SV] containing the result value. (See
  * {!Perl.int_of_sv} etc.).
  *
  * If the Perl code calls [die] then this will throw [Perl_failure].
  *)

val call_array : ?sv:sv -> ?fn:string -> sv list -> sv list
(** Call a Perl function in an array context, either by name (using the [?fn]
  * parameter) or by calling a string/CODEREF (using the [?sv] parameter).
  *
  * Returns the list of results.
  *
  * If the Perl code calls [die] then this will throw [Perl_failure].
  *)

val call_void : ?sv:sv -> ?fn:string -> sv list -> unit
(** Call a Perl function in a void context, either by name (using the [?fn]
  * parameter) or by calling a string/CODEREF (using the [?sv] parameter).
  *
  * Any results are discarded.
  *
  * If the Perl code calls [die] then this will throw [Perl_failure].
  *)

val eval : string -> sv
(** This is exactly like the Perl [eval] command. It evaluates a piece of
  * Perl code (in scalar context) and returns the result (a Perl [SV]).
  *)

val call_method : sv -> string -> sv list -> sv
(** [call_method obj name [parameters]] calls the method [name] on the Perl
  * object [obj] with the given parameters, in a scalar context. Thus this
  * is equivalent to [$obj->name (parameters)].
  *
  * Returns the Perl [SV] containing the result value.
  *
  * If the method calls [die] then this will throw [Perl_failure].
  *)

val call_method_array : sv -> string -> sv list -> sv list
(** Like [call_method], but the method is called in an array context. *)

val call_method_void : sv -> string -> sv list -> unit
(** Like [call_method], but the method is called in a void context (results
  * are discarded). *)

val call_class_method : string -> string -> sv list -> sv
(** [call_class_method classname name [parameters]] calls the static method
  * [name] in the Perl class [classname] with the given parameters, in a
  * scalar context. Thus this is equivalent to [$classname->name (parameters)].
  *
  * Returns the Perl [SV] containing the result value.
  *
  * If the static method calls [die] then this will throw [Perl_failure].
  *)

val call_class_method_array : string -> string -> sv list -> sv list
(** Like [call_class_method], but the method is called in an array context. *)

val call_class_method_void : string -> string -> sv list -> unit
(** Like [call_class_method], but the method is called in a void context. *)