This file is indexed.

/usr/lib/ocaml/xml-light/dtd.mli is in libxml-light-ocaml-dev 2.2-17build1.

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
(*
 * Xml Light, an small Xml parser/printer with DTD support.
 * Copyright (C) 2003 Nicolas Cannasse (ncannasse@motion-twin.com)
 *
 * This library 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; either
 * version 2.1 of the License, or (at your option) any later version.
 *
 * This library 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 library; if not, write to the Free Software
 * Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
 *)

(** Xml Light DTD

	This module provide several functions to create, check, and use DTD
	to prove Xml documents : {ul
	{li using the DTD types, you can directly create your own DTD structure}
	{li the {!Dtd.check} function can then be used to check that all DTD
		states have been declared, that no attributes are declared twice,
		and so on.}
	{li the {!Dtd.prove} function can be used to check an {!Xml} data
		structure with a checked DTD. The function will return the
		expanded Xml document or raise an exception if the DTD proving
		fails.}
	}

	{i Note about ENTITIES:}
	
	While parsing Xml, PCDATA is always parsed and
	the Xml entities & > < ' " are replaced by their
	corresponding ASCII characters. For Xml attributes, theses can be
	put between either double or simple quotes, and the backslash character
	can be used to escape inner quotes. There is no support for CDATA Xml
	nodes or PCDATA attributes declarations in DTD, and no support for
	user-defined entities using the ENTITY DTD element.
*)

(** {6 The DTD Types} *)

type dtd_child =
	| DTDTag of string
	| DTDPCData
	| DTDOptional of dtd_child
	| DTDZeroOrMore of dtd_child
	| DTDOneOrMore of dtd_child
	| DTDChoice of dtd_child list
	| DTDChildren of dtd_child list

type dtd_element_type =
	| DTDEmpty
	| DTDAny
	| DTDChild of dtd_child

type dtd_attr_default =
	| DTDDefault of string
	| DTDRequired
	| DTDImplied
	| DTDFixed of string

type dtd_attr_type =
	| DTDCData
	| DTDNMToken
	| DTDEnum of string list

type dtd_item =
	| DTDAttribute of string * string * dtd_attr_type * dtd_attr_default
	| DTDElement of string * dtd_element_type

type dtd = dtd_item list

type checked

(** {6 The DTD Functions} *)

(** Parse the named file into a Dtd data structure. Raise
	{!Xml.File_not_found} if an error occured while opening the file. 
	Raise {!Dtd.Parse_error} if parsing failed. *)
val parse_file : string -> dtd

(** Read the content of the in_channel and parse it into a Dtd data
 structure. Raise {!Dtd.Parse_error} if parsing failed. *)
val parse_in : in_channel -> dtd

(** Parse the string containing a Dtd document into a Dtd data
 structure. Raise {!Dtd.Parse_error} if parsing failed. *)
val parse_string : string -> dtd

(** Check the Dtd data structure declaration and return a checked
 DTD. Raise {!Dtd.Check_error} if the DTD checking failed. *)
val check : dtd -> checked

(** Prove an Xml document using a checked DTD and an entry point.
 The entry point is the first excepted tag of the Xml document,
 the returned Xml document has the same structure has the original
 one, excepted that non declared optional attributes have been set
 to their default value specified in the DTD.
 Raise {!Dtd.Check_error} [ElementNotDeclared] if the entry point
 is not found, raise {!Dtd.Prove_error} if the Xml document failed
 to be proved with the DTD. *)
val prove : checked -> string -> Xml.xml -> Xml.xml

(** Print a DTD element into a string. You can easily get a DTD
 document from a DTD data structure using for example
 [String.concat "\n" (List.map Dtd.to_string) my_dtd] *)
val to_string : dtd_item -> string

(** {6 The DTD Exceptions} *)

(** There is three types of DTD excecptions : {ul
	{li {!Dtd.Parse_error} is raised when an error occured while
	parsing a DTD document into a DTD data structure.}
	{li {!Dtd.Check_error} is raised when an error occured while
	checking a DTD data structure for completeness, or when the
	prove entry point is not found when calling {!Dtd.prove}.}
	{li {!Dtd.Prove_error} is raised when an error occured while
	proving an Xml document.}
	}

	Several string conversion functions are provided to enable you
	to report errors to the user.
*)

type parse_error_msg =
	| InvalidDTDDecl
	| InvalidDTDElement
	| InvalidDTDAttribute
	| InvalidDTDTag
	| DTDItemExpected

type check_error =
	| ElementDefinedTwice of string
	| AttributeDefinedTwice of string * string
	| ElementEmptyContructor of string
	| ElementReferenced of string * string
	| ElementNotDeclared of string

type prove_error =
	| UnexpectedPCData
	| UnexpectedTag of string
	| UnexpectedAttribute of string
	| InvalidAttributeValue of string
	| RequiredAttribute of string
	| ChildExpected of string
	| EmptyExpected

type parse_error = parse_error_msg * Xml.error_pos

exception Parse_error of parse_error
exception Check_error of check_error
exception Prove_error of prove_error

val parse_error : parse_error -> string
val check_error : check_error -> string
val prove_error : prove_error -> string

(**/**)

(* internal usage only... *)
val _raises : (string -> exn) -> unit