This file is indexed.

/usr/lib/ocaml/netstring/netpagebuffer.mli is in libocamlnet-ocaml-dev 4.1.2-1+b2.

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
(* $Id$ *)

(** Buffer for page-aligned I/O *)

(** This kind of buffer uses page-aligned bigarrays. Data can only be
    added to the end, or deleted at the beginning of the buffer.

    The idea of this buffer is that input data is added to the last
    page of the buffer only (with [add_inplace]). If then all previous
    input was already a multiple of the page size, it is ensured that
    the new input is added at a page boundary. This kind of input operation
    can often be accelerated by the OS ("zero copy network I/O").
 *)

open Netsys_types

type t

val create : int -> t
  (** create [blocksize]: creates new buffer with this [blocksize], which must
      be a whole multiple of the page size of the OS

      The [blocksize] is normally either
      - {!Netsys_mem.default_block_size}, or
      - {!Netsys_mem.small_block_size}

      These cases are optimized, and the buffer is allocated in a shared
      pool.
    *)

val contents : t -> string
  (** Returns the contents as string *)

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

val to_tstring_poly : t -> 's Netstring_tstring.tstring_kind -> 's
    (** Return the buffer in the format as selected by the arg *)

val to_tstring : t -> _ Netstring_tstring.tstring_kind -> tstring
    (** Returns the buffer as tagged string, selecting the chosen representation
     *)

val length : t -> int
  (** The length *)

val sub : t -> int -> int -> string
  (** Returns a substring *)

val sub_bytes : t -> int -> int -> Bytes.t
    (** Same for bytes *)

val blit_to_bytes : t -> int -> Bytes.t -> int -> int -> unit
  (** Blits contents to a string *)

val blit_to_string : t -> int -> Bytes.t -> int -> int -> unit
  DEPRECATED("Use blit_to_bytes instead.")

val blit_to_memory : t -> int -> Netsys_mem.memory -> int -> int -> unit
  (** Blits contents to another memory buffer *)

val blit_to_tbuffer : t -> int -> tbuffer -> int -> int -> unit
  (** Blits contents to a tagged buffer *)

val blit : t -> int -> Bytes.t -> int -> int -> unit
    (** Compatibility name for [blit_to_bytes] *)

val add_string : t -> string -> unit
  (** Adds a string to the end of the buffer *)

val add_bytes : t -> Bytes.t -> unit
    (** Same for bytes *)

val add_tstring : t -> tstring -> unit
    (** Same for tagged string *)

val add_substring : t -> string -> int -> int -> unit
  (** Adds a sub string to the end of the buffer *)

val add_sub_string : t -> string -> int -> int -> unit
    DEPRECATED("Use add_substring instead.")

val add_subbytes : t -> Bytes.t -> int -> int -> unit
  (** Adds a sub string to the end of the buffer *)

val add_submemory : t -> Netsys_mem.memory -> int -> int -> unit
  (** Adds a sub memory buffer to the end of the buffer *)

val add_sub_memory : t -> Netsys_mem.memory -> int -> int -> unit
  DEPRECATED("Use add_submemory instead.")

val add_subtstring : t -> tstring -> int -> int -> unit
  (** Adds a sub tstring to the end of the buffer *)

val add_inplace : t -> (Netsys_mem.memory -> int -> int -> int) -> int
  (** [add_inplace b f]: Calls [f m pos len] where [m] is the last page
      of the buffer, and [pos] is the first free byte on the page, and
      [len] is the number of free bytes on the page. The function [f] is
      expected to store new data in [m] from [pos] to [pos+n-1] and to
      return [n]. The number [n] is also returned as final result.

      It is ensured that [f] is called with a value of [len>=1].
   *)

val page_for_additions : t -> (Netsys_mem.memory * int * int)
  (** [let (m,pos,len) = page_for_additions b]: Returns the last page 
      in [m], the first free byte on the page in [pos], and 
      the number of free bytes on the page in [len]. (The same values
      the function [f] would have got as arguments in [add_inplace].)
   *)

val advance : t -> int -> unit
  (** [advance b n]: Marks further [n] bytes in the last page of the
      buffer as used. These bytes are not modified in any way - it is
      expected that the user calls [page_for_additions] first, and sets
      these [n] bytes to new values directly.
   *)

val page_for_consumption : t -> (Netsys_mem.memory * int * int)
  (** [let (m,pos,len) = page_for_consumption b]: Returns the first page 
      in [m], the first used byte on the page in [pos], and 
      the number of used bytes on the page in [len].
   *)


val delete_hd : t -> int -> unit
  (** [delete_hd b n]: Deletes [n] bytes from the beginning of the buffer
   *)

val clear : t -> unit
  (** Deletes all contents of the buffer *)

(** {2 Searching} *)

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