This file is indexed.

/usr/lib/ocaml/ocsigenserver/ocsigen_stream.mli is in libocsigenserver-ocaml-dev 2.2.0-3.

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
(* Ocsigen
 * ocsigen_stream.ml Copyright (C) 2005 Vincent Balat
 *
 * This program 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, with linking exception;
 * either version 2.1 of the License, or (at your option) any later version.
 *
 * This program 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, write to the Free Software
 * Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
 *)

exception Interrupted of exn
exception Cancelled
exception Already_read
exception Finalized

(** Streams are a means to read data block by block *)

type 'a stream

(** A stream may be composed by several substreams.
   Thus a stream is either something that contains the current buffer and
   a function to retrieve the following data,
   or a finished stream with possibly another stream following.
 *)
type 'a step = private
  | Finished of 'a stream option
  | Cont of 'a * 'a stream

type 'a t

type outcome = [`Success | `Failure]

(** creates a new stream *)
val make : ?finalize:(outcome -> unit Lwt.t) -> (unit -> 'a step Lwt.t) -> 'a t

(** call this function if you decide to start reading a stream.
    @raise Already_read if the stream has already been read. *)
val get : 'a t -> 'a stream

(** get the next step of a stream.
    Fails with [Interrupted e] if reading the thread failed with exception [e],
    and with [Cancelled] if the thread has been cancelled. *)
val next : 'a stream -> 'a step Lwt.t


(** creates an empty step. The parameter is the following substream, if any. *)
val empty : (unit -> 'a step Lwt.t) option -> 'a step Lwt.t

(** creates a non empty step. *)
val cont : 'a -> (unit -> 'a step Lwt.t) -> 'a step Lwt.t


(** Add a finalizer function. In the current version,
    finalizers must be called manually. *)
val add_finalizer : 'a t -> (outcome -> unit Lwt.t) -> unit

(** Finalize the stream. This function must be called explicitely after reading
    the stream, otherwise finalizers won't be called. *)
val finalize : 'a t -> outcome -> unit Lwt.t

(** Cancel the stream, i.e. read the stream until the end, without decoding.
    Further tries to read on the stream will fail with exception
    {!Ocsigen_stream.Cancelled}
 *)
val cancel : 'a t -> unit Lwt.t

(** Consume without cancelling.
    Read the stream until the end, without decoding. *)
val consume : 'a t -> unit Lwt.t


exception Stream_too_small
  (** possibly with the size of the stream *)

exception Stream_error of string
exception String_too_large

(** Creates a string from a stream. The first argument is the upper limit of the
    string length *)
val string_of_stream : int -> string stream -> string Lwt.t

(** Read more data in the buffer *)
val enlarge_stream : string step -> string step Lwt.t

(** [stream_want s len] Returns a stream with at least len
    bytes in the buffer if possible *)
val stream_want : string step -> int -> string step Lwt.t

(** Returns the value of the current buffer *)
val current_buffer : string step -> string

(** Skips data. Raises [Stream_too_small (Some size)] 
    if the stream is too small, where [size] is the size of the stream. *)
val skip : string step -> int64 -> string step Lwt.t

(** Cut the stream at the position given by a string delimiter *)
val substream : string -> string step -> string step Lwt.t



(*VVV à revoir : *)

(** returns a stream reading from a file.
   Do not forget to finalize the stream to close the file.
 *)
val of_file : string -> string t

(** returns a stream containing a string. *)
val of_string : string -> string t


module StringStream : sig

  (** Interface for stream creation (for tyxml) *)
  type out = string t
  type m

  val make: m -> out

  (** Create an empty stream *)
  val empty: m

  (** Create a stream with one element *)
  val put: string -> m

  (** Concatenate two stream *)
  val concat: m -> m -> m

end