~ubuntu-branches/ubuntu/oneiric/haxe/oneiric

« back to all changes in this revision

Viewing changes to ocaml/xml-light/dtd.mli

  • Committer: Bazaar Package Importer
  • Author(s): Jens Peter Secher
  • Date: 2008-06-15 11:04:09 UTC
  • mfrom: (2.1.6 intrepid)
  • Revision ID: james.westby@ubuntu.com-20080615110409-7pyykgwmk5v0cues
Tags: 1:1.19-3
* Remove bashism in script.
  (Closes: #484390)
* Upgrade to Policy 3.8.0 by including a README.source explaining how to
  use dpatch.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
(*
 
2
 * Xml Light, an small Xml parser/printer with DTD support.
 
3
 * Copyright (C) 2003 Nicolas Cannasse (ncannasse@motion-twin.com)
 
4
 *
 
5
 * This library is free software; you can redistribute it and/or
 
6
 * modify it under the terms of the GNU Lesser General Public
 
7
 * License as published by the Free Software Foundation; either
 
8
 * version 2.1 of the License, or (at your option) any later version.
 
9
 *
 
10
 * This library has the special exception on linking described in file
 
11
 * README.
 
12
 *
 
13
 * This library is distributed in the hope that it will be useful,
 
14
 * but WITHOUT ANY WARRANTY; without even the implied warranty of
 
15
 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
 
16
 * Lesser General Public License for more details.
 
17
 *
 
18
 * You should have received a copy of the GNU Lesser General Public
 
19
 * License along with this library; if not, write to the Free Software
 
20
 * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston,
 
21
 * MA 02110-1301 USA
 
22
 *)
 
23
 
 
24
(** Xml Light DTD
 
25
 
 
26
        This module provide several functions to create, check, and use DTD
 
27
        to prove Xml documents : {ul
 
28
        {li using the DTD types, you can directly create your own DTD structure}
 
29
        {li the {!Dtd.check} function can then be used to check that all DTD
 
30
                states have been declared, that no attributes are declared twice,
 
31
                and so on.}
 
32
        {li the {!Dtd.prove} function can be used to check an {!Xml} data
 
33
                structure with a checked DTD. The function will return the
 
34
                expanded Xml document or raise an exception if the DTD proving
 
35
                fails.}
 
36
        }
 
37
 
 
38
        {i Note about ENTITIES:}
 
39
        
 
40
        While parsing Xml, PCDATA is always parsed and
 
41
        the Xml entities & > < ' " are replaced by their
 
42
        corresponding ASCII characters. For Xml attributes, theses can be
 
43
        put between either double or simple quotes, and the backslash character
 
44
        can be used to escape inner quotes. There is no support for CDATA Xml
 
45
        nodes or PCDATA attributes declarations in DTD, and no support for
 
46
        user-defined entities using the ENTITY DTD element.
 
47
*)
 
48
 
 
49
(** {6 The DTD Types} *)
 
50
 
 
51
type dtd_child =
 
52
        | DTDTag of string
 
53
        | DTDPCData
 
54
        | DTDOptional of dtd_child
 
55
        | DTDZeroOrMore of dtd_child
 
56
        | DTDOneOrMore of dtd_child
 
57
        | DTDChoice of dtd_child list
 
58
        | DTDChildren of dtd_child list
 
59
 
 
60
type dtd_element_type =
 
61
        | DTDEmpty
 
62
        | DTDAny
 
63
        | DTDChild of dtd_child
 
64
 
 
65
type dtd_attr_default =
 
66
        | DTDDefault of string
 
67
        | DTDRequired
 
68
        | DTDImplied
 
69
        | DTDFixed of string
 
70
 
 
71
type dtd_attr_type =
 
72
        | DTDCData
 
73
        | DTDNMToken
 
74
        | DTDEnum of string list
 
75
        | DTDID
 
76
        | DTDIDRef
 
77
 
 
78
type dtd_item =
 
79
        | DTDAttribute of string * string * dtd_attr_type * dtd_attr_default
 
80
        | DTDElement of string * dtd_element_type
 
81
 
 
82
type dtd = dtd_item list
 
83
 
 
84
type checked
 
85
 
 
86
(** {6 The DTD Functions} *)
 
87
 
 
88
(** Parse the named file into a Dtd data structure. Raise
 
89
        {!Xml.File_not_found} if an error occured while opening the file. 
 
90
        Raise {!Dtd.Parse_error} if parsing failed. *)
 
91
val parse_file : string -> dtd
 
92
 
 
93
(** Read the content of the in_channel and parse it into a Dtd data
 
94
 structure. Raise {!Dtd.Parse_error} if parsing failed. *)
 
95
val parse_in : in_channel -> dtd
 
96
 
 
97
(** Parse the string containing a Dtd document into a Dtd data
 
98
 structure. Raise {!Dtd.Parse_error} if parsing failed. *)
 
99
val parse_string : string -> dtd
 
100
 
 
101
(** Check the Dtd data structure declaration and return a checked
 
102
 DTD. Raise {!Dtd.Check_error} if the DTD checking failed. *)
 
103
val check : dtd -> checked
 
104
 
 
105
(** Prove an Xml document using a checked DTD and an entry point.
 
106
 The entry point is the first excepted tag of the Xml document,
 
107
 the returned Xml document has the same structure has the original
 
108
 one, excepted that non declared optional attributes have been set
 
109
 to their default value specified in the DTD.
 
110
 Raise {!Dtd.Check_error} [ElementNotDeclared] if the entry point
 
111
 is not found, raise {!Dtd.Prove_error} if the Xml document failed
 
112
 to be proved with the DTD. *)
 
113
val prove : checked -> string -> Xml.xml -> Xml.xml
 
114
 
 
115
(** Print a DTD element into a string. You can easily get a DTD
 
116
 document from a DTD data structure using for example
 
117
 [String.concat "\n" (List.map Dtd.to_string) my_dtd] *)
 
118
val to_string : dtd_item -> string
 
119
 
 
120
(** {6 The DTD Exceptions} *)
 
121
 
 
122
(** There is three types of DTD excecptions : {ul
 
123
        {li {!Dtd.Parse_error} is raised when an error occured while
 
124
        parsing a DTD document into a DTD data structure.}
 
125
        {li {!Dtd.Check_error} is raised when an error occured while
 
126
        checking a DTD data structure for completeness, or when the
 
127
        prove entry point is not found when calling {!Dtd.prove}.}
 
128
        {li {!Dtd.Prove_error} is raised when an error occured while
 
129
        proving an Xml document.}
 
130
        }
 
131
 
 
132
        Several string conversion functions are provided to enable you
 
133
        to report errors to the user.
 
134
*)
 
135
 
 
136
type parse_error_msg =
 
137
        | InvalidDTDDecl
 
138
        | InvalidDTDElement
 
139
        | InvalidDTDAttribute
 
140
        | InvalidDTDTag
 
141
        | DTDItemExpected
 
142
 
 
143
type check_error =
 
144
        | ElementDefinedTwice of string
 
145
        | AttributeDefinedTwice of string * string
 
146
        | ElementEmptyContructor of string
 
147
        | ElementReferenced of string * string
 
148
        | ElementNotDeclared of string
 
149
        | WrongImplicitValueForID of string * string
 
150
 
 
151
type prove_error =
 
152
        | UnexpectedPCData
 
153
        | UnexpectedTag of string
 
154
        | UnexpectedAttribute of string
 
155
        | InvalidAttributeValue of string
 
156
        | RequiredAttribute of string
 
157
        | ChildExpected of string
 
158
        | EmptyExpected
 
159
        | DuplicateID of string
 
160
        | MissingID of string
 
161
 
 
162
type parse_error = parse_error_msg * Xml.error_pos
 
163
 
 
164
exception Parse_error of parse_error
 
165
exception Check_error of check_error
 
166
exception Prove_error of prove_error
 
167
 
 
168
val parse_error : parse_error -> string
 
169
val check_error : check_error -> string
 
170
val prove_error : prove_error -> string
 
171
 
 
172
(**/**)
 
173
 
 
174
(* internal usage only... *)
 
175
val _raises : (string -> exn) -> unit