This file is indexed.

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

(** Edition engines *)

open CamomileLibrary
open React

type 'a t
  (** Type of edition engines. ['a] is the type of custom data
      attached to the engine in order to extend it. *)

(** Type of clipboards. *)
type clipboard = {
  clipboard_get : unit -> Zed_rope.t;
  (** Returns the current contents of the clipboard. *)
  clipboard_set : Zed_rope.t -> unit;
  (** Sets the contents of the clipboard. *)
}

val new_clipboard : unit -> clipboard
  (** [new_clipboard ()] creates a new clipboard using a reference. *)

val create :
  ?editable : (int -> int -> bool) ->
  ?move : (int -> int -> int) ->
  ?clipboard : clipboard ->
  ?match_word : (Zed_rope.t -> int -> int option) ->
  ?locale : string option signal ->
  ?undo_size : int ->
  unit -> 'a t
  (** [create ?editable ?move ?clipboard ()] creates a new edition
      engine in the initial state.

      [editable] is used to determine whether the text at given
      position is editable or not. It takes as argument the position
      and the length of the text to remove.

      [move] is unused.

      [clipboard] is the clipboard to use for this engine. If none is
      defined, a new one using a reference is created.

      [match_word] is used to recognize words. It must returns the end
      of the matched word if any.

      [locale] is the locale of this buffer. It is used for case
      mapping.

      [undo_size] is the size of the undo buffer. It is the number of
      state zed will remember. It defaults to [1000]. *)

val match_by_regexp : Zed_re.t -> Zed_rope.t -> int -> int option
  (** [match_by_regexp re] creates a word-matching function using a
      regular expression. *)

(** {6 State} *)

val get_data : 'a t -> 'a
  (** [get_data edit] returns the custom data attached to the
      engine. It raises [Not_found] if no data is attached to the
      engine. *)

val set_data : 'a t -> 'a -> unit
  (** [set_data edit data] attach [data] to the engine. *)

val clear_data : 'a t -> unit
  (** [clear_data edit] removes the custom data of engine. *)

val text : 'a t -> Zed_rope.t
  (** [text edit] returns the signal holding the current contents of
      the buffer. *)

val lines : 'a t -> Zed_lines.t
  (** [lines edit] returns the set of line position of [text edit]. *)

val get_line : 'a t -> int -> Zed_rope.t
  (** [get_line edit n] returns the rope corresponding to the [n]th line
      without the newline character. *)

val changes : 'a t -> (int * int * int) event
  (** [changes edit] returns an event which occurs with values of the
      form [(start, added, removed)] when the contents of the engine
      changes. [start] is the start of modifications, [added] is the
      number of characters added and [removed] is the number of
      characters removed. *)

val update : 'a t -> Zed_cursor.t list -> unit event
  (** [update edit cursors] returns an event which occurs each the
      rendering of the engine should be updated. *)

val erase_mode : 'a t -> bool signal
  (** [erase_mode edit] returns the ``erase'' mode of the buffer. In
      this mode character inserted in the buffer erase existing
      ones. *)

val get_erase_mode : 'a t -> bool
  (** [erase_mode edit] returns the current erase mode of the
      buffer. *)

val set_erase_mode : 'a t -> bool -> unit
  (** [set_erase_mode edit state] sets the status of the erase mode
      for the given engine. *)

val mark : 'a t -> Zed_cursor.t
  (** [mark edit] returns the cursor used to for the mark in the given
      engine. *)

val selection : 'a t -> bool signal
  (** [selection edit] returns the signal holding the current
      selection state. If [true], text is being selectionned. *)

val get_selection : 'a t -> bool
  (** [selection edit] returns the current selection state. *)

val set_selection : 'a t -> bool -> unit
  (** [set_selection edit state] sets the selection state. *)

(** {6 Cursors} *)

val new_cursor : 'a t -> Zed_cursor.t
  (** [new_cursor edit] creates a new cursor for the given edition
      engine. The cursor initially points to the beginning of the
      buffer. *)

(** {6 Actions} *)

exception Cannot_edit
  (** Exception raised when trying to edit a non-editable portion of a
      buffer. *)

type 'a context
  (** Type of contexts. Contexts are used to modify an edition
      buffer. *)

val context : ?check : bool -> 'a t -> Zed_cursor.t -> 'a context
  (** [context ?check edit cursor] creates a new context with given
      parameters. [cursor] is the cursor that will be used for all
      modification of the text. If [check] is [true] (the default)
      then all modification of the text will be checked with the
      [editable] function of the engine. *)

val edit : 'a context -> 'a t
  (** [edit ctx] returns the edition engine used by the given
      context. *)

val cursor : 'a context -> Zed_cursor.t
  (** [cursor ctx] returns the cursor used by this context. *)

val check : 'a context -> bool
  (** [check ctx] returns whether the context has been created with
      the [check] flag. *)

val with_check : bool -> 'a context -> 'a context
  (** [with_check check ctx] retuns [ctx] with the check flag set to
      [check]. *)

val goto : 'a context -> ?set_wanted_column : bool -> int -> unit
  (** [goto ctx ?set_column position] moves the cursor to the given
      position. It raises {!Zed_cursor.Out_of_bounds} if the position
      is outside the bounds of the text. If [set_wanted_column] is
      [true], the wanted column of the cursor is set to the new
      column. *)

val move : 'a context -> ?set_wanted_column : bool -> int -> unit
  (** [move ctx ?set_wanted_column delta] moves the cursor by the
      given number of characters. It raises
      {!Zed_cursor.Out_of_bounds} if the current plus [delta] is
      outside the bounds of the text. *)

val move_line : 'a context -> int -> unit
  (** [move_line ctx ?set_wanted_column delta] moves the cursor by the
      given number of lines. *)

val position : 'a context -> int
  (** [position ctx] returns the position of the cursor. *)

val line : 'a context -> int
  (** [line ctx] returns the line of the cursor. *)

val column : 'a context -> int
  (** [column ctx] returns the column of the cursor. *)

val at_bol : 'a context -> bool
  (** [at_bol ctx] returns [true] iff the cursor is at the beginning
      of the current line. *)

val at_eol : 'a context -> bool
  (** [at_eol ctx] returns [true] iff the cursor is at the end of the
      current line. *)

val at_bot : 'a context -> bool
  (** [at_bot ctx] returns [true] iff the cursor is at the beginning
      of the text. *)

val at_eot : 'a context -> bool
  (** [at_eot ctx] returns [true] iff the cursor is at the end of the
      text. *)

val insert : 'a context -> Zed_rope.t -> unit
  (** [insert ctx rope] inserts the given rope at current position. *)

val insert_no_erase : 'a context -> Zed_rope.t -> unit
  (** [insert ctx rope] inserts the given rope at current position but
      do not erase text if the buffer is currently in erase mode. *)

val remove_next : 'a context -> int -> unit
  (** [remove_next ctx n] removes [n] characters at current
      position. If there is less than [n] characters at current
      position, it removes everything until the end of the text. *)

val remove_prev : 'a context -> int -> unit
  (** [remove_prev ctx n] removes [n] characters before current
      position. If there is less than [n] characters before current
      position, it removes everything until the beginning of the
      text. *)

val remove : 'a context -> int -> unit
  (** Alias for {!remove_next} *)

val replace : 'a context -> int -> Zed_rope.t -> unit
  (** [replace ctx n rope] does the same as:

      {[
        remove ctx n;
        insert_no_erase ctx rope
      ]}

      but in one atomic operation. *)

val newline : 'a context -> unit
  (** Insert a newline character. *)

val next_char : 'a context -> unit
  (** [next_char ctx] moves the cursor to the next character. It does
      nothing if the cursor is at the end of the text. *)

val prev_char : 'a context -> unit
  (** [prev_char ctx] moves the cursor to the previous character. It
      does nothing if the cursor is at the beginning of the text. *)

val next_line : 'a context -> unit
  (** [next_line ctx] moves the cursor to the next line. If the cursor
      is on the last line, it is moved to the end of the buffer. *)

val prev_line : 'a context -> unit
  (** [prev_line ctx] moves the cursor to the previous line. If the
      cursor is on the first line, it is moved to the beginning of the
      buffer. *)

val goto_bol : 'a context -> unit
  (** [goto_bol ctx] moves the cursor to the beginning of the current
      line. *)

val goto_eol : 'a context -> unit
  (** [goto_eol ctx] moves the cursor to the end of the current
      line. *)

val goto_bot : 'a context -> unit
  (** [goto_bot ctx] moves the cursor to the beginning of the text. *)

val goto_eot : 'a context -> unit
  (** [goto_eot ctx] moves the cursor to the end of the text. *)

val delete_next_char : 'a context -> unit
  (** [delete_next_char ctx] deletes the character after the cursor,
      if any. *)

val delete_prev_char : 'a context -> unit
  (** [delete_prev_char ctx] delete the character before the
      cursor. *)

val delete_next_line : 'a context -> unit
  (** [delete_next_line ctx] delete everything until the end of the
      current line. *)

val delete_prev_line : 'a context -> unit
  (** [delete_next_line ctx] delete everything until the beginning of
      the current line. *)

val kill_next_line : 'a context -> unit
  (** [kill_next_line ctx] delete everything until the end of the
      current line and save it to the clipboard. *)

val kill_prev_line : 'a context -> unit
  (** [kill_next_line ctx] delete everything until the beginning of
      the current line and save it to the clipboard. *)

val switch_erase_mode : 'a context -> unit
  (** [switch_erase_mode ctx] switch the current erase mode. *)

val set_mark : 'a context -> unit
  (** [set_mark ctx] sets the mark at current position. *)

val goto_mark : 'a context -> unit
  (** [goto_mark ctx] moves the cursor to the mark. *)

val copy : 'a context -> unit
  (** [copy ctx] copies the current selectionned region to the
      clipboard. *)

val kill : 'a context -> unit
  (** [kill ctx] copies the current selectionned region to the
      clipboard and remove it. *)

val yank : 'a context -> unit
  (** [yank ctx] inserts the contents of the clipboard at current
      position. *)

val capitalize_word : 'a context -> unit
  (** [capitalize_word ctx] capitalizes the first word after the
      cursor. *)

val lowercase_word : 'a context -> unit
  (** [lowercase_word ctx] converts the first word after the cursor to
      lowercase. *)

val uppercase_word : 'a context -> unit
  (** [uppercase_word ctx] converts the first word after the cursor to
      uppercase. *)

val next_word : 'a context -> unit
  (** [next_word ctx] moves the cursor to the end of the next word. *)

val prev_word : 'a context -> unit
  (** [prev_word ctx] moves the cursor to the beginning of the
      previous word. *)

val delete_next_word : 'a context -> unit
  (** [delete_next_word ctx] deletes the word after the cursor. *)

val delete_prev_word : 'a context -> unit
  (** [delete_prev_word ctx] deletes the word before the cursor. *)

val kill_next_word : 'a context -> unit
  (** [kill_next_word ctx] deletes the word after the cursor and save
      it to the clipboard. *)

val kill_prev_word : 'a context -> unit
  (** [kill_prev_word ctx] deletes the word before the cursor and save
      it to the clipboard. *)

val undo : 'a context -> unit
  (** [undo ctx] reverts the last performed action. *)

(** {6 Action by names} *)

(** Type of actions. *)
type action =
  | Insert of UChar.t
  | Newline
  | Next_char
  | Prev_char
  | Next_line
  | Prev_line
  | Goto_bol
  | Goto_eol
  | Goto_bot
  | Goto_eot
  | Delete_next_char
  | Delete_prev_char
  | Delete_next_line
  | Delete_prev_line
  | Kill_next_line
  | Kill_prev_line
  | Switch_erase_mode
  | Set_mark
  | Goto_mark
  | Copy
  | Kill
  | Yank
  | Capitalize_word
  | Lowercase_word
  | Uppercase_word
  | Next_word
  | Prev_word
  | Delete_next_word
  | Delete_prev_word
  | Kill_next_word
  | Kill_prev_word
  | Undo

val get_action : action -> ('a context -> unit)
  (** [get_action action] returns the function associated to the given
      action. *)

val actions : (action * string) list
  (** List of actions with their names, except {!Insert}. *)

val doc_of_action : action -> string
  (** [doc_of_action action] returns a short description of the
      action. *)

val action_of_name : string -> action
  (** [action_of_name str] converts the given action name into an
      action. Action name are the same as function name but with '_'
      replaced by '-'. It raises [Not_found] if the name does not
      correspond to an action.

      [Insert ch] is represented by "insert(<char>)" where [<char>] is:

      - a literal ascii character, such as "a", "b", ...
      - a unicode character, written "U+< code >", such as "U+0041"
  *)

val name_of_action : action -> string
  (** [name_of_action act] returns the name of the given action. *)