This file is indexed.

/usr/lib/ocaml/eliom/client/eliom_comet.mli is in libeliom-ocaml-dev 2.2.2-1.

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
(* Ocsigen
 * http://www.ocsigen.org
 * Copyright (C) 2010
 * Raphaƫl Proust
 * Pierre Chambart
 *
 * 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.
 *)

(** Handle unsolicited server to client communications.

    See the Eliom manual for a detailed introduction to the concept of
    {% <<a_manual chapter="client-communication"|client server communication>>%}. *)

(** When the page is not active the client stops making comet requests
    to the server, implying that the client can't be notified by the
    server anymore. The activity status is changed when the page is
    focused or unfocused.

    To stop receiving inputs from a channel, use Lwt.cancel on a
    thread waiting for datas. For instance, if you iterate with
    [ let t = Lwt_stream.iter f %channel ] calling [Lwt.cancel t]
    will close the channel. *)

(** [Channel_full] is raised when trying to read on a channel marked
    full by the server. It is not possible to read anything else from a
    full channel. *)
exception Channel_full

(** [Process_closed] is raised when reading on a channel and the
    server side of the application closed the client process.
    This apply only to stateful channels *)
exception Process_closed

(** [Process_closed] is raised when reading on a channel and the
    server side of the application closed channel ( the channel
    was garbage collected ). This apply only to stateless channels *)
exception Channel_closed

(** [is_active ()] returns the current activity state *)
val is_active : unit -> bool

(** if the client is inactive [activate ()] launch a new xhr
    connection to start receiving server messages *)
val activate : unit -> unit

(** Change the reactivity of channels. Multiples configurations ( of
    type [t] ) can be created. The resulting behaviour is the minimal
    ( in the meaning of maximal reactivity ) between all
    configurations *)
module Configuration :
sig

  type t

  (** Creates a new configuration with default value. It modifies the
      current behaviour immediately *)
  val new_configuration : unit -> t

  (** [drop_configuration t] restores the behaviour to the minimum of
      configuration without [t]. If there is no other configuration
      than [t], it is restored to the defaults. *)
  val drop_configuration : t -> unit

  (** [set_always_active c b] if b is true, tells the client to always
      stay active.
      Default value is false. *)
  val set_always_active : t -> bool -> unit

  (** [set_timeout c t] tells the client to stay active at least [t]
      seconds when the application lose the focus.
      Default value is 20. *)
  val set_timeout : t -> float -> unit

  (** [set_active_until_timeout c v] sets the activity changing
      behaviour. if [v] is [true] the page is kept active even if not
      focused until the client receive a timeout message from the
      server. It implies that if the server keeps sending datas to the
      client, the comet connection will never be closed.
      Default value is false. *)
  val set_active_until_timeout : t -> bool -> unit

  (** after [set_time_between_request t v], the main loop will wait for
      [v] seconds between two requests. It is taken into account
      immediately.
      Default value is 0.*)
  val set_time_between_request : t -> float -> unit

end

module Channel :
sig
  type 'a t = 'a Lwt_stream.t
end

(**/**)

(** if wake is false, the registration of the channel won't
    activate the handling loop ( no request will be sent ). Default is true *)
val register : ?wake:bool -> 'a Eliom_comet_base.wrapped_channel ->
  'a Lwt_stream.t

(** [restart ()] Restarts the loop waiting for server messages. It is
    only usefull after that a formulary is sent. Indeed browsers stops
    all xhr requests in that case. It is normaly not needed, but some
    brosers (based on webkit) also destroy the xhr object in that
    case, preventing client code from receiving the failure
    notification. This shouldn't be used by average user. *)
val restart : unit -> unit

(** [close c] closes the channel c. This function should be only use
    internaly. The normal way to close a channel is to cancel a thread
    waiting on inputs. *)
val close : 'a Eliom_comet_base.wrapped_channel -> unit

val force_link : unit

(** When the page is not active the client stops making comet requests
    to the server, implying that the client can't be notified by the
    server anymore. The activity status is changed when the page is
    focused or unfocused.

    To stop receiving inputs from a channel, use Lwt.cancel on a
    thread waiting for datas. For instance, if you iterate with
    [ let t = Lwt_stream.iter f %channel ] calling [Lwt.cancel t]
    will close the channel. *)

(** [Channel_full] is raised when trying to read on a channel marked
    full by the server. It is not possible to read anything else from a
    full channel. *)
exception Channel_full

(** [Process_closed] is raised when reading on a channel and the
    server side of the application closed the client process.
    This apply only to stateful channels *)
exception Process_closed

(** [Process_closed] is raised when reading on a channel and the
    server side of the application closed channel ( the channel
    was garbage collected ). This apply only to stateless channels *)
exception Channel_closed

(** [is_active ()] returns the current activity state *)
val is_active : unit -> bool

(** if the client is inactive [activate ()] launch a new xhr
    connection to start receiving server messages *)
val activate : unit -> unit

(** Change the reactivity of channels. Multiples configurations ( of
    type [t] ) can be created. The resulting behaviour is the minimal
    ( in the meaning of maximal reactivity ) between all
    configurations *)
module Configuration :
sig

  type t

  (** Creates a new configuration with default value. It modifies the
      current behaviour immediately *)
  val new_configuration : unit -> t

  (** [drop_configuration t] restores the behaviour to the minimum of
      configuration without [t]. If there is no other configuration
      than [t], it is restored to the defaults. *)
  val drop_configuration : t -> unit

  (** [set_always_active c b] if b is true, tells the client to always
      stay active.
      Default value is false. *)
  val set_always_active : t -> bool -> unit

  (** [set_timeout c t] tells the client to stay active at least [t]
      seconds when the application lose the focus.
      Default value is 20. *)
  val set_timeout : t -> float -> unit

  (** [set_active_until_timeout c v] sets the activity changing
      behaviour. if [v] is [true] the page is kept active even if not
      focused until the client receive a timeout message from the
      server. It implies that if the server keeps sending datas to the
      client, the comet connection will never be closed.
      Default value is false. *)
  val set_active_until_timeout : t -> bool -> unit

  (** after [set_time_between_request t v], the main loop will wait for
      [v] seconds between two requests. It is taken into account
      immediately.
      Default value is 0.*)
  val set_time_between_request : t -> float -> unit

end

module Channel :
sig
  type 'a t = 'a Lwt_stream.t
end

(**/**)

(** if wake is false, the registration of the channel won't
    activate the handling loop ( no request will be sent ). Default is true *)
val register : ?wake:bool -> 'a Eliom_comet_base.wrapped_channel ->
  'a Lwt_stream.t

(** [restart ()] Restarts the loop waiting for server messages. It is
    only usefull after that a formulary is sent. Indeed browsers stops
    all xhr requests in that case. It is normaly not needed, but some
    brosers (based on webkit) also destroy the xhr object in that
    case, preventing client code from receiving the failure
    notification. This shouldn't be used by average user. *)
val restart : unit -> unit

(** [close c] closes the channel c. This function should be only use
    internaly. The normal way to close a channel is to cancel a thread
    waiting on inputs. *)
val close : 'a Eliom_comet_base.wrapped_channel -> unit

val force_link : unit