This file is indexed.

/usr/lib/ocaml/netstring/netbuffer.mli is in libocamlnet-ocaml-dev 3.7.3-3build2.

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
(* $Id: netbuffer.mli 1476 2010-08-31 00:05:15Z gerd $
 * ----------------------------------------------------------------------
 *
 *)


(** A Netbuffer.t is a buffer that can grow and shrink dynamically. *)

type t

val create : int -> t
    (** Creates a netbuffer which allocates initially this number of bytes. 
     * The logical length is zero.
     *)

val contents : t -> string
    (** Returns the contents of the buffer as fresh string. *)

val length : t -> int
    (** Returns the logical length of the buffer *)

(** {2 Extracting strings} *)

val get : t -> int -> char
    (** [get nb pos]: Get the character at [pos] *)

val nth : t -> int -> char
    (** Alias for [get] *)

val sub : t -> int -> int -> string
    (** [sub nb k n]: returns the n characters starting at position [n] from 
     * netbuffer [nb] as fresh string
     *)

val blit_to_string : t -> int -> string -> int -> int -> unit
    (** [blit_to_string nb srcpos dest destpos len]: Copies the [len] bytes at
     * position [srcpos] from [nb] to the string [dest] at position [destpos].
     *)

val blit : t -> int -> string -> int -> int -> unit
    (** Compatibility name for [blit_to_string], now deprecated *)

(** {2 Appending strings} *)

val add_string : t -> string -> unit
    (** [add_string nb s]: Adds a copy of the string [s] to the logical end of
     * the netbuffer [nb]. If necessary, [nb] grows.
     *)

val add_sub_string : t -> string -> int -> int -> unit
    (** [add_sub_string nb s k n]: Adds the substring of [s] starting at position
     * [k] with length [n] to the logical end of the netbuffer [nb]. If necessary,
     * [nb] grows.
     *
     * This is semantically the same as
     * [add_string nb (String.sub s k n)], but the extra copy is avoided.
     *)

val add_substring : t -> string -> int -> int -> unit
    (** Alias for add_sub_string *)

val add_char : t -> char -> unit
    (** [add_char nb c]: Adds a single char at the end of the buffer *)

val add_char_2 : t -> char -> char -> unit
    (** [add_char_2 nb c1 c2]: Adds two chars at the end of the buffer *)

val add_char_4 : t -> char -> char -> char -> char -> unit
    (** [add_char_4 nb c1 c2 c3 c4]: Adds four chars at the end of the buffer *)

val add_inplace : ?len:int -> t -> (string -> int -> int -> int) -> int
    (** [add_inplace nb f]: Calls the function [f] to add bytes to the
     * netbuffer [nb]. The arguments of [f] are the buffer, the position
     * in the buffer, and the maximum length. The function [f] must return
     * the actual number of added bytes; this number is also returned by
     * [add_inplace].
     *
     * Example: let n = add_inplace nb (Pervasives.input ch)
     *
     * The argument [len] is the number of bytes to add (second argument of
     * [f]). It defaults to the number of free bytes in the buffer after space
     * for at least one byte has been allocated.
     *)

val add_buffer : t -> t -> unit
  (** [add_buffer nb1 nb2]: Adds the contents of [nb2] to the end of [nb1] *)

val area_for_additions : ?len:int -> t -> (string * int * int)
val advance : t -> int -> unit
  (** These two functions work together, so that the effect of [add_inplace]
      can be obtained in two steps. First, the user calls
      {[
        let (s,pos,len) = area_for_additions nb
      ]}
      to get the area where to put new data of length [n], with [n <= len].
      After this the data is made valid by
      {[
        advance n
      ]}
   *)


(** {2 Inserting strings} *)

val insert_string : t -> int -> string -> unit
    (** [insert_string nb p s]: Inserts the value of string [s] at position
     * [p] into the netbuffer [nb]
     *)

val insert_sub_string : t -> int -> string -> int -> int -> unit
    (** [insert_string nb p s k n]: Inserts a substring of string [s] at position
     * [p] into the netbuffer [nb]. The substring is denoted by position [k]
     * and has length [n]
     *)

val insert_char : t -> int -> char -> unit
    (** [insert_char nb p c]: Inserts character [c] at position [p] into
     * the netbuffer [nb]
     *)

(** {2 Overwriting strings} *)

val set : t -> int -> char -> unit
    (** [set nb pos c]: Sets the character at [pos] to [c] *)

val put_string : t -> int -> string -> unit
    (** [put_string nb pos s]: Copies the string [s] to the position [pos]
        of netbuffer [nb]
     *)

val blit_from_string : string -> int -> t -> int -> int -> unit
    (** [blit_from_string src srcpos dest destpos len]: Copies the [len] bytes
     * at position [srcpos] from the string [src] to the netbuffer [dest] at
     * position [destpos].
     *
     * It is possible to copy the string beyond the end of the buffer. The
     * buffer is automatically enlarged in this case.
     *)

(** {2 Deleting} *)

val delete : t -> int -> int -> unit
    (** [delete nb k n]: Deletes the [n] bytes at position [k] of netbuffer 
     * [nb] in-place.
     *
     * The netbuffer does not shrink, however, i.e. the free space is not
     * given back to the memory manager.
     *)

val clear : t -> unit
    (** Deletes all contents from the buffer. As [delete], the netbuffer does
     * not shrink.
     *)

val reset : t -> unit
    (** Empty the buffer, deallocate the internal string, and replace it
        with a new string of length [n] that was allocated by
        {!Netbuffer.create} [n].
     *)

val try_shrinking : t -> unit
    (** [try_shrinking nb]: If the length of the buffer is less than half of
     * the allocated space, the netbuffer is reallocated in order to save
     * memory.
     *)

(** {2 Searching} *)

val index_from : t -> int -> char -> int
    (** [index_from nb k c]: Searches the character [c] in the netbuffer beginning
     * at position [k]. If found, the position of the left-most occurence is
     * returned. Otherwise, [Not_found] is raised.
     *)

(** {2 Memory} *)

val blit_to_memory : t -> int -> Netsys_mem.memory -> int -> int -> unit
    (** [blit_to_memory nb srcpos dest destpos len]: Copies the [len] bytes at
     *  position [srcpos] from [nb] to the membuffer [dest] at position
	[destpos].
     *)

val add_sub_memory : t -> Netsys_mem.memory -> int -> int -> unit
  (** Same as [add_sub_string], but gets data from a memory buffer *)


(** {2 Miscelleneous} *)

val unsafe_buffer : t -> string
    (** {b Warning! This is a low-level function!}
     * Returns the current string that internally holds the buffer.
     * The byte positions 0 to length - 1 actually store the contents of
     * the buffer. You can directly read and modify the buffer. Note that
     * there is no protection if you read or write positions beyond the
     * length of the buffer.
     *)

val print_buffer : t -> unit
    (** For the toploop *)


(* MISSING: searching substrings *)