This file is indexed.

/usr/lib/ocaml/zed/zed_utf8.mli is in libzed-ocaml-dev 1.4-2.

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

(** UTF-8 enoded strings *)

open CamomileLibrary

type t = string
    (** Type of UTF-8 encoded strings. *)

exception Invalid of string * string
  (** [Invalid(error, text)] Exception raised when an invalid UTF-8
      encoded string is encountered. [text] is the faulty text and
      [error] is a description of the first error in [text]. *)

exception Out_of_bounds
  (** Exception raised when trying to access a character which is
      outside the bounds of a string. *)

(** {6 Validation} *)

(** Result of cheking a string for correct UTF-8. *)
type check_result =
  | Correct of int
      (** The string is correctly UTF-8 encoded, and the paramter is
          the length of the string. *)
  | Message of string
      (** The string is invalid and the parameter is an error
          message. *)

val check : t -> check_result
  (** [check str] checks that [str] is a valid UTF-8 encoded
      string. *)

val validate : t -> int
  (** Same as check but raises an exception in case the argument is
      not a valid text, otherwise returns the length of the string. *)

val next_error : t -> int -> int * int * string
  (** [next_error str ofs] returns [(ofs', count, msg)] where [ofs']
      is the offset of the start of the first invalid sequence after
      [ofs] (inclusive) in [str], [count] is the number of unicode
      character between [ofs] and [ofs'] (exclusive) and [msg] is an
      error message. If there is no error until the end of string then
      [ofs] is [String.length str] and [msg] is the empty string. *)

(** {6 Construction} *)

val singleton : UChar.t -> t
  (** [singleton ch] creates a string of length 1 containing only the
      given character. *)

val make : int -> UChar.t -> t
  (** [make n ch] creates a string of length [n] filled with [ch]. *)

val init : int -> (int -> UChar.t) -> t
  (** [init n f] returns the contenation of [singleton (f 0)],
      [singleton (f 1)], ..., [singleton (f (n - 1))]. *)

val rev_init : int -> (int -> UChar.t) -> t
  (** [rev_init n f] returns the contenation of [singleton (f (n -
      1))], ..., [singleton (f 1)], [singleton (f 0)]. *)

(** {6 Informations} *)

val length : t -> int
  (** Returns the length of the given string. *)

(** {6 Comparison} *)

val compare : t -> t -> int
  (** Compares two strings (in code point order). *)

(** {6 Random access} *)

val get : t -> int -> UChar.t
  (** [get str idx] returns the character at index [idx] in
      [str]. *)

(** {6 String manipulation} *)

val sub : t -> int -> int -> t
  (** [sub str ofs len] Returns the sub-string of [str] starting at
      [ofs] and of length [len]. *)

val break : t -> int -> t * t
  (** [break str pos] returns the sub-strings before and after [pos]
      in [str]. It is more efficient than creating two sub-strings
      with {!sub}. *)

val before : t -> int -> t
  (** [before str pos] returns the sub-string before [pos] in [str] *)

val after : t -> int -> t
  (** [after str pos] returns the sub-string after [pos] in [str] *)

val insert : t -> int -> t -> t
  (** [insert str pos sub] inserts [sub] in [str] at position
      [pos]. *)

val remove : t -> int -> int -> t
  (** [remove str pos len] removes the [len] characters at position
      [pos] in [str] *)

val replace : t -> int -> int -> t -> t
  (** [replace str pos len repl] replaces the [len] characters at
      position [pos] in [str] by [repl]. *)

(** {6 Tranformation} *)

val rev : t -> t
  (** [rev str] reverses all characters of [str]. *)

val concat : t -> t list -> t
  (** [concat sep l] returns the concatenation of all strings of [l]
      separated by [sep]. *)

val rev_concat : t -> t list -> t
  (** [concat sep l] returns the concatenation of all strings of [l]
      in reverse order separated by [sep]. *)

val explode : t -> UChar.t list
  (** [explode str] returns the list of all characters of [str]. *)

val rev_explode : t -> UChar.t list
  (** [rev_explode str] returns the list of all characters of [str] in
      reverse order. *)

val implode : UChar.t list -> t
  (** [implode l] returns the concatenation of all characters of [l]. *)

val rev_implode : UChar.t list -> t
  (** [rev_implode l] is the same as [implode (List.rev l)] but more
      efficient. *)

(** {6 Text traversals} *)

val iter : (UChar.t -> unit) -> t -> unit
  (** [iter f str] applies [f] an all characters of [str] starting
      from the left. *)

val rev_iter : (UChar.t -> unit) -> t -> unit
  (** [rev_iter f str] applies [f] an all characters of [str] starting
      from the right. *)

val fold : (UChar.t -> 'a -> 'a) -> t -> 'a -> 'a
  (** [fold f str acc] applies [f] on all characters of [str]
      starting from the left, accumulating a value. *)

val rev_fold : (UChar.t -> 'a -> 'a) -> t -> 'a -> 'a
  (** [rev_fold f str acc] applies [f] on all characters of [str]
      starting from the right, accumulating a value. *)

val map : (UChar.t -> UChar.t) -> t -> t
  (** [map f str] maps all characters of [str] with [f]. *)

val rev_map : (UChar.t -> UChar.t) -> t -> t
  (** [rev_map f str] maps all characters of [str] with [f] in reverse
      order. *)

val map_concat : (UChar.t -> t) -> t -> t
  (** [map f str] maps all characters of [str] with [f] and
      concatenate the result. *)

val rev_map_concat : (UChar.t -> t) -> t -> t
  (** [rev_map f str] maps all characters of [str] with [f] in reverse
      order and concatenate the result. *)

val filter : (UChar.t -> bool) -> t -> t
  (** [filter f str] filters characters of [str] with [f]. *)

val rev_filter : (UChar.t -> bool) -> t -> t
  (** [rev_filter f str] filters characters of [str] with [f] in
      reverse order. *)

val filter_map : (UChar.t -> UChar.t option) -> t -> t
  (** [filter_map f str] filters and maps characters of [str] with
      [f]. *)

val rev_filter_map : (UChar.t -> UChar.t option) -> t -> t
  (** [rev_filter_map f str] filters and maps characters of [str] with
      [f] in reverse order. *)

val filter_map_concat : (UChar.t -> t option) -> t -> t
  (** [filter_map f str] filters and maps characters of [str] with [f]
      and concatenate the result. *)

val rev_filter_map_concat : (UChar.t -> t option) -> t -> t
  (** [rev_filter_map f str] filters and maps characters of [str] with
      [f] in reverse order and concatenate the result. *)

(** {6 Scanning} *)

val for_all : (UChar.t -> bool) -> t -> bool
  (** [for_all f text] returns whether all characters of [text] verify
      the predicate [f]. *)

val exists : (UChar.t -> bool) -> t -> bool
  (** [exists f text] returns whether at least one character of [text]
      verify [f]. *)

val count : (UChar.t -> bool) -> t -> int
  (** [count f text] returhs the number of characters of [text]
      verifying [f]. *)

(** {6 Tests} *)

val contains : t -> t -> bool
  (** [contains text sub] returns whether [sub] appears in [text] *)

val starts_with : t -> t -> bool
  (** [starts_with text prefix] returns [true] iff [s] starts with
      [prefix]. *)

val ends_with : t -> t -> bool
  (** [ends_with text suffix] returns [true] iff [s] ends with
      [suffix]. *)

(** {6 Stripping} *)

val strip : ?predicate : (UChar.t -> bool) -> t -> t
  (** [strip ?predicate text] returns [text] without its firsts and
      lasts characters that match [predicate]. [predicate] default to
      testing whether the given character has the [`White_Space]
      unicode property. For example:

      {[
        strip "\n  foo\n  " = "foo"
      ]}
  *)

val lstrip : ?predicate : (UChar.t -> bool) -> t -> t
  (** [lstrip ?predicate text] is the same as {!strip} but it only
      removes characters at the left of [text]. *)

val rstrip : ?predicate : (UChar.t -> bool) -> t -> t
  (** [lstrip ?predicate text] is the same as {!strip} but it only
      removes characters at the right of [text]. *)

val lchop : t -> t
  (** [lchop t] returns [t] without is first character. Returns [""]
      if [t = ""] *)

val rchop : t -> t
  (** [rchop t] returns [t] without is last character. Returns [""] if
      [t = ""]. *)

(** {6 Buffers} *)

val add : Buffer.t -> UChar.t -> unit
  (** [add buf ch] is the same as [Buffer.add_string buf (singleton
      ch)] but is more efficient. *)

(** {6 Escaping} *)

val escaped_char : UChar.t -> t
  (** [escaped_char ch] returns a string containg [ch] or an escaped
      version of [ch] if:
      - [ch] is a control character (code < 32)
      - [ch] is the character with code 127
      - [ch] is a non-ascii, non-alphabetic character

      It uses the syntax [\xXX], [\uXXXX], [\UXXXXXX] or a specific
      escape sequence [\n, \r, ...]. *)

val add_escaped_char : Buffer.t -> UChar.t -> unit
  (** [add_escaped_char buf ch] is the same as [Buffer.add_string buf
      (escaped_char ch)] but a bit more efficient. *)

val escaped : t -> t
  (** [escaped text] escape all characters of [text] as with
      [escape_char]. *)

val add_escaped : Buffer.t -> t -> unit
  (** [add_escaped_char buf text] is the same as [Buffer.add_string
      buf (escaped text)] but a bit more efficient. *)

val escaped_string : CamomileLibraryDyn.Camomile.CharEncoding.t -> string -> t
  (** [escaped_string enc str] escape the string [str] which is
      encoded with encoding [enc]. If decoding [str] with [enc] fails,
      it escape all non-printable bytes of [str] with the syntax
      [\yAB]. *)

val add_escaped_string : Buffer.t -> CamomileLibraryDyn.Camomile.CharEncoding.t -> string -> unit
  (** [add_escaped_char buf enc text] is the same as
      [Buffer.add_string buf (escaped_string enc text)] but a bit more
      efficient. *)

(** {6 Safe offset API} *)

val next : t -> int -> int
  (** [next str ofs] returns the offset of the next character in
      [str]. *)

val prev : t -> int -> int
  (** [prev str ofs] returns the offset of the previous character in
      [str]. *)

val extract : t -> int -> UChar.t
  (** [extract str ofs] returns the code-point at offset [ofs] in
      [str]. *)

val extract_next : t -> int -> UChar.t * int
  (** [extract_next str ofs] returns the code-point at offset [ofs] in
      [str] and the offset the next character. *)

val extract_prev : t -> int -> UChar.t * int
  (** [extract_prev str ofs] returns the code-point at the previous
      offset in [str] and this offset. *)

(** {6 Unsafe offset API} *)

(** These functions does not check that the given offset is inside the
    bounds of the given string. *)

val unsafe_next : t -> int -> int
  (** [unsafe_next str ofs] returns the offset of the next character
      in [str]. *)

val unsafe_prev : t -> int -> int
  (** [unsafe_prev str ofs] returns the offset of the previous
      character in [str]. *)

val unsafe_extract : t -> int -> UChar.t
  (** [unsafe_extract str ofs] returns the code-point at offset [ofs]
      in [str]. *)

val unsafe_extract_next : t -> int -> UChar.t * int
  (** [unsafe_extract_next str ofs] returns the code-point at offset
      [ofs] in [str] and the offset the next character. *)

val unsafe_extract_prev : t -> int -> UChar.t * int
  (** [unsafe_extract_prev str ofs] returns the code-point at the
      previous offset in [str] and this offset. *)