This file is indexed.

/usr/lib/ocaml/typerep_lib/variant_and_record_intf.ml is in libtyperep-camlp4-dev 113.00.00-1.

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
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
(**
   Place holder for common Variants and Fields interface
*)

module M (X : sig

  (**
     This functor is essentially there because we use this same interface in different
     contexts, with different types for ['a t].

     1) One use case for it is where ['a X.t = 'a Typerep.t].  These interfaces are then
        part of the type witness built for a type containing a record or a variant in its
        structure. [traverse] will give a way of accessing the type representation for the
        arguments of a variant or record type.

     2) Another use case is for building "staged generic computations". In that case, the
        type ['a X.t] is the type of the computation that is being built.  [traverse]
        returns the computation built for the argument. The interface no longer exports
        the typerep of the arguments in hopes of enforcing that no typerep traversal
        happens at runtime if the computation happen to be a function.
  *)
  type 'a t
end) = struct

  (* The functions prefixed by [internal] as well as the module suffixed by [_internal]
     are used by the code generated by the camlp4 extension [with typerep] as well as some
     internals of the typerep library. Do not consider using these somewhere else.  They
     should ideally not be exported outside the typerep library, but the generated code
     needs somehow to access this, even outside. *)

  module Tag_internal = struct
    type ('variant, 'args) create = Args of ('args -> 'variant) | Const of 'variant
    type ('variant, 'args) t = {
      label : string;
      rep : 'args X.t;
      arity : int;
      index : int;
      ocaml_repr : int;
      tyid : 'args Typename.t;
      create : ('variant, 'args) create;
    }
  end

  (**
     Witness of a tag, that is an item in a variant type, also called an "applied
     variant Constructor"

     The first parameter is the variant type, the second is the type of the tag
     parameters.  Example:

     type t =
       | A of (int * string)
       | B of string

     this type has two constructors. for each of them we'll have a corresponding [Tag.t]
     val tag_A : (t, (int * string)) Tag.t
     val tag_B : (t, string) Tag.t
  *)
  module Tag : sig
    type ('variant, 'args) create = Args of ('args -> 'variant) | Const of 'variant
    type ('variant, 'args) t

    (**
       The name of the constructor as it is given in the concrete syntax
       Examples:
       | A of int      "A"
       | `a of int     "a"
       | `A of int     "A"

       for standard variant, the ocaml syntax implies that this label will always starts
       with a capital letter. For polymorphic variants, this might be a lowercase char.
       For polymorphic variant, this label does not include the [`] character.
    *)
    val label : (_, _) t -> string

    (**
       The size of the ocaml heap block containing the arguments
       Examples:
       0: | A | 'A
       1: | A of int | `A of int | A of (int * int) | `A of (int * int) | `A of int * int
       2: | A of int * float
       etc.
    *)
    val arity : (_, _) t -> int

    (**
       The index of the constructor in the list of all the variant type's constructors
       Examples:
       type t =
        | A of int  (* 0 *)
        | B         (* 1 *)
        | C of int  (* 2 *)
        | D of char (* 3 *)
    *)
    val index : (_, _) t -> int

    (**
       ocaml_repr is related to the runtime of objects. this is essentially a way of
       giving one the ability to rebuild dynamically an [Obj.t] representing a tag.

       Polymorphic variants:
       ---------------------

       [ocaml_repr] is the hash of the label, as done by the compiler.
       Example:
       print_int (Obj.magic `bar)  (* 4895187 *)
       print_int (Obj.magic 'foo)  (* 5097222 *)

       Standards variants:
       -------------------

       [ocaml_repr] is the tag corresponding to the constructor within the type.
       the way it works in the ocaml runtime is by partitioning the constructors regarding
       if they have some arguments or not, preserving the order, then assign increasing
       index withing each partition.
       Example:

       type t =                  (* no arg *)  (* args *)
         | A                       (* 0 *)
         | B of int                              (* 0 *)
         | C                       (* 1 *)
         | D of (float * string)                 (* 1 *)
         | E                       (* 2 *)
         | F                       (* 3 *)
         | G of string                           (* 2 *)
    *)
    val ocaml_repr : (_, _) t -> int

    (**
       Give back a way of constructing a value of that constructor from its arguments.
       Examples:
       type t =
         | A of (int * string)
         | B of int * float
         | C

       [create] will return something equivalent to:
       tag_A : [Args (fun (d : (int * string) -> A d)]
       tag_B : [Args (fun (i, f) -> B (i, f))]
       tag_C : [Const C]
    *)
    val create : ('variant, 'args) t -> ('variant, 'args) create

    (** return the type_name of the arguments. might be used to perform some lookup based
        on it while building a computation for example *)
    val tyid : (_, 'args) t -> 'args Typename.t

    (** get the representation/computation of the arguments *)
    val traverse : (_, 'args) t -> 'args X.t

    (* used by the camlp4 extension to build type witnesses, or by some internal parts of
       typerep. you should feel bad if you need to use it in some user code *)
    val internal_use_only : ('a, 'b) Tag_internal.t -> ('a, 'b) t
  end = struct
    include Tag_internal
    let label t = t.label
    let arity t = t.arity
    let index t = t.index
    let ocaml_repr t = t.ocaml_repr
    let create t = t.create
    let tyid t = t.tyid
    let traverse t = t.rep

    let internal_use_only t = t
  end

  module Variant_internal = struct
    type _ tag = Tag : ('variant, 'a) Tag.t -> 'variant tag
    type _ value = Value : ('variant, 'a) Tag.t * 'a -> 'variant value
    type 'a t = {
      typename : 'a Typename.t;
      tags : 'a tag array;
      polymorphic : bool;
      value : 'a -> 'a value;
    }
  end

  module Variant : sig

    (**
       An existential type used to gather all the tags constituing a variant
       type. the ['variant] parameter is the variant type, it is the same for all the
       constructors of that variant type. The type of the parameters might be different
       for each constructor and is thus existential
    *)
    type _ tag = Tag : ('variant, 'args) Tag.t -> 'variant tag

    (**
       A similar existential constructor to [_ tag] but this one holds a value whose type
       is the arguments of the tag constructor.  A value of type ['a value] is a pair of
       (1) a value of variant type ['a] along with (2) some information about the
       constructor within the type ['a]
    *)
    type _ value = Value : ('variant, 'args) Tag.t * 'args -> 'variant value

    (**
       Witness of a variant type. The parameter is the type of the variant type witnessed.
    *)
    type 'a t

    val typename_of_t : 'a t -> 'a Typename.t

    (**
       Returns the number of tags of this variant type definition.
    *)
    val length : 'a t -> int

    (**
       Get the nth tag of this variant type, indexed from 0.
    *)
    val tag : 'a t -> int -> 'a tag

    (**
       Distinguish polymorphic variants and standard variants. Typically, polymorphic
       variants tags starts with the [`] character.
       Example
       polymorphic variant: type t = [ `A | `B ]
       standard variant:    type t = A | B
    *)
    val is_polymorphic : _ t -> bool

    (**
       Pattern matching on a value of this variant type.
    *)
    val value : 'a t -> 'a -> 'a value

    (**
       folding along the tags of the variant type
    *)
    val fold : 'a t -> init:'acc -> f:('acc -> 'a tag -> 'acc) -> 'acc

    (* used by the camlp4 extension to build type witnesses, or by some internal parts of
       typerep. you should feel bad if you need to use it in some user code *)
    val internal_use_only : 'a Variant_internal.t -> 'a t
  end = struct
    include Variant_internal
    let typename_of_t t = t.typename
    let length t = Array.length t.tags
    let tag t index = t.tags.(index)
    let is_polymorphic t = t.polymorphic
    let value t = t.value

    let fold t ~init ~f = Array.fold_left f init t.tags

    let internal_use_only t = t
  end

  module Field_internal = struct
    type ('record, 'field) t = {
      label : string;
      rep : 'field X.t;
      index : int;
      tyid : 'field Typename.t;
      get : ('record -> 'field);
      (* set : ('record -> 'field -> unit) option; (\* mutable field *\) *)
    }
  end

  (**
     Witness of a field, that is an item in a record type.
     The first parameter is the record type, the second is the type of the field.
     Example:

     type t = \{ x : int ; y : string \}

     This type has two fields. for each of them we'll have a corresponding [Field.t]

     val field_x : (t, int) Field.t
     val field_y : (t, string) Field.t
  *)
  module Field : sig
    type ('record, 'field) t

    (**
       The name of the field as it is given in the concrete syntax
       Examples:
       \{ x   : int;     (* "x" *)
         foo : string;  (* "foo" *)
         bar : float;   (* "bar" *)
       \}
    *)
    val label : (_, _) t -> string

    (**
       The 0-based index of the field in the list of all fields for this record type.
       Example:
       type t = \{
         x   : int;     (* 0 *)
         foo : string;  (* 1 *)
         bar : string;  (* 2 *)
       \}
    *)
    val index : (_, _) t -> int

    (**
       Field accessors. This corresponds to the dot operation.
       [Field.get bar_field t] returns the field [bar] of the record value [t], just the
       same as [t.bar]
    *)
    val get : ('record, 'field) t -> 'record -> 'field

    (** return the type_name of the arguments.  Might be used to perform some lookup based
        on it *)
    val tyid : (_, 'field) t -> 'field Typename.t

    (** get the computation of the arguments *)
    val traverse : (_, 'field) t -> 'field X.t

    (* used by the camlp4 extension to build type witnesses, or by some internal parts of
       typerep. you should feel bad if you need to use it in some user code *)
    val internal_use_only : ('a, 'b) Field_internal.t -> ('a, 'b) t
  end = struct
    include Field_internal
    let label t = t.label
    let index t = t.index
    let get t = t.get
    let tyid t = t.tyid
    let traverse t = t.rep

    let internal_use_only t = t
  end

  module Record_internal = struct
    type _ field = Field : ('record, 'a) Field.t -> 'record field
    type 'record fields = { get : 'field. ('record, 'field) Field.t -> 'field }
    type 'a t = {
      typename : 'a Typename.t;
      fields : 'a field array;
      has_double_array_tag : bool;
      create : 'a fields -> 'a;
    }
  end

  module Record : sig

    (**
       An existential type used to gather all the fields constituing a record type. the
       ['record] parameter is the record type, it is the same for all the field of that
       record type. The type of the fields might be different for each field and is thus
       existential.
    *)
    type _ field = Field : ('record, 'a) Field.t -> 'record field

    (**
       ['record fields] is a type isomorphic to ['record].  This gives a way to get the
       field value for each field of the record.  The advantage of this representation is
       that it is convenient for writing generic computations.
    *)
    type 'record fields = { get : 'field. ('record, 'field) Field.t -> 'field }

    (**
       Witness of a record type. The parameter is the type of the record type witnessed.
    *)
    type 'a t

    val typename_of_t : 'a t -> 'a Typename.t

    (**
       Returns the number of fields of this record type definition.
    *)
    val length : 'a t -> int

    (**
       Get the nth field of this record type, indexed from 0.
    *)
    val field : 'a t -> int -> 'a field

    (**
       This is a low level metadata regarding the way the ocaml compiler represent the
       array underneath that is the runtime value of a record of type ['a] given a witness
       of type ['a t]. [has_double_array_tag w] returns [true] if the array that
       represents runtime values of this type is an optimized ocaml float array.
       Typically, this will be true for record where all fields are statically known as to
       be [floats].

       Note that you can't get this information dynamically by inspecting the typerep once
       it is applied, because there is at this point no way to tell whether one of the
       field is polymorphic in the type definition.
    *)
    val has_double_array_tag : _ t -> bool

    (**
       Expose one direction of the isomorphism between a value of type ['a] and a value of
       type ['a fields]. Basically, given an encoding way of accessing the value of all
       the fields of a record, create that record and return it.
    *)
    val create : 'a t -> 'a fields -> 'a

    (**
       folding along the tags of the variant type
    *)
    val fold : 'a t -> init:'acc -> f:('acc -> 'a field -> 'acc) -> 'acc

    (* used by the camlp4 extension to build type witnesses, or by some internal parts of
       typerep. you should feel bad if you need to use it in some user code *)
    val internal_use_only : 'a Record_internal.t -> 'a t
  end = struct
    include Record_internal
    let typename_of_t t = t.typename
    let length t = Array.length t.fields
    let field t index = t.fields.(index)
    let has_double_array_tag t = t.has_double_array_tag
    let create t = t.create
    let fold t ~init ~f = Array.fold_left f init t.fields

    let internal_use_only t = t
  end
end

module type S = sig
  type 'a t
  include (module type of M (struct type 'a rep = 'a t type 'a t = 'a rep end))
end