This file is indexed.

/usr/lib/ocaml/tyxml/xml_sigs.mli is in libtyxml-ocaml-dev 3.5.0-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
(* TyXML
 * http://www.ocsigen.org/tyxml
 * Copyright (C) 2004 Thorsten Ohl <ohl@physik.uni-wuerzburg.de>
 * Copyright (C) 2011 Pierre Chambart, Grégoire Henry
 *
 * 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., 51 Franklin Street, Suite 500, Boston, MA 02111-1307, USA.
*)

module type Wrapped = sig

  type 'a wrap
  type 'a list_wrap

  type uri
  val string_of_uri : uri -> string
  val uri_of_string : string -> uri

  type aname = string
  type event_handler
  type mouse_event_handler
  type keyboard_event_handler

  type attrib

  val float_attrib : aname -> float wrap -> attrib
  val int_attrib : aname -> int wrap -> attrib
  val string_attrib : aname -> string wrap -> attrib
  val space_sep_attrib : aname -> string list wrap -> attrib
  val comma_sep_attrib : aname -> string list wrap -> attrib
  val event_handler_attrib : aname -> event_handler -> attrib
  val mouse_event_handler_attrib : aname -> mouse_event_handler -> attrib
  val keyboard_event_handler_attrib : aname -> keyboard_event_handler -> attrib
  val uri_attrib : aname -> uri wrap -> attrib
  val uris_attrib : aname -> uri list wrap -> attrib

  type elt
  type ename = string

  val empty : unit -> elt
  val comment : string -> elt

  val pcdata : string wrap -> elt
  val encodedpcdata : string wrap -> elt
  val entity : string -> elt

  val leaf : ?a:(attrib list) -> ename -> elt
  val node : ?a:(attrib list) -> ename -> elt list_wrap -> elt

  val cdata : string -> elt
  val cdata_script : string -> elt
  val cdata_style : string -> elt

end

module type T = Wrapped with type 'a wrap = 'a
                         and type 'a list_wrap = 'a list
module type Iterable = sig

  include T

  type separator = Space | Comma

  val aname : attrib -> aname

  type acontent = private
    | AFloat of float
    | AInt of int
    | AStr of string
    | AStrL of separator * string list
  val acontent : attrib -> acontent

  type econtent = private
    | Empty
    | Comment of string
    | EncodedPCDATA of string
    | PCDATA of string
    | Entity of string
    | Leaf of ename * attrib list
    | Node of ename * attrib list * elt list
  val content : elt -> econtent

end

module type Info = sig
  val content_type: string
  val alternative_content_types: string list
  val version: string
  val standard: string
  val namespace: string
  val doctype: string
  val emptytags: string list
end

module type Output = sig
  type out
  type m
  val empty: m
  val concat: m -> m -> m
  val put: string -> m
  val make: m -> out
end

module type Typed_xml = sig

  module Xml : T
  module Info : Info

  type 'a elt
  type doc
  val toelt : 'a elt -> Xml.elt
  val doc_toelt : doc -> Xml.elt

end

module type Iterable_typed_xml = sig

  module Xml : Iterable
  module Info : Info

  type 'a elt
  type doc
  val toelt : 'a elt -> Xml.elt
  val doc_toelt : doc -> Xml.elt

end

module type Printer = sig

  type xml_elt
  type out

  val print_list: ?encode:(string -> string) -> xml_elt list -> out

end

module type Simple_printer = sig

  type xml_elt

  val print_list:
    output:(string -> unit) ->
    ?encode:(string -> string) ->
    xml_elt list -> unit

end

module type Typed_printer = sig

  type 'a elt
  type doc
  type out

  val print_list: ?encode:(string -> string) -> 'a elt list -> out
  val print: ?encode:(string -> string) -> ?advert:string-> doc -> out

end


module type Typed_simple_printer = sig

  type 'a elt
  type doc

  val print_list:
    output:(string -> unit) ->
    ?encode:(string -> string) ->
    'a elt list -> unit

  val print:
    output:(string -> unit) ->
    ?encode:(string -> string) -> ?advert:string->
    doc -> unit

end