This file is indexed.

/usr/lib/ocaml/raw_spacetime_lib.mli is in ocaml-nox 4.05.0-10ubuntu1.

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
(**************************************************************************)
(*                                                                        *)
(*                                 OCaml                                  *)
(*                                                                        *)
(*           Mark Shinwell and Leo White, Jane Street Europe              *)
(*                                                                        *)
(*   Copyright 2015--2016 Jane Street Group LLC                           *)
(*                                                                        *)
(*   All rights reserved.  This file is distributed under the terms of    *)
(*   the GNU Lesser General Public License version 2.1, with the          *)
(*   special exception on linking described in the file LICENSE.          *)
(*                                                                        *)
(**************************************************************************)

(** Access to the information recorded by the [Spacetime]
    module.  (It is intended that this module will be used by
    post-processors rather than users wishing to understand their
    programs.)
    For 64-bit targets only.
    This module may be used from any program, not just one compiled
    with a compiler configured for Spacetime. *)

module Gc_stats : sig
  type t

  val minor_words : t -> int
  val promoted_words : t -> int
  val major_words : t -> int
  val minor_collections : t -> int
  val major_collections : t -> int
  val heap_words : t -> int
  val heap_chunks : t -> int
  val compactions : t -> int
  val top_heap_words : t -> int
end

module Annotation : sig
  (** An annotation written into a value's header.  These may be looked up
      in a [Trace.t] (see below). *)
  type t

  (* CR-someday mshinwell: consider using tag and size to increase the
     available space of annotations.  Need to be careful of [Obj.truncate].
     Could also randomise the tags on records.
  *)

  val to_int : t -> int
end

module Program_counter : sig
  module OCaml : sig
    type t

    val to_int64 : t -> Int64.t
  end

  module Foreign : sig
    type t

    val to_int64 : t -> Int64.t
  end

end

module Frame_table : sig
  (* CR-someday mshinwell: move to [Gc] if dependencies permit? *)
  (** A value of type [t] corresponds to the frame table of a running
      OCaml program.  The table is indexed by program counter address
      (typically, but not always when using Spacetime, return addresses). *)
  type t

  (** Find the location, including any inlined frames, corresponding to the
      given program counter address.  Raises [Not_found] if the location
      could not be resolved. *)
  val find_exn : Program_counter.OCaml.t -> t -> Printexc.Slot.t list
end

module Function_entry_point : sig
  type t

  val to_int64 : t -> Int64.t
end

module Function_identifier : sig
  type t
  (* CR-soon mshinwell: same as [Function_entry_point] now *)
  val to_int64 : t -> Int64.t
end

module Shape_table : sig
  type t
end

module Trace : sig
  (** A value of type [t] holds the dynamic call structure of the program
      (i.e. which functions have called which other functions) together with
      information required to decode profiling annotations written into
      values' headers. *)
  type t

  type node
  type ocaml_node
  type foreign_node
  type uninstrumented_node

  module OCaml : sig
    module Allocation_point : sig
      (** A value of type [t] corresponds to an allocation point in OCaml
          code. *)
      type t

      (** The program counter at (or close to) the allocation site. *)
      val program_counter : t -> Program_counter.OCaml.t

      (** The annotation written into the headers of boxed values allocated
          at the given allocation site. *)
      val annotation : t -> Annotation.t

      (** The total number of words allocated at this point. *)
      val num_words_including_headers : t -> int
    end

    module Direct_call_point : sig
      (** A value of type ['target t] corresponds to a direct (i.e. known
          at compile time) call point in OCaml code.  ['target] is the type
          of the node corresponding to the callee. *)
      type 'target t

      (** The program counter at (or close to) the call site. *)
      val call_site : _ t -> Program_counter.OCaml.t

      (** The address of the first instruction of the callee. *)
      val callee : _ t -> Function_entry_point.t

      (** The node corresponding to the callee. *)
      val callee_node : 'target t -> 'target
    end

    module Indirect_call_point : sig
      (** A value of type [t] corresponds to an indirect call point in OCaml
          code.  Each such value contains a list of callees to which the
          call point has branched. *)
      type t

      (** The program counter at (or close to) the call site. *)
      val call_site : t -> Program_counter.OCaml.t

      module Callee : sig
        type t

        (** The address of the first instruction of the callee. *)
        val callee : t -> Function_entry_point.t

        (** The node corresponding to the callee. *)
        val callee_node : t -> node

        (** Move to the next callee to which this call point has branched.
            [None] is returned when the end of the list is reached. *)
        val next : t -> t option
      end

      (** The list of callees to which this indirect call point has
          branched. *)
      val callees : t -> Callee.t option
    end

    module Field : sig
      (** A value of type [t] enables iteration through the contents
          ("fields") of an OCaml node. *)
      type t

      type direct_call_point =
        | To_ocaml of ocaml_node Direct_call_point.t
        | To_foreign of foreign_node Direct_call_point.t
        (* CR-soon mshinwell: once everything's finished, "uninstrumented"
           should be able to go away.  Let's try to do this after the
           first release. *)
        | To_uninstrumented of
            uninstrumented_node Direct_call_point.t

      type classification =
        | Allocation of Allocation_point.t
        | Direct_call of direct_call_point
        | Indirect_call of Indirect_call_point.t

      val classify : t -> classification
      val next : t -> t option
    end

    module Node : sig
      (** A node corresponding to an invocation of a function written in
          OCaml. *)
      type t = ocaml_node

      val compare : t -> t -> int

      (** A unique identifier for the function corresponding to this node. *)
      val function_identifier : t -> Function_identifier.t

      (** This function traverses a circular list. *)
      val next_in_tail_call_chain : t -> t

      val fields : t -> shape_table:Shape_table.t -> Field.t option
    end
  end

  module Foreign : sig
    module Allocation_point : sig
      (** A value of type [t] corresponds to an allocation point in non-OCaml
          code. *)
      type t

      val program_counter : t -> Program_counter.Foreign.t
      val annotation : t -> Annotation.t
      val num_words_including_headers : t -> int
    end

    module Call_point : sig
      (** A value of type [t] corresponds to a call point from non-OCaml
          code (to either non-OCaml code, or OCaml code via the usual
          assembly veneer). *)
      type t

      (** N.B. The address of the callee (of type [Function_entry_point.t]) is
          not available.  It must be recovered during post-processing. *)
      val call_site : t -> Program_counter.Foreign.t
      val callee_node : t -> node
    end

    module Field : sig
      (** A value of type [t] enables iteration through the contents ("fields")
          of a C node. *)
      type t

      type classification = private
        | Allocation of Allocation_point.t
        | Call of Call_point.t

      val classify : t -> classification
      val next : t -> t option
    end

    module Node : sig
      (** A node corresponding to an invocation of a function written in C
          (or any other language that is not OCaml). *)
      type t = foreign_node

      val compare : t -> t -> int

      val fields : t -> Field.t option

    end

  end

  module Node : sig
    (** Either an OCaml or a foreign node; or an indication that this
        is a branch of the graph corresponding to uninstrumented
        code. *)
    type t = node

    val compare : t -> t -> int

    type classification = private
      | OCaml of OCaml.Node.t
      | Foreign of Foreign.Node.t

    val classify : t -> classification

    val of_ocaml_node : OCaml.Node.t -> t
    val of_foreign_node : Foreign.Node.t -> t

    module Set : Set.S with type elt = t
    module Map : Map.S with type key = t
  end

  (** Obtains the root of the graph for traversal.  [None] is returned if
      the graph is empty. *)
  val root : t -> Node.t option
end

module Heap_snapshot : sig
  type t
  type heap_snapshot = t

  module Entries : sig
    (** An immutable array of the total number of blocks (= boxed
        values) and the total number of words occupied by such blocks
        (including their headers) for each profiling annotation in
        the heap. *)
    type t

    val length : t -> int
    val annotation : t -> int -> Annotation.t
    val num_blocks : t -> int -> int
    val num_words_including_headers : t -> int -> int

  end

  (** The timestamp of a snapshot.  The units are as for [Sys.time]
      (unless custom timestamps are being provided, cf. the [Spacetime] module
      in the standard library). *)
  val timestamp : t -> float

  val gc_stats : t -> Gc_stats.t
  val entries : t -> Entries.t
  val words_scanned : t -> int
  val words_scanned_with_profinfo : t -> int

  module Total_allocation : sig
    type t

    val annotation : t -> Annotation.t
    val num_words_including_headers : t -> int
    val next : t -> t option
  end
  (** Total allocations across *all threads*. *)
  (* CR-someday mshinwell: change the relevant variables to be thread-local *)
  val total_allocations : t -> Total_allocation.t option

  module Event : sig
    type t

    val event_name : t -> string
    val timestamp : t -> float
  end

  module Series : sig
    type t

    (** At present, the [Trace.t] associated with a [Series.t] cannot be
        garbage collected or freed.  This should not be a problem, since
        the intention is that a post-processor reads the trace and outputs
        another format. *)
    val read : path:string -> t

    val time_of_writer_close : t -> float
    val num_threads : t -> int

    type trace_kind = Normal | Finaliser
    val trace : t -> kind:trace_kind -> thread_index:int -> Trace.t option

    val frame_table : t -> Frame_table.t
    val shape_table : t -> Shape_table.t
    val num_snapshots : t -> int
    val snapshot : t -> index:int -> heap_snapshot
    val events : t -> Event.t list
  end
end