This file is indexed.

/usr/lib/ocaml/utop/uTop.mli is in libutop-ocaml-dev 1.19.3-2build1.

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
(*
 * uTop.mli
 * --------
 * Copyright : (c) 2011, Jeremie Dimino <jeremie@dimino.org>
 * Licence   : BSD3
 *
 * This file is a part of utop.
 *)

(** UTop configuration. *)

open React

val version : string
  (** Version of utop. *)

val count : int React.signal
  (** The number of commands already executed. *)

val keywords : Set.Make(String).t ref
  (** The set of OCaml keywords. *)

val add_keyword : string -> unit
  (** Add a new OCaml keyword. *)

val require : string list -> unit
  (** Load all the given findlib packages *)

type ui = Console | Emacs
    (** The user interface in use. *)

val get_ui : unit -> ui
  (** Returns the user interface in use. *)

val hide_reserved : bool signal
  (** If [true] (the default) identifiers starting with a '_' will be hidden from the
      output. i.e. the following phrase won't produces any output:

      {[
        let _x = 1
      ]}

      This is for hidding variables created by code generators for internal use. It can
      also be set/unset by the command line options [-hide-reserved] and [-show-reserved].
  *)

val get_hide_reserved : unit -> bool
  (** Returns the value of {!hide_reserved}. *)

val set_hide_reserved : bool -> unit
  (** Modifies {!hide_reserved}. *)

val topfind_verbose : bool signal
  (** If [false] (the default) messages from findlib are hidden. This is only effective
      with findlib >= 1.4. *)

val get_topfind_verbose : unit -> bool
  (** Returns the value of {!topfind_verbose}. *)

val set_topfind_verbose : bool -> unit
  (** Modifies {!topfind_verbose}. *)

val topfind_log : string list signal
  (** List of messages logged by findlib since the beginning of the session. This
      requires findlib >= 1.4. *)

val show_box : bool signal
  (** If [true] (the default) the completion bar is displayed. *)

val get_show_box : unit -> bool
  (** Returns the value of {!show_box}. *)

val set_show_box : bool -> unit
  (** Modifies {!show_box}. *)

val set_margin_function : (LTerm_geom.size -> int option) -> unit
  (** Margin of the standard and error formatters as a function of the screen size.

      The default is:

      {[
        fun size -> Some (max 80 size.cols)
      ]}
  *)

(** Syntax. *)
type syntax =
  | Normal
      (** No camlp4. *)
  | Camlp4o
      (** Camlp4, original syntax. *)
  | Camlp4r
      (** Camlp4, revised syntax. *)

val syntax : syntax signal
  (** The syntax in use. If it is {!Camlp4o} or {!Camlp4r} quotations
      are recognized. It is modified when you type [#camlp4o] or
      [#camlp4r]. At the beginning it is {!Normal}. *)

val get_syntax : unit -> syntax
  (** Returns the current value of {!syntax}. *)

val set_syntax : syntax -> unit
  (** Changes the syntax used in utop. If the syntax is the same as
      the current one, it does nothing. Otherwise it loads camlp4 and
      setup several configuration variables.

      Notes:
      - the syntax can only be changed once. Once you set it to
        {!Camlp4o} or {!Camlp4r} you cannot change it again.
      - Typing [#camlp4o] is the same as calling [set_syntax Camlp4o].
      - Typing [#camlp4r] is the same as calling [set_syntax Camlp4r]. *)

val phrase_terminator : string signal
  (** The phrase terminator. It is ";;" by default and ";" when you
      use revised syntax. *)

val get_phrase_terminator : unit -> string
  (** Returns the value of {!phrase_terminator}. *)

val set_phrase_terminator : string -> unit
  (** Modifies {!phrase_terminator}. *)

val auto_run_lwt : bool signal
  (** If [true] (the default) toplevel lwt expressions are
      automatically run with [Lwt_main.run]. i.e. if you type:

      {[
        Lwt_io.printl "Hello, world"
      ]}

      this will be replaced by:

      {[
        Lwt_main.run (Lwt_io.printl "Hello, world")
      ]}
  *)

val get_auto_run_lwt : unit -> bool
  (** Returns the value of {!auto_run_lwt}. *)

val set_auto_run_lwt : bool -> unit
  (** Modifies {!auto_run_lwt}. *)

val auto_run_async : bool signal
  (** If [true] (the default) toplevel Async expressions are
      automatically run with in a separate thread with
      [Thread_safe.block_on_async_exn]. i.e. if you type:

      {[
        after (Time.Span.of_s 1.0)
      ]}

      this will be replaced by:

      {[
        Thread_safe.block_on_async_exn (fun () -> after (Time.Span.of_s 1.0))
      ]}
  *)

val get_auto_run_async : unit -> bool
  (** Returns the value of {!auto_run_async}. *)

val set_auto_run_async : bool -> unit
  (** Modifies {!auto_run_async}. *)

val end_and_accept_current_phrase : LTerm_read_line.action
 (** Action that add the phrase terminator at the end of the current phrase
     and accepts it. For instance to avoid typing [;;], add this to your
     ~/.ocamlinit:

     {[
       #require "lambda-term";;
       LTerm_read_line.bind
         [ { control = false; meta = false; shift = false; code = Enter } ]
         [ UTop.end_and_accept_current_phrase ]
     ]}
 *)

(** External editor command. [None] for default. *)
val external_editor : string signal
val set_external_editor : string -> unit
val get_external_editor : unit -> string

(** {6 History} *)

val history : LTerm_history.t
  (** The history used by utop. You can configure limits using the
      [LTerm_history] module.

      For example if you want to limit the history to 1000 line, add
      these lines to your ~/.ocamlinit file:

      {[
        #require "lambda-term";;
        LTerm_history.set_max_entries UTop.history 1000;;
      ]}
  *)

val history_file_name : string option ref
  (** Name of the history file. If [None], no history will be loaded
      or saved. *)

val history_file_max_size : int option ref
  (** Maximum size of the history file. If [None] (the default) the
      maximum size of [history] will be used. *)

val history_file_max_entries : int option ref
  (** Maximum entries to store in the history file. If [None] (the
      default) the maximum number of entries if [history] will be
      used. *)

(** {6 Console specific configuration} *)

type profile = Dark | Light
    (** Profile for colors. *)

val profile : profile React.signal
  (** The color profile. It defaults to {!Dark}. This is used by the
      default prompt to choose colors. *)

val set_profile : profile -> unit
  (** Sets the color profile. *)

val size : LTerm_geom.size React.signal
  (** The current size of the terminal. This is used only in the
      console UI. *)

val key_sequence : LTerm_key.t list React.signal
  (** The current key sequence entered by the user. This is used only
      in the console UI. *)

val time : float ref
  (** The time of the beginning of the current command. *)

val prompt : LTerm_text.t React.signal ref
  (** The prompt. *)

(** {6 Hooks} *)

val new_command_hooks : (unit -> unit) Lwt_sequence.t
  (** Functions called before each new command. *)

val at_new_command : (unit -> unit) -> unit
  (** [at_new_command f] adds [f] to the hooks executed before each
      new commands. *)

(** {6 Parsing} *)

type location = int * int
    (** Type of a string-location. It is composed of a start and stop
        offsets (in bytes). *)

(** Result of a function processing a programx. *)
type 'a result =
  | Value of 'a
      (** The function succeeded and returned this value. *)
  | Error of location list * string
      (** The function failed. Arguments are a list of locations to
          highlight in the source and an error message. *)

exception Need_more
  (** Exception raised by a parser when it need more data. *)

val parse_use_file : (string -> bool -> Parsetree.toplevel_phrase list result) ref

val parse_use_file_default : string -> bool -> Parsetree.toplevel_phrase list result
  (** The default parser for toplevel regions. It uses the standard
      ocaml parser. *)

val parse_toplevel_phrase : (string -> bool -> Parsetree.toplevel_phrase result) ref
  (** [parse_toplevel_phrase] is the function used to parse a phrase
      typed in the toplevel.

      Its arguments are:
      - [input]: the string to parse
      - [eos_is_error]

      If [eos_is_error] is [true] and the parser reach the end of
      input, then {!Parse_failure} should be returned.

      If [eos_is_error] is [false] and the parser reach the end of
      input, the exception {!Need_more} must be thrown.

      Except for {!Need_more}, the function must not raise any
      exception. *)

val parse_toplevel_phrase_default : string -> bool -> Parsetree.toplevel_phrase result
  (** The default parser for toplevel phrases. It uses the standard
      ocaml parser. *)

val parse_default : (Lexing.lexbuf -> 'a) -> string -> bool -> 'a result
  (** The default parser. It uses the standard ocaml parser. *)

val input_name : string
  (** The name you must use in location to let ocaml know that it is
      from the toplevel. *)

val lexbuf_of_string : bool ref -> string -> Lexing.lexbuf
  (** [lexbuf_of_string eof str] is the same as [Lexing.from_string
      str] except that if the lexer reach the end of [str] then [eof] is
      set to [true]. *)

(** {6 Helpers} *)

val get_message : (Format.formatter -> 'a -> unit) -> 'a -> string
  (** [get_message printer x] applies [printer] on [x] and
      returns everything it prints as a string. *)

val get_ocaml_error_message : exn -> location * string
  (** [get_ocaml_error_message exn] returns the location and error
      message for the exception [exn] which must be an exception from
      the compiler. *)

val check_phrase : Parsetree.toplevel_phrase -> (location list * string) option
  (** [check_phrase phrase] checks that [phrase] can be executed
      without typing or compilation errors. It returns [None] if
      [phrase] is OK and an error message otherwise.

      If the result is [None] it is guaranteed that
      [Toploop.execute_phrase] won't raise any exception. *)

val collect_formatters : Buffer.t -> Format.formatter list -> (unit -> 'a) -> 'a
  (** [collect_formatters buf pps f] executes [f] and redirect
      everything it prints on [pps] to [buf]. *)

val discard_formatters : Format.formatter list -> (unit -> 'a) -> 'a
  (** [discard_formatters pps f] executes [f], dropping everything it
      prints on [pps]. *)

val split_words : string -> string list

(** {6 compiler-libs reexports} *)

val load_path : string list ref
  (** [load_path] is an alias of [Config.load_path], normally hidden in toplevel.
      It contains the list of directories added by findlib-required packages
      and [#directory] directives. *)

(**/**)

(* These variables are not used and deprecated: *)

val prompt_continue : LTerm_text.t React.signal ref
val prompt_comment : LTerm_text.t React.signal ref
val smart_accept : bool ref
val new_prompt_hooks : (unit -> unit) Lwt_sequence.t
val at_new_prompt : (unit -> unit) -> unit