This file is indexed.

/usr/lib/ocaml/dose2/fragments.mli is in libdose2-ocaml-dev 1.4.2-6build1.

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
(* Copyright 2005-2007 Berke DURAK, INRIA Rocquencourt.

This file is part of Dose2.

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

Dose2 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 Lesser General Public License for more details.

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

(** General literate module

    This module provides low-level functions for doing structured data I/O.
*)

exception Error of string
val sf : ('a, unit, string) format -> 'a
(** Data tags *)
type tag =
| T_LParen
| T_RParen
| T_LBrack
| T_RBrack
| T_LBrace
| T_RBrace
| T_Equal
| T_Comma
| T_Semicolon
| T_Array
| T_Hashtbl
| T_Set
;;

val tags : tag list (** List of all existing tags *)

(** Functions for interconverting tags and purely alphabetical lowercase strings *)
val string_of_tag : tag -> string
(*val short_string_of_tag : tag -> string*)
val tag_of_string : string -> tag

(** Functions for interconverting tags and integers between 0 and [max_tag] *)
val int_of_tag : tag -> int
val tag_of_int : int -> tag
val max_tag : int (** Note that in order to reserver space for future tags, max_tag can be higher than the number of
existing tags. *)

val is_start_tag : tag -> bool (** Suggest open a pretty-printing box *)
val is_end_tag : tag -> bool   (** Suggest to close a pretty-printing box *)

(** Tokens used by the lower-level I/O functions *)
type token =
| Bool of bool
| Char of char
| Int of int
| Int64 of int64
| Float of float
| String of string
| Tag of tag
| Field of string
| Constructor of string
| EOF

val string_of_token : token -> string (** Build a string representation of a token (usually for debugging) *)

type io_in  (** The type of input channels *)
type io_out (** The type of output channels *)
val string_of_token : token -> string

val create_io_in :
  read_token:(unit -> token) ->
  peek_token:(unit -> token) ->
  ?finish:(io_in -> unit -> unit) -> unit -> io_in 
  (** Create an input channel from the given functions *)

val flush : io_out -> unit

val is_word_reserved : string -> bool
  (** Is this a reserved word, such as array, hash or set ? *)
val is_tag_voluminous : tag -> bool
  (** Does this tag require space around it ? *)

(** On failure, the following functions raise an Error(...) exception containing a useful message. *)
val drop_token : io_in -> unit
  (** Remove a token from an input channel *)
val peek_token : io_in -> token
  (** Peek a token from an input channel *)
val read_token : io_in -> token
  (** Read a token from an input channel *)
val read_tag : io_in -> tag
  (** Read a tag token. *)
val read_this_tag : io_in -> tag -> unit
  (** Read this particular tag. *)
val finish : io_in -> unit
  (** Finish consuming the input.  Actually, this matches the Stop_data tag. *)
val read_int : io_in -> int
  (** Read an integer. *)
val read_int64 : io_in -> int64
  (** Read a 64-bit integer. *)
val read_float : io_in -> float
  (** Read a floating-point number. *)
val read_bool : io_in -> bool
  (** Read a boolean. *)
val read_char : io_in -> char
  (** Read a character. *)
val read_field : io_in -> string
  (** Read a field label. *)
val read_constructor : io_in -> string
  (** Read a constructor name. *)
val read_string : io_in -> string
  (** Read a string. *)
val loss : io_in -> unit
  (** Signal that some data has been lost.  This will be called, for instance, if the reader sees an unknown record
      field name. *)
val lost : io_in -> bool
  (** Tells us if any data has been lost, e.g., if [loss] has ever been called on this channel. *)

val create_io_out : write_token:(token -> unit) -> ?flush:(unit -> unit) -> unit -> io_out
  (** Create an output channel from the given functions. *)

val write_token : io_out -> token -> unit
  (** Write a token. *)
val write_int : io_out -> int -> unit
  (** Write an integer. *)
val write_int64 : io_out -> int64 -> unit
  (** Write a 64-bit integer. *)
val write_char : io_out -> char -> unit
  (** Write a char. *)
val write_string : io_out -> string -> unit
  (** Write a string. *)
val write_bool : io_out -> bool -> unit
  (** Write a boolean. *)
val write_float : io_out -> float -> unit
  (** Write a floating-point number. *)
val write_tag : io_out -> tag -> unit
  (** Write a tag. *)
val write_field : io_out -> string -> unit
  (** Write a fiel label. *)
val write_constructor : io_out -> string -> unit
  (** Write a constructor name. *)