This file is indexed.

/usr/lib/ocaml/rss/rss.mli is in librss-ocaml-dev 2.2.1-3+b6.

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
(******************************************************************************)
(*               OCamlrss                                                     *)
(*                                                                            *)
(*   Copyright (C) 2004-2013 Institut National de Recherche en Informatique   *)
(*   et en Automatique. All rights reserved.                                  *)
(*                                                                            *)
(*   This program is free software; you can redistribute it and/or modify     *)
(*   it under the terms of the GNU Lesser General Public License version      *)
(*   3 as published by the Free Software Foundation.                          *)
(*                                                                            *)
(*   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 Library General Public License for more details.                     *)
(*                                                                            *)
(*   You should have received a copy of the GNU Library 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                                                          *)
(*                                                                            *)
(*   Contact: Maxence.Guesdon@inria.fr                                        *)
(*                                                                            *)
(*                                                                            *)
(******************************************************************************)

(** The RSS library to read and write RSS 2.0 files.

    Reference:
    {{:http://www.rssboard.org/rss-specification}RSS
    2.0 specification}. *)

(** {2 Types} *)

type date = Netdate.t

val string_of_date : ?fmt: string -> date -> string
(** Format a date/time record as a string according to the format
    string [fmt].

    @param fmt The format string.  It consists of zero or more
    conversion specifications and ordinary characters.  All ordinary
    characters are kept as such in the final string.  A conversion
    specification consists of the '%' character and one other
    character.  See [Netdate.format_to] for more details.
    Default: ["%d %b %Y"].
 *)

type email = string (** can be, for example: foo\@bar.com (Mr Foo Bar) *)
type pics_rating = string
type skip_hours = int list (** 0 .. 23 *)
type skip_days = int list (** 0 is Sunday, 1 is Monday, ... *)

type url = Neturl.url

type category =
  {
    cat_name : string ;
    (** A forward-slash-separated string that identifies a hierarchic
        location in the indicated taxonomy. *)
    cat_domain : url option ;
    (** Identifies a categorization taxonomy. *)
  }

type image =
  {
    image_url : url ;
    (** The URL of a GIF, JPEG or PNG image that represents the channel. *)
    image_title : string ;
    (** Description of the image, it's used in the ALT attribute of
        the HTML <img> tag when the channel is rendered in HTML.  *)
    image_link : url ;
    (** The URL of the site, when the channel is rendered, the image
        is a link to the site. (Note, in practice the [image_title]
        and [image_link] should have the same value as the {!channel}'s
        [ch_title] and [ch_link].)  *)
    image_height : int option ;
    (** Height of the image, in pixels. *)
    image_width : int option ;
    (** Width of the image, in pixels. *)
    image_desc : string option ;
    (** Text to be included in the "title" attribute of the link formed
        around the image in the HTML rendering. *)
  }

type text_input =
    {
      ti_title : string ;
      (** The label of the Submit button in the text input area. *)
      ti_desc : string ;
      (** Explains the text input area. *)
      ti_name : string ;
      (** The name of the text object in the text input area. *)
      ti_link : url ;
      (** The URL of the CGI script that processes text input requests. *)
    }

type enclosure =
  {
    encl_url : url ; (** URL of the enclosure *)
    encl_length : int ; (** size in bytes *)
    encl_type : string ; (** MIME type *)
  }

type guid =
  | Guid_permalink of url (** A permanent URL pointing to the story. *)
  | Guid_name of string   (** A string that uniquely identifies the item.  *)

type source =
    {
      src_name : string ;
      src_url : url ;
    }

(** See {{:http://cyber.law.harvard.edu/rss/soapMeetsRss.html#rsscloudInterface} specification} *)
type cloud = {
    cloud_domain : string ;
    cloud_port : int ;
    cloud_path : string ;
    cloud_register_procedure : string ;
    cloud_protocol : string ;
  }

(** An item may represent a "story".  Its description is a synopsis of
    the story (or sometimes the full story), and the link points to
    the full story. *)
type 'a item_t =
  {
    item_title : string option; (** Optional title *)
    item_link : url option; (** Optional link *)
    item_desc : string option; (** Optional description *)
    item_pubdate : date option ; (** Date of publication *)
    item_author : email option ;
    (** The email address of the author of the item. *)
    item_categories : category list ;
    (** Categories for the item.  See the field {!category}. *)
    item_comments : url option ; (** Url of comments about this item *)
    item_enclosure : enclosure option ;
    item_guid : guid option ;
    (** A globally unique identifier for the item. *)
    item_source : source option ;
    item_data : 'a option ;
    (** Additional data, since RSS can be extended with namespace-prefixed nodes.*)
  }

(** A namespace is a pair (name, url). *)
type namespace = string * string

type ('a, 'b) channel_t =
  {
    ch_title : string ;
    (** Mandatory.  The name of the channel, for example the title of
        your web site. *)
    ch_link : url ;
    (** Mandatory.  The URL to the HTML website corresponding to the channel. *)
    ch_desc : string ;
    (** Mandatory.  A sentence describing the channel. *)
    ch_language : string option ;
    (** Language of the news, e.g. "en".  See the W3C
        {{:http://www.w3.org/TR/REC-html40/struct/dirlang.html#langcodes}
        language codes}. *)
    ch_copyright : string option ; (** Copyright notice. *)
    ch_managing_editor : email option ;
    (** Managing editor of the news. *)
    ch_webmaster : email option ;
    (** The address of the webmasterof the site. *)
    ch_pubdate : date option ;
    (** Publication date of the channel. *)
    ch_last_build_date : date option ;
    (** When the channel content changed for the last time. *)
    ch_categories : category list ;
    (** Categories for the channel.  See the field {!category}. *)
    ch_generator : string option ;
    (** The tool used to generate this channel. *)
    ch_cloud : cloud option ;
    (** Allows processes to register with a cloud to be notified of updates to the channel. *)
    ch_docs : url option ; (** An url to a RSS format reference. *)
    ch_ttl : int option ;
    (** Time to live, in minutes.  It indicates how long a channel can
        be cached before refreshing from the source. *)
    ch_image : image option ;
    ch_rating : pics_rating option;
    (** The PICS rating for the channel. *)
    ch_text_input : text_input option ;
    ch_skip_hours : skip_hours option ;
    (** A hint for aggregators telling them which hours they can skip.*)
    ch_skip_days : skip_days option ;
    (** A hint for aggregators telling them which days they can skip. *)
    ch_items : 'b item_t list ;
    ch_data : 'a option ;
        (** Additional data, since RSS can be extended with namespace-prefixed nodes.*)
    ch_namespaces : namespace list ;
  }

type item = unit item_t
type channel = (unit, unit) channel_t

(** {2 Building items and channels} *)

val item :
  ?title: string ->
  ?link: url ->
  ?desc: string ->
  ?pubdate: date ->
  ?author: email ->
  ?cats: category list ->
  ?comments: url ->
  ?encl: enclosure ->
  ?guid: guid ->
  ?source: source ->
  ?data: 'a ->
  unit ->
  'a item_t
(** [item()] creates a new item with all fields set to [None].  Use the
    optional parameters to set fields. *)

val channel :
  title: string ->
  link: url ->
  desc: string ->
  ?language: string ->
  ?copyright: string ->
  ?managing_editor: email ->
  ?webmaster: email ->
  ?pubdate: date ->
  ?last_build_date: date ->
  ?cats: category list ->
  ?generator: string ->
  ?cloud: cloud ->
  ?docs: url ->
  ?ttl: int ->
  ?image: image ->
  ?rating: pics_rating ->
  ?text_input: text_input ->
  ?skip_hours: skip_hours ->
  ?skip_days: skip_days ->
  ?data: 'a ->
  ?namespaces: namespace list ->
  'b item_t list ->
  ('a, 'b) channel_t
(** [channel items] creates a new channel containing [items].  Other
    fields are set to [None] unless the corresponding optional
    parameter is used. *)

val compare_item : ?comp_data: ('a -> 'a -> int) -> 'a item_t -> 'a item_t -> int

val copy_item : 'a item_t -> 'a item_t
val copy_channel : ('a, 'b) channel_t -> ('a, 'b) channel_t


(** {2 Manipulating channels} *)

val keep_n_items : int -> ('a, 'b) channel_t -> ('a, 'b) channel_t
(** [keep_n_items n ch] returns a copy of the channel, keeping only
    [n] items maximum. *)

val sort_items_by_date : 'a item_t list -> 'a item_t list
(** Sort items by date, older last. *)

val merge_channels : ('a, 'b) channel_t -> ('a, 'b) channel_t -> ('a, 'b) channel_t
(** [merge_channels c1 c2] merges the given channels in a new channel,
    sorting items using {!sort_items_by_date}. Channel information are
    copied from the first channel [c1]. *)


(** {2 Reading channels} *)

(** This represents XML trees. Such XML trees are given to
  functions provided to read additional data from RSS channels and items. *)
type xmltree =
    E of Xmlm.tag * xmltree list
  | D of string

(** Read an XML tree from a source.
   @raise Failure in case of error.*)
val xml_of_source : Xmlm.source -> xmltree

(** Use this exception to indicate an error is functions given to [make_opts] used
  to read additional data from prefixed XML nodes. *)
exception Error of string

(** Options used when reading source. *)
type ('a, 'b) opts

(** See Neturl documentation for [schemes] and [base_syntax] options.
  They are used to parse URLs.
  @param read_channel_data provides a way to read additional information from the
  subnodes of the channels. All these subnodes are prefixed by an expanded namespace.
  @param read_item_data is the equivalent of [read_channel_data] parameter but
  is called of each item with its prefixed subnodes.
  *)
val make_opts :
  ?schemes: (string, Neturl.url_syntax) Hashtbl.t ->
  ?base_syntax: Neturl.url_syntax ->
  ?read_channel_data: (xmltree list -> 'a option) ->
  ?read_item_data: (xmltree list -> 'b option) ->
  unit -> ('a, 'b) opts

val default_opts : (unit, unit) opts

(** [channel_[t_]of_X] returns the parsed channel and a list of encountered errors.
  Note that only namespaces declared in the root not of the XML tree are added to [ch_namespaces] field.
  @raise Failure if the channel could not be parsed.
*)
val channel_t_of_file : ('a, 'b) opts -> string -> (('a, 'b) channel_t * string list)
val channel_t_of_string : ('a, 'b) opts -> string -> (('a, 'b) channel_t * string list)
val channel_t_of_channel : ('a, 'b) opts -> in_channel -> (('a, 'b) channel_t * string list)

(** Read a channel from XML trees. These trees correspond to nodes under the ["channel"] XML node
 of a reguler RSS document. *)
val channel_t_of_xmls : ('a, 'b) opts -> xmltree list -> (('a, 'b) channel_t * string list)

val channel_of_file : string -> (channel * string list)
val channel_of_string : string -> (channel * string list)
val channel_of_channel : in_channel -> (channel * string list)

(** {2 Writing channels} *)

type 'a data_printer = 'a -> xmltree list

val print_channel :
  ?channel_data_printer: 'a data_printer ->
  ?item_data_printer: 'b data_printer ->
  ?indent: int -> ?date_fmt: string -> ?encoding: string ->
    Format.formatter -> ('a, 'b) channel_t -> unit

val print_file :
  ?channel_data_printer: 'a data_printer ->
  ?item_data_printer: 'b data_printer ->
    ?indent: int -> ?date_fmt: string -> ?encoding: string ->
    string -> ('a, 'b) channel_t -> unit