[m-rev.] For review: Allow custom functor to element mappings in term_to_xml

Ian MacLarty maclarty at cs.mu.OZ.AU
Fri Dec 10 13:15:51 AEDT 2004


On Fri, Dec 10, 2004 at 02:20:56AM +1100, Julien Fischer wrote:
> 
> On Thu, 9 Dec 2004, Ian MacLarty wrote:
> 
> >
> > tests/hard_coded/write_xml.m
> > tests/hard_coded/write_xml.exp
> > 	Test custom and predefined mapping schemes.
> >
> Does this version work for the high-level backend?
> 

It works but the output is slightly different due to different output from
deconstruct.deconstruct in the high-level backend when called with, for
example, a curried predicate. (I believe this is because it uses the
rtti_implementation version which from my understanding is not complete yet).

Here is the diff between write_xml.exp and write_xml.exp2 (which I have now
added):

--- write_xml.exp	2004-12-09 12:20:33.000000000 +1100
+++ write_xml.exp2	2004-12-10 12:17:46.000000000 +1100
@@ -112,17 +112,7 @@
 		<Int type="int">999</Int>
 	</a-32-60-33-64-35-36-37-94-38-42-40-41-62-32functor-32name-33-33-33--1--write_xml-46mytype>
 	<a_pred--1--write_xml-46mytype functor="a_pred" type="write_xml.mytype" arity="1">
-		<pred-40int-41 functor="p" type="pred(int)" arity="3">
-			<Int type="int">1</Int>
-			<Int type="int">2</Int>
-			<hello--5--write_xml-46mytype functor="hello" type="write_xml.mytype" arity="5">
-				<String type="string">a string</String>
-				<Int type="int">1</Int>
-				<Char type="character">c</Char>
-				<Float type="float">-1.00000000000000e-15</Float>
-				<yes--0--bool-46bool functor="yes" type="bool.bool" arity="0" />
-			</hello--5--write_xml-46mytype>
-		</pred-40int-41>
+		<pred-40int-41 functor="<<predicate>>" type="pred(int)" arity="0" />
 	</a_pred--1--write_xml-46mytype>
 	<t--1--write_xml-46mytype functor="t" type="write_xml.mytype" arity="1">
 		<type_desc-46type_desc functor="tree234" type="type_desc.type_desc" arity="2">


> > -	dtd_generation_result::out, io::di, io::uo) is cc_multi.
> > -
> > -	% write_xml_doc_cc(Stream, Term, MaybeStyleSheet, MaybeDTD, DTDResult,
> > -	%	!IO).
> > -	% Same as write_xml_doc/5 except write the XML doc to the given
> > +	% will be be written out in full.  If an embedded DTD is requested, but
> > +	% it is not possible to generated a DTD for Term using ElementMapping,
> s/generated/generate/
>

Fixed.

> > +	% then a value other than `ok' is returned in DTDResult and nothing is
> > +	% written out.  See the documentatin of the dtd_generation_result type
> > +	% for more information on the meaning of DTDResult when it is not `ok'.
> > +	%
> This last sentence should be changed as per the previous part of this
> review - it is repeated a few times below also.
> 

I've changed it.

> > +	% `ok' if it is possible to generate a DTD and will be another value
> > +	% otherwise.  See the documentation of the dtd_generation_result type
> > +	% for the meaning of Result when it is not `ok'.
> > +	%
> > +:- pred check_ok_to_generate_dtd(element_mapping::in(element_mapping),
> > +	type_desc::in, dtd_generation_result::out) is det.
> 
> I think `can_generate_dtd' would be a better name for this predicate,
> and that this predicate should actually now be a function.
> 

Okay.  Here's the new version:

	% can_generate_dtd(ElementMapping, Type) = Result.
	% Check if a DTD can be generated for the given Type using the
	% functor-to-element mapping scheme ElementMapping.  Return `ok' if it
	% is possible to generate a DTD.  See the documentation of the
	% dtd_generation_result type for the meaning of the return value when
	% it is not `ok'.
	%
:- func can_generate_dtd(element_mapping, type_desc) = dtd_generation_result.
:- mode can_generate_dtd(in(element_mapping), in) = out is det.

Note that predmode syntax doesn't seem work in this case (I get an
"unrecognised declaration" error).

> > +
> > +	% Values of this type are passed to custom functor-to-element
> > +	% mapping predicates to tell the predicate which functor to generate
> > +	% an element name for if the type is a discriminated union.  If the
> > +	% type is not a discriminated union, then not_a_du is passed to
> > +	% the predicate when requesting an element for the type.
> > +	%
> > +:- type maybe_functor_info
> > +			% The functor's name and arity.
> > +	--->	du_functor(
> > +			functor_name	:: string,
> > +			functor_arity	:: int
> > +		)
> > +			% The type is not a discriminated union.
> > +	;	not_a_du.
> > +
> Perhaps that type should be called maybe_du_functor_info?  In which case
> I think the second constructor should just be `no'.
> 

To me this would indicate that perhaps the du functor info is not available for
some reason.  I want it to be clear that not_a_du means the type is not a
discriminated union.

> > +	% Values of this type specify attributes that should be set by
> > +	% particular element.  The attribute_name field specifys the name
> s/specifys/specifies/
> 

Fixed.

> > +	% of the attribute in the generated XML and the attribute_source
> > +	% field indicates where the attributes value should come from.
> > +	%
> s/attributes/attribute's/
> 

Fixed.

> >
> > +:- pred yessify(T::in, maybe(T)::out) is det.
> > +
> > +yessify(X, yes(X)).
> > +
> yessify?!? How about `maybe' or `to_maybe' as a function here?
> I wonder if this worth adding to std_util ... probably not.
> 

yessify is a brilliant name - what are you on about :-)

I've changed it to Mark's suggestion.

> ...
> > -			ChildMaybeFieldNames = get_field_names(TypeDesc,
> > -				Functor, Arity),
> > +			% XXX This has been commented out until a bug in
> > +			% the runtime system has been fixed that causes
> > +			% a seg fault when construct.get_functor is invoked on
> > +			% a functor with existentially quantified argument
> > +			% types.
> Do we currently have a test case in tests for this bug?
> 

No, Zoltan was going to have a look at fixing this, but I'm happy to create a
test case if you think that's a good idea.

> > +:- pred check_types_ok(element_pred::in(element_pred),
> > +	list(type_desc)::in, map(type_desc, unit)::in,
> > +	map(string, type_desc)::in, dtd_generation_result::out) is det.
> > +
> check_types_ok is not the most meaningful name in the world.  What
> exactly about types is it checking that is ok?  Could you please
> either give it a more meaningful name, add a comment or preferably both.
> 

	% Check that we can reliably generate a DTD for the types in the list.
	% At the moment this means each type (and all the types of the arguments
	% of functors of the type if it's a discriminated union) must be either
	% be a discriminated union, an array, an int, a character, a float or a
	% string.  
:- func can_generate_dtd_for_types(element_pred, list(type_desc), 
	map(type_desc, unit), map(string, type_desc)) = dtd_generation_result.
:- mode can_generate_dtd_for_types(in(element_pred), in, in, in) = out is det.
	

> > +
> > +			io.write_list(ArgTypeList, ",",
> > +				write_dtd_allowed_functors_regex(MakeElement),
> > +					!IO),
> > +
> > +			( Braces = yes, io.write_string(")", !IO)
> > +			; Braces = no ),
> > +
> > +			( is_array(TypeDesc, _) -> io.write_string("*)", !IO)
> > +			; true ),
> I think it would be better to format these if-then-elses as the coding
> standard suggests.
> 

Okay.

> I think that certain sections of the implementation section of this
> module, notably the code that generates DTDs, could be documented more
> thoroughly.
> 
> Looks good otherwise.  You can commit after addressing the above comments and
> assuming that the test case now passes in the high-level C grades ;-)
> 

I've attached a relative diff to summarize:

Diffing .
--- /home/jupiter/maclarty/ws41_old//NEWS	2004-12-10 04:20:46.000000000 +1100
+++ NEWS	2004-12-10 13:06:13.000000000 +1100
@@ -20,7 +20,8 @@
   concatenation, array2d, for two-dimensional arrays, and version_array,
   version_array2d, version_bitmap, version_hash_table, and version_store,
   implementing non-unique versions of these types supporting O(1) access for
-  non-persistent use.
+  non-persistent use.  A new module term_to_xml has been added for converting
+  arbitrary terms to XML documents.
 * New procedures have been added to many of the existing standard library
   modules.  Most notably, these include procedures for creating
   directories and symbolic links, for checking file types and file
@@ -717,6 +718,12 @@
   given range, and random__randcount/3, which returns the number of
   distinct random numbers that can be generated.
 
+* A new module `term_to_xml' has been added to the standard library.  This
+  module contains predicates to write arbitrary Mercury terms to an output
+  stream as XML.  Automatic generation of DTDs for Mercury types is also
+  supported.  Once a Mercury term is in XML it can be converted to many other
+  formats such as HTML or XUL using an appropriate stylesheet.
+
 Changes to the extras distribution:
 
 * The lex subdirectory now contains a new module, regex, which provides
Diffing analysis
Diffing bindist
Diffing boehm_gc
Diffing boehm_gc/Mac_files
Diffing boehm_gc/cord
Diffing boehm_gc/cord/private
Diffing boehm_gc/doc
Diffing boehm_gc/include
Diffing boehm_gc/include/private
Diffing boehm_gc/tests
Diffing browser
Diffing bytecode
Diffing compiler
Diffing compiler/notes
Diffing debian
Diffing deep_profiler
Diffing deep_profiler/notes
Diffing doc
Diffing extras
Diffing extras/aditi
Diffing extras/cgi
Diffing extras/complex_numbers
Diffing extras/complex_numbers/samples
Diffing extras/complex_numbers/tests
Diffing extras/concurrency
Diffing extras/curs
Diffing extras/curs/samples
Diffing extras/curses
Diffing extras/curses/sample
Diffing extras/dynamic_linking
Diffing extras/error
Diffing extras/graphics
Diffing extras/graphics/easyx
Diffing extras/graphics/easyx/samples
Diffing extras/graphics/mercury_glut
Diffing extras/graphics/mercury_opengl
Diffing extras/graphics/mercury_tcltk
Diffing extras/graphics/samples
Diffing extras/graphics/samples/calc
Diffing extras/graphics/samples/gears
Diffing extras/graphics/samples/maze
Diffing extras/graphics/samples/pent
Diffing extras/lazy_evaluation
Diffing extras/lex
Diffing extras/lex/samples
Diffing extras/lex/tests
Diffing extras/logged_output
Diffing extras/moose
Diffing extras/moose/samples
Diffing extras/moose/tests
Diffing extras/morphine
Diffing extras/morphine/non-regression-tests
Diffing extras/morphine/scripts
Diffing extras/morphine/source
Diffing extras/odbc
Diffing extras/posix
Diffing extras/quickcheck
Diffing extras/quickcheck/tutes
Diffing extras/references
Diffing extras/references/samples
Diffing extras/references/tests
Diffing extras/stream
Diffing extras/trailed_update
Diffing extras/trailed_update/samples
Diffing extras/trailed_update/tests
Diffing extras/xml
Diffing extras/xml/samples
Diffing extras/xml_stylesheets
Diffing java
Diffing java/runtime
Diffing library
--- /home/jupiter/maclarty/ws41_old//library/term_to_xml.m	2004-12-10 13:04:10.000000000 +1100
+++ term_to_xml.m	2004-12-10 12:54:33.000000000 +1100
@@ -15,7 +15,7 @@
 %
 % Each functor in a term is given a corresponding well-formed element name 
 % in the XML document according to a mapping.  Some predefined mappings are 
-% prodice, but user defined mappings may also be used.
+% provided, but user defined mappings may also be used.
 %
 % The following attributes can be set for each XML element:
 %
@@ -41,16 +41,15 @@
 %
 % To support third parties generating XML which is compatible with the XML
 % generated by this library, a DTD for a Mercury type can also be generated.
-% A DTD for a given type and functo-to-element mapping may be generated
+% A DTD for a given type and functor-to-element mapping may be generated
 % provided the following conditions hold:
 %
 %	1. If the type is a discriminated union then there must be only 
 %	one top-level functor for the type.  This is because the top
 %	level functor will be used to generate the document type name.
 %
-%	2. The provided functor to element mapping must map each functor
-%	to a unique element name for every functor that could appear in
-%	terms of the type.
+%	2. The functor to element mapping must map each functor to a unique
+%	element name for every functor that could appear in terms of the type.
 %
 %	3. Only types whose terms consist of discriminated unions, arrays
 %	and the builtin types `int', `string', `character' and `float' can be
@@ -98,13 +97,12 @@
 		)
 	;	no_stylesheet.
 
-	% Values of this type indicate whether a DTD was successfully 
-	% generated or not.  A DTD cannot be generated for a type with more
-	% than one top-level functor since only one root element can be
-	% specified by a DTD.  A DTD also cannot be generated for a
-	% type where the mapping from functors of the type to
-	% elements is not unique (since then the legal children DTD rules
-	% cannot be expressed properly).
+	% Values of this type indicate whether a DTD was successfully generated
+	% or not.  A DTD cannot be generated for a type with more than one
+	% top-level functor since only one root element can be specified by a
+	% DTD.  A DTD also cannot be generated for a type where the mapping
+	% from functors of the type to elements is not unique (since then the
+	% DTD rules for legal children cannot be expressed properly)
 	%
 :- type dtd_generation_result
 	--->	ok
@@ -129,8 +127,8 @@
 			%
 		unsupported_dtd_type(type_desc).
 
-	% Values of this type specify what mapping from functors to elements
-	% to use when generating XML.  The role of a mapping is two fold:
+	% Values of this type specify which mapping from functors to elements
+	% to use when generating XML.  The role of a mapping is twofold:
 	%	1. To map functors to elements, and
 	%	2. To map functors to a set of attributes that should be
 	%	set for the corresponding element.
@@ -186,10 +184,10 @@
 	% MaybeStyleSheet and MaybeDTD specify whether or not a stylesheet
 	% reference and/or a DTD should be included.  Any non-canonical terms
 	% will be canonicalized.  If an embedded DTD is requested, but it is
-	% not possible to generated a DTD for Term using ElementMapping, then a
+	% not possible to generate a DTD for Term using ElementMapping, then a
 	% value other than `ok' is returned in DTDResult and nothing is written
-	% out.  See the documentatin of the dtd_generation_result type for more
-	% information of DTDResult when it is not `ok'.
+	% out.  See the dtd_generation_result type for a list of the other
+	% possible values of DTDResult and their meanings.
 	%
 :- pred write_xml_doc(T::in, element_mapping::in(element_mapping),
 	maybe_stylesheet::in, maybe_dtd::in, 
@@ -211,10 +209,10 @@
 	% MaybeStyleSheet and MaybeDTD specify whether or not a stylesheet
 	% reference and/or a DTD should be included.  Any non-canonical terms
 	% will be be written out in full.  If an embedded DTD is requested, but
-	% it is not possible to generated a DTD for Term using ElementMapping,
+	% it is not possible to generate a DTD for Term using ElementMapping,
 	% then a value other than `ok' is returned in DTDResult and nothing is
-	% written out.  See the documentatin of the dtd_generation_result type
-	% for more information on the meaning of DTDResult when it is not `ok'.
+	% written out.  See the dtd_generation_result type for a list of the other
+	% possible values of DTDResult and their meanings.
 	%
 :- pred write_xml_doc_cc(T::in, element_mapping::in(element_mapping), 
 	maybe_stylesheet::in, maybe_dtd::in, dtd_generation_result::out,
@@ -229,23 +227,23 @@
 	element_mapping::in(element_mapping), maybe_stylesheet::in,
 	maybe_dtd::in, dtd_generation_result::out, io::di, io::uo) is cc_multi.
 
-	% check_ok_to_generate_dtd(ElementMapping, Type, Result).
+	% can_generate_dtd(ElementMapping, Type) = Result.
 	% Check if a DTD can be generated for the given Type using the 
-	% functor-to-element mapping scheme ElementMapping.  Result will be
-	% `ok' if it is possible to generate a DTD and will be another value
-	% otherwise.  See the documentation of the dtd_generation_result type
-	% for the meaning of Result when it is not `ok'.
+	% functor-to-element mapping scheme ElementMapping.  Return `ok' if it
+	% is possible to generate a DTD.  See the documentation of the
+	% dtd_generation_result type for the meaning of the return value when
+	% it is not `ok'.
 	%
-:- pred check_ok_to_generate_dtd(element_mapping::in(element_mapping), 
-	type_desc::in, dtd_generation_result::out) is det.
+:- func can_generate_dtd(element_mapping, type_desc) = dtd_generation_result.
+:- mode can_generate_dtd(in(element_mapping), in) = out is det.
 
 	% write_dtd(Term, ElementMapping, DTDResult, !IO).
 	% Write a DTD for the given term to the current output stream using
 	% ElementMapping to map functors to elements.  If a DTD
 	% cannot be generated for Term using ElementMapping then a value
 	% other than `ok' is returned in DTDResult and nothing is written.
-	% See the documentation of the dtd_generation_result type for the 
-	% meaning of Result when it is not `ok'.
+	% See the dtd_generation_result type for a list of the other
+	% possible values of DTDResult and their meanings.
 	%
 :- pred write_dtd(T::unused, element_mapping::in(element_mapping), 
 	dtd_generation_result::out, io::di, io::uo) is det.
@@ -262,8 +260,8 @@
 	% Write a DTD for the given type to the current output stream. If a DTD
 	% cannot be generated for Type using ElementMapping then a value
 	% other than `ok' is returned in DTDResult and nothing is written.
-	% See the documentation of the dtd_generation_result type for the 
-	% meaning of Result when it is not `ok'.
+	% See the dtd_generation_result type for a list of the other
+	% possible values of DTDResult and their meanings.
 	%
 :- pred write_dtd_from_type(type_desc::in, 
 	element_mapping::in(element_mapping), dtd_generation_result::out, 
@@ -325,9 +323,9 @@
 	;	not_a_du.
 
 	% Values of this type specify attributes that should be set by 
-	% particular element.  The attribute_name field specifys the name
+	% particular element.  The attribute_name field specifies the name
 	% of the attribute in the generated XML and the attribute_source
-	% field indicates where the attributes value should come from.
+	% field indicates where the attribute's value should come from.
 	%
 :- type attribute
 	--->	attribute(
@@ -362,8 +360,7 @@
 %-----------------------------------------------------------------------------%
 
 write_xml_doc(X, ElementMapping, MaybeStyleSheet, MaybeDTD, DTDResult, !IO) :-
-	check_ok_to_generate_dtd(MaybeDTD, ElementMapping, type_of(X), 
-		DTDResult),
+	DTDResult = can_generate_dtd(MaybeDTD, ElementMapping, type_of(X)),
 	(
 		DTDResult = ok
 	->
@@ -386,8 +383,7 @@
 
 write_xml_doc_cc(X, ElementMapping, MaybeStyleSheet, MaybeDTD, DTDResult, 
 		!IO) :-
-	check_ok_to_generate_dtd(MaybeDTD, ElementMapping, type_of(X), 
-		DTDResult),
+	DTDResult = can_generate_dtd(MaybeDTD, ElementMapping, type_of(X)),
 	(
 		DTDResult = ok
 	->
@@ -708,8 +704,8 @@
 			list.map3(get_functor(TypeDesc), FunctorNums, 
 				Functors, Arities, ArgTypeLists0)
 		->
-			list.map(yessify, Functors, MaybeFunctors),
-			list.map(yessify, Arities, MaybeArities),
+			MaybeFunctors = list.map((func(X) = yes(X)), Functors),
+			MaybeArities = list.map((func(X) = yes(X)), Arities),
 			ArgTypeLists = ArgTypeLists0,
 			Requests = list.map_corresponding(make_du_functor, 
 				Functors, Arities),
@@ -736,10 +732,6 @@
 		)
 	).
 
-:- pred yessify(T::in, maybe(T)::out) is det.
-
-yessify(X, yes(X)).
-
 :- func make_du_functor(string, int) = maybe_functor_info.
 
 make_du_functor(Functor, Arity) = du_functor(Functor, Arity).
@@ -1087,7 +1079,7 @@
 %
 
 write_dtd_from_type(TypeDesc, ElementMapping, DTDResult, !IO) :-
-	check_ok_to_generate_dtd(ElementMapping, TypeDesc, DTDResult),
+	DTDResult = can_generate_dtd(ElementMapping, TypeDesc),
 	(
 		DTDResult = ok
 	->
@@ -1112,34 +1104,39 @@
 		true
 	).
 
-check_ok_to_generate_dtd(ElementMapping, TypeDesc, Result) :-
+can_generate_dtd(ElementMapping, TypeDesc) =  Result :-
 	get_element_pred(ElementMapping, MakeElement),
 	(
 		get_elements_and_args(MakeElement, TypeDesc, [_], [_], [_], 
 			[_], [_])
 	->
-		check_types_ok(MakeElement, [TypeDesc], 
-			map.init, map.init, Result)
+		Result = can_generate_dtd_for_types(MakeElement, [TypeDesc],
+			map.init, map.init)
 	;
 		Result = multiple_functors_for_root
 	).
 
-:- pred check_ok_to_generate_dtd(maybe_dtd::in, 
-	element_mapping::in(element_mapping), 
-	type_desc::in, dtd_generation_result::out) is det.
-
-check_ok_to_generate_dtd(no_dtd, _, _, ok).
-check_ok_to_generate_dtd(external(_), _, _, ok).
-check_ok_to_generate_dtd(embed, ElementMapping, TypeDesc, Result) :-
-	check_ok_to_generate_dtd(ElementMapping, TypeDesc, Result).
-
-:- pred check_types_ok(element_pred::in(element_pred), 
-	list(type_desc)::in, map(type_desc, unit)::in, 
-	map(string, type_desc)::in, dtd_generation_result::out) is det.
-
-check_types_ok(_, [], _, _, ok).
-check_types_ok(MakeElement, [TypeDesc | TypeDescs], DoneTypeDescs,
-		ElementsSoFar, Result) :-
+:- func can_generate_dtd(maybe_dtd, element_mapping, type_desc) =
+	dtd_generation_result.  
+:- mode can_generate_dtd(in, in(element_mapping), in) = out is det.
+
+can_generate_dtd(no_dtd, _, _) = ok.
+can_generate_dtd(external(_), _, _) = ok.
+can_generate_dtd(embed, ElementMapping, TypeDesc) 
+	= can_generate_dtd(ElementMapping, TypeDesc).
+
+	% Check that we can reliably generate a DTD for the types in the list.
+	% At the moment this means each type (and all the types of the arguments
+	% of functors of the type if it's a discriminated union) must be either
+	% be a discriminated union, an array, an int, a character, a float or a
+	% string.  
+:- func can_generate_dtd_for_types(element_pred, list(type_desc), 
+	map(type_desc, unit), map(string, type_desc)) = dtd_generation_result.
+:- mode can_generate_dtd_for_types(in(element_pred), in, in, in) = out is det.
+	
+can_generate_dtd_for_types(_, [], _, _) = ok.
+can_generate_dtd_for_types(MakeElement, [TypeDesc | TypeDescs], DoneTypeDescs,
+		ElementsSoFar) = Result :-
 	(
 		(
 			is_discriminated_union(TypeDesc, _)
@@ -1152,8 +1149,8 @@
 		(
 			map.search(DoneTypeDescs, TypeDesc, _)
 		->
-			check_types_ok(MakeElement, TypeDescs, DoneTypeDescs,
-				ElementsSoFar, Result)
+			Result = can_generate_dtd_for_types(MakeElement, 
+				TypeDescs, DoneTypeDescs, ElementsSoFar)
 		;
 			get_elements_and_args(MakeElement, TypeDesc, Elements,
 				_, _, ArgLists, _),
@@ -1178,9 +1175,9 @@
 					NewElementsSoFar),
 				map.det_insert(DoneTypeDescs, TypeDesc, unit, 
 					NewDoneTypeDescs),
-				check_types_ok(MakeElement, NewTypeDescs,
-					NewDoneTypeDescs, NewElementsSoFar,
-					Result)
+				Result = can_generate_dtd_for_types(
+					MakeElement, NewTypeDescs,
+					NewDoneTypeDescs, NewElementsSoFar)
 			)
 		)
 	;
@@ -1210,6 +1207,8 @@
 			NewAlreadyDone, !IO)
 	).
 
+	% Write the IMPLIED, FIXED or REQUIRED part of the ATTLIST entry.
+	%
 :- pred write_attribute_source_kind(attribute_source::in, maybe(string)::in,
 	io::di, io::uo) is det. 
 
@@ -1234,6 +1233,8 @@
 	write_xml_escaped_string(Value, !IO),
 	io.write_string("""", !IO).
 
+	% Write an ATTLIST entry for the given attribute.
+	%
 :- pred write_dtd_attlist(string::in, maybe(string)::in, maybe(int)::in,
 	type_desc::in, attribute::in, io::di, io::uo) is det.
 
@@ -1274,11 +1275,11 @@
 	list.foldl(write_dtd_attlist(Element, MaybeFunctor, MaybeArity, 
 		TypeDesc), Attributes, !IO).
 
+	% Write DTD entries for all the functors for a type
+	%
 :- pred write_dtd_type_elements(element_pred::in(element_pred), type_desc::in, 
 	list(type_desc)::out, io::di, io::uo) is det.
 
-	% Write DTD entries for all the functors for a type
-	%
 write_dtd_type_elements(MakeElement, TypeDesc, ChildArgTypes, !IO) :-
 	get_elements_and_args(MakeElement, TypeDesc, Elements, 
 		MaybeFunctors, MaybeArities, ArgTypeLists, AttributeLists),
@@ -1338,21 +1339,35 @@
 			),
 
 			% Put extra braces for arrays for the * at the end.
-			( is_array(TypeDesc, _) -> io.write_string("(", !IO) 
-			; true ),
+			( is_array(TypeDesc, _) -> 
+				io.write_string("(", !IO) 
+			; 
+				true 
+			),
 			
-			( Braces = yes, io.write_string("(", !IO) 
-			; Braces = no ),
+			( 
+				Braces = yes, 
+				io.write_string("(", !IO) 
+			; 
+				Braces = no 
+			),
 			
 			io.write_list(ArgTypeList, ",", 
 				write_dtd_allowed_functors_regex(MakeElement), 
 					!IO),
 			
-			( Braces = yes, io.write_string(")", !IO) 
-			; Braces = no ),
+			( 
+				Braces = yes, 
+				io.write_string(")", !IO) 
+			; 
+				Braces = no 
+			),
 			
-			( is_array(TypeDesc, _) -> io.write_string("*)", !IO) 
-			; true ),
+			( is_array(TypeDesc, _) -> 
+				io.write_string("*)", !IO) 
+			; 
+				true 
+			),
 
 			io.write_string(">\n", !IO)
 		)
Diffing profiler
Diffing robdd
Diffing runtime
Diffing runtime/GETOPT
Diffing runtime/machdeps
Diffing samples
Diffing samples/c_interface
Diffing samples/c_interface/c_calls_mercury
Diffing samples/c_interface/cplusplus_calls_mercury
Diffing samples/c_interface/mercury_calls_c
Diffing samples/c_interface/mercury_calls_cplusplus
Diffing samples/c_interface/mercury_calls_fortran
Diffing samples/c_interface/simpler_c_calls_mercury
Diffing samples/c_interface/simpler_cplusplus_calls_mercury
Diffing samples/diff
Diffing samples/muz
Diffing samples/rot13
Diffing samples/solutions
Diffing samples/tests
Diffing samples/tests/c_interface
Diffing samples/tests/c_interface/c_calls_mercury
Diffing samples/tests/c_interface/cplusplus_calls_mercury
Diffing samples/tests/c_interface/mercury_calls_c
Diffing samples/tests/c_interface/mercury_calls_cplusplus
Diffing samples/tests/c_interface/mercury_calls_fortran
Diffing samples/tests/c_interface/simpler_c_calls_mercury
Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
Diffing samples/tests/diff
Diffing samples/tests/muz
Diffing samples/tests/rot13
Diffing samples/tests/solutions
Diffing samples/tests/toplevel
Diffing scripts
Diffing tests
Diffing tests/benchmarks
Diffing tests/debugger
Diffing tests/debugger/declarative
Diffing tests/dppd
Diffing tests/general
Diffing tests/general/accumulator
Diffing tests/general/string_format
Diffing tests/general/structure_reuse
Diffing tests/grade_subdirs
Diffing tests/hard_coded
--- /dev/null	2003-10-15 16:20:24.000000000 +1000
+++ write_xml.exp2	2004-12-10 12:17:46.000000000 +1100
@@ -0,0 +1,554 @@
+Result 1:
+unsupported_dtd_type(pred(int))
+
+<?xml version="1.0"?>
+<?xml-stylesheet type="text/css" href="http://www.cs.mu.oz.au/a_css.css"?>
+<Array--array-46array-40write_xml-46mytype-41 functor="<<array>>" type="array.array(write_xml.mytype)" arity="12">
+	<Tag_Tag-45--1--write_xml-46mytype functor="Tag-" type="write_xml.mytype" arity="1">
+		<Int type="int">44</Int>
+	</Tag_Tag-45--1--write_xml-46mytype>
+	<Tag_String--1--write_xml-46mytype functor="String" type="write_xml.mytype" arity="1">
+		<String type="string">a string</String>
+	</Tag_String--1--write_xml-46mytype>
+	<hello--5--write_xml-46mytype functor="hello" type="write_xml.mytype" arity="5">
+		<String type="string">this 
+
+is a <string>&</String>
+		<Int type="int">-123</Int>
+		<Char type="character"><</Char>
+		<Float type="float">1.12300000000000</Float>
+		<yes--0--bool-46bool functor="yes" type="bool.bool" arity="0" />
+	</hello--5--write_xml-46mytype>
+	<a_tuple--1--write_xml-46mytype functor="a_tuple" type="write_xml.mytype" arity="1">
+		<Tuple--3--Tag_-123string-44-32int-44-32-123character-44-32float-125-125 functor="{}" type="{string, int, {character, float}}" arity="3">
+			<String type="string">some more stuf</String>
+			<Int type="int">123456</Int>
+			<Tuple--2--Tag_-123character-44-32float-125 functor="{}" type="{character, float}" arity="2">
+				<Char type="character">a</Char>
+				<Float type="float">1.23553225220000e-97</Float>
+			</Tuple--2--Tag_-123character-44-32float-125>
+		</Tuple--3--Tag_-123string-44-32int-44-32-123character-44-32float-125-125>
+	</a_tuple--1--write_xml-46mytype>
+	<Tag_List--1--write_xml-46mytype functor="List" type="write_xml.mytype" arity="1">
+		<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+			<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+				<Int type="int">1</Int>
+			</listPart--1--write_xml-46listPart>
+			<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+				<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+					<Int type="int">2</Int>
+				</listPart--1--write_xml-46listPart>
+				<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+					<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+					<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+						<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+							<Int type="int">4</Int>
+						</listPart--1--write_xml-46listPart>
+						<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+							<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+							<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+								<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+									<Int type="int">6</Int>
+								</listPart--1--write_xml-46listPart>
+								<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+									<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+										<Int type="int">7</Int>
+									</listPart--1--write_xml-46listPart>
+									<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+										<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+											<Int type="int">8</Int>
+										</listPart--1--write_xml-46listPart>
+										<List--2--list-46list-40write_xml-46listPart-41 functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+											<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+											<Nil--0--list-46list-40write_xml-46listPart-41 functor="[]" type="list.list(write_xml.listPart)" arity="0" />
+										</List--2--list-46list-40write_xml-46listPart-41>
+									</List--2--list-46list-40write_xml-46listPart-41>
+								</List--2--list-46list-40write_xml-46listPart-41>
+							</List--2--list-46list-40write_xml-46listPart-41>
+						</List--2--list-46list-40write_xml-46listPart-41>
+					</List--2--list-46list-40write_xml-46listPart-41>
+				</List--2--list-46list-40write_xml-46listPart-41>
+			</List--2--list-46list-40write_xml-46listPart-41>
+		</List--2--list-46list-40write_xml-46listPart-41>
+	</Tag_List--1--write_xml-46mytype>
+	<a_map--1--write_xml-46mytype functor="a_map" type="write_xml.mytype" arity="1">
+		<four--10--tree234-46tree234-40int-44-32string-41 functor="four" type="tree234.tree234(int, string)" arity="10">
+			<Int type="int">2</Int>
+			<String type="string">hello1</String>
+			<Int type="int">4</Int>
+			<String type="string">hello3</String>
+			<Int type="int">6</Int>
+			<String type="string">hello5</String>
+			<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+				<Int type="int">1</Int>
+				<String type="string">hello</String>
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			</two--4--tree234-46tree234-40int-44-32string-41>
+			<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+				<Int type="int">3</Int>
+				<String type="string">hello2</String>
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			</two--4--tree234-46tree234-40int-44-32string-41>
+			<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+				<Int type="int">5</Int>
+				<String type="string">hello4</String>
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			</two--4--tree234-46tree234-40int-44-32string-41>
+			<three--7--tree234-46tree234-40int-44-32string-41 functor="three" type="tree234.tree234(int, string)" arity="7">
+				<Int type="int">7</Int>
+				<String type="string">hello6</String>
+				<Int type="int">8</Int>
+				<String type="string">hello7</String>
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+				<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			</three--7--tree234-46tree234-40int-44-32string-41>
+		</four--10--tree234-46tree234-40int-44-32string-41>
+	</a_map--1--write_xml-46mytype>
+	<a-32-60-33-64-35-36-37-94-38-42-40-41-62-32functor-32name-33-33-33--1--write_xml-46mytype functor="a <!@#$%^&*()> functor name!!!" type="write_xml.mytype" arity="1">
+		<Int type="int">999</Int>
+	</a-32-60-33-64-35-36-37-94-38-42-40-41-62-32functor-32name-33-33-33--1--write_xml-46mytype>
+	<a_pred--1--write_xml-46mytype functor="a_pred" type="write_xml.mytype" arity="1">
+		<pred-40int-41 functor="<<predicate>>" type="pred(int)" arity="0" />
+	</a_pred--1--write_xml-46mytype>
+	<t--1--write_xml-46mytype functor="t" type="write_xml.mytype" arity="1">
+		<type_desc-46type_desc functor="tree234" type="type_desc.type_desc" arity="2">
+			<type_desc-46type_desc functor="int" type="type_desc.type_desc" arity="0" />
+			<type_desc-46type_desc functor="string" type="type_desc.type_desc" arity="0" />
+		</type_desc-46type_desc>
+	</t--1--write_xml-46mytype>
+	<ctor--1--write_xml-46mytype functor="ctor" type="write_xml.mytype" arity="1">
+		<type_desc-46type_ctor_desc functor="tree234.tree234/2" type="type_desc.type_ctor_desc" arity="0" />
+	</ctor--1--write_xml-46mytype>
+	<foreign--1--write_xml-46mytype functor="foreign" type="write_xml.mytype" arity="1">
+		<write_xml-46ftype functor="<<foreign>>" type="write_xml.ftype" arity="0" />
+	</foreign--1--write_xml-46mytype>
+	<pointer--1--write_xml-46mytype functor="pointer" type="write_xml.mytype" arity="1">
+		<c_pointer functor="<<c_pointer>>" type="c_pointer" arity="0" />
+	</pointer--1--write_xml-46mytype>
+</Array--array-46array-40write_xml-46mytype-41>
+Result 2:
+ok
+
+<?xml version="1.0"?>
+<?xml-stylesheet type="text/css" href="http://www.cs.mu.oz.au/a_css.css"?>
+<!DOCTYPE wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 [
+
+<!-- Elements for functors of type "write_xml.wrap(tree234.tree234(int, string))" -->
+
+<!ELEMENT wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 (empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41)>
+<!ATTLIST wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 functor CDATA #FIXED "wrap">
+<!ATTLIST wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 field CDATA #IMPLIED>
+<!ATTLIST wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 type CDATA #FIXED "write_xml.wrap(tree234.tree234(int, string))">
+<!ATTLIST wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 arity CDATA #FIXED "1">
+
+<!-- Elements for functors of type "tree234.tree234(int, string)" -->
+
+<!ELEMENT empty--0--tree234-46tree234-40int-44-32string-41 EMPTY>
+<!ATTLIST empty--0--tree234-46tree234-40int-44-32string-41 functor CDATA #FIXED "empty">
+<!ATTLIST empty--0--tree234-46tree234-40int-44-32string-41 field CDATA #IMPLIED>
+<!ATTLIST empty--0--tree234-46tree234-40int-44-32string-41 type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST empty--0--tree234-46tree234-40int-44-32string-41 arity CDATA #FIXED "0">
+
+<!ELEMENT four--10--tree234-46tree234-40int-44-32string-41 (Int,String,Int,String,Int,String,(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41))>
+<!ATTLIST four--10--tree234-46tree234-40int-44-32string-41 functor CDATA #FIXED "four">
+<!ATTLIST four--10--tree234-46tree234-40int-44-32string-41 field CDATA #IMPLIED>
+<!ATTLIST four--10--tree234-46tree234-40int-44-32string-41 type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST four--10--tree234-46tree234-40int-44-32string-41 arity CDATA #FIXED "10">
+
+<!ELEMENT three--7--tree234-46tree234-40int-44-32string-41 (Int,String,Int,String,(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41))>
+<!ATTLIST three--7--tree234-46tree234-40int-44-32string-41 functor CDATA #FIXED "three">
+<!ATTLIST three--7--tree234-46tree234-40int-44-32string-41 field CDATA #IMPLIED>
+<!ATTLIST three--7--tree234-46tree234-40int-44-32string-41 type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST three--7--tree234-46tree234-40int-44-32string-41 arity CDATA #FIXED "7">
+
+<!ELEMENT two--4--tree234-46tree234-40int-44-32string-41 (Int,String,(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41),(empty--0--tree234-46tree234-40int-44-32string-41|four--10--tree234-46tree234-40int-44-32string-41|three--7--tree234-46tree234-40int-44-32string-41|two--4--tree234-46tree234-40int-44-32string-41))>
+<!ATTLIST two--4--tree234-46tree234-40int-44-32string-41 functor CDATA #FIXED "two">
+<!ATTLIST two--4--tree234-46tree234-40int-44-32string-41 field CDATA #IMPLIED>
+<!ATTLIST two--4--tree234-46tree234-40int-44-32string-41 type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST two--4--tree234-46tree234-40int-44-32string-41 arity CDATA #FIXED "4">
+
+<!-- Elements for functors of type "int" -->
+
+<!ELEMENT Int (#PCDATA)>
+<!ATTLIST Int type CDATA #FIXED "int">
+<!ATTLIST Int field CDATA #IMPLIED>
+
+<!-- Elements for functors of type "string" -->
+
+<!ELEMENT String (#PCDATA)>
+<!ATTLIST String type CDATA #FIXED "string">
+<!ATTLIST String field CDATA #IMPLIED>
+
+
+]>
+<wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41 functor="wrap" type="write_xml.wrap(tree234.tree234(int, string))" arity="1">
+	<four--10--tree234-46tree234-40int-44-32string-41 functor="four" type="tree234.tree234(int, string)" arity="10">
+		<Int type="int">2</Int>
+		<String type="string">hello1</String>
+		<Int type="int">4</Int>
+		<String type="string">hello3</String>
+		<Int type="int">6</Int>
+		<String type="string">hello5</String>
+		<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">1</Int>
+			<String type="string">hello</String>
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two--4--tree234-46tree234-40int-44-32string-41>
+		<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">3</Int>
+			<String type="string">hello2</String>
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two--4--tree234-46tree234-40int-44-32string-41>
+		<two--4--tree234-46tree234-40int-44-32string-41 functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">5</Int>
+			<String type="string">hello4</String>
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two--4--tree234-46tree234-40int-44-32string-41>
+		<three--7--tree234-46tree234-40int-44-32string-41 functor="three" type="tree234.tree234(int, string)" arity="7">
+			<Int type="int">7</Int>
+			<String type="string">hello6</String>
+			<Int type="int">8</Int>
+			<String type="string">hello7</String>
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty--0--tree234-46tree234-40int-44-32string-41 functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</three--7--tree234-46tree234-40int-44-32string-41>
+	</four--10--tree234-46tree234-40int-44-32string-41>
+</wrap--1--write_xml-46wrap-40tree234-46tree234-40int-44-32string-41-41>
+Result 3:
+ok
+
+<?xml version="1.0"?>
+<?xml-stylesheet type="text/css" href="http://www.cs.mu.oz.au/a_css.css"?>
+<!DOCTYPE wrap [
+
+<!-- Elements for functors of type "write_xml.wrap(tree234.tree234(int, string))" -->
+
+<!ELEMENT wrap (empty|four|three|two)>
+<!ATTLIST wrap functor CDATA #FIXED "wrap">
+<!ATTLIST wrap field CDATA #IMPLIED>
+<!ATTLIST wrap type CDATA #FIXED "write_xml.wrap(tree234.tree234(int, string))">
+<!ATTLIST wrap arity CDATA #FIXED "1">
+
+<!-- Elements for functors of type "tree234.tree234(int, string)" -->
+
+<!ELEMENT empty EMPTY>
+<!ATTLIST empty functor CDATA #FIXED "empty">
+<!ATTLIST empty field CDATA #IMPLIED>
+<!ATTLIST empty type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST empty arity CDATA #FIXED "0">
+
+<!ELEMENT four (Int,String,Int,String,Int,String,(empty|four|three|two),(empty|four|three|two),(empty|four|three|two),(empty|four|three|two))>
+<!ATTLIST four functor CDATA #FIXED "four">
+<!ATTLIST four field CDATA #IMPLIED>
+<!ATTLIST four type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST four arity CDATA #FIXED "10">
+
+<!ELEMENT three (Int,String,Int,String,(empty|four|three|two),(empty|four|three|two),(empty|four|three|two))>
+<!ATTLIST three functor CDATA #FIXED "three">
+<!ATTLIST three field CDATA #IMPLIED>
+<!ATTLIST three type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST three arity CDATA #FIXED "7">
+
+<!ELEMENT two (Int,String,(empty|four|three|two),(empty|four|three|two))>
+<!ATTLIST two functor CDATA #FIXED "two">
+<!ATTLIST two field CDATA #IMPLIED>
+<!ATTLIST two type CDATA #FIXED "tree234.tree234(int, string)">
+<!ATTLIST two arity CDATA #FIXED "4">
+
+<!-- Elements for functors of type "int" -->
+
+<!ELEMENT Int (#PCDATA)>
+<!ATTLIST Int type CDATA #FIXED "int">
+<!ATTLIST Int field CDATA #IMPLIED>
+
+<!-- Elements for functors of type "string" -->
+
+<!ELEMENT String (#PCDATA)>
+<!ATTLIST String type CDATA #FIXED "string">
+<!ATTLIST String field CDATA #IMPLIED>
+
+
+]>
+<wrap functor="wrap" type="write_xml.wrap(tree234.tree234(int, string))" arity="1">
+	<four functor="four" type="tree234.tree234(int, string)" arity="10">
+		<Int type="int">2</Int>
+		<String type="string">hello1</String>
+		<Int type="int">4</Int>
+		<String type="string">hello3</String>
+		<Int type="int">6</Int>
+		<String type="string">hello5</String>
+		<two functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">1</Int>
+			<String type="string">hello</String>
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two>
+		<two functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">3</Int>
+			<String type="string">hello2</String>
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two>
+		<two functor="two" type="tree234.tree234(int, string)" arity="4">
+			<Int type="int">5</Int>
+			<String type="string">hello4</String>
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</two>
+		<three functor="three" type="tree234.tree234(int, string)" arity="7">
+			<Int type="int">7</Int>
+			<String type="string">hello6</String>
+			<Int type="int">8</Int>
+			<String type="string">hello7</String>
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+			<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+		</three>
+	</four>
+</wrap>
+Result 3_1:
+ok
+
+<?xml version="1.0"?>
+<?xml-stylesheet type="text/css" href="http://www.cs.mu.oz.au/a_css.css"?>
+<!DOCTYPE Array--array-46array-40write_xml-46listPart-41 [
+
+<!-- Elements for functors of type "array.array(write_xml.listPart)" -->
+
+<!ELEMENT Array--array-46array-40write_xml-46listPart-41 ((listPart--1--write_xml-46listPart|nothing--0--write_xml-46listPart)*)>
+<!ATTLIST Array--array-46array-40write_xml-46listPart-41 functor CDATA #IMPLIED>
+<!ATTLIST Array--array-46array-40write_xml-46listPart-41 field CDATA #IMPLIED>
+<!ATTLIST Array--array-46array-40write_xml-46listPart-41 type CDATA #FIXED "array.array(write_xml.listPart)">
+<!ATTLIST Array--array-46array-40write_xml-46listPart-41 arity CDATA #IMPLIED>
+
+<!-- Elements for functors of type "write_xml.listPart" -->
+
+<!ELEMENT listPart--1--write_xml-46listPart (Int)>
+<!ATTLIST listPart--1--write_xml-46listPart functor CDATA #FIXED "listPart">
+<!ATTLIST listPart--1--write_xml-46listPart field CDATA #IMPLIED>
+<!ATTLIST listPart--1--write_xml-46listPart type CDATA #FIXED "write_xml.listPart">
+<!ATTLIST listPart--1--write_xml-46listPart arity CDATA #FIXED "1">
+
+<!ELEMENT nothing--0--write_xml-46listPart EMPTY>
+<!ATTLIST nothing--0--write_xml-46listPart functor CDATA #FIXED "nothing">
+<!ATTLIST nothing--0--write_xml-46listPart field CDATA #IMPLIED>
+<!ATTLIST nothing--0--write_xml-46listPart type CDATA #FIXED "write_xml.listPart">
+<!ATTLIST nothing--0--write_xml-46listPart arity CDATA #FIXED "0">
+
+<!-- Elements for functors of type "int" -->
+
+<!ELEMENT Int (#PCDATA)>
+<!ATTLIST Int type CDATA #FIXED "int">
+<!ATTLIST Int field CDATA #IMPLIED>
+
+
+]>
+<Array--array-46array-40write_xml-46listPart-41 functor="<<array>>" type="array.array(write_xml.listPart)" arity="9">
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">1</Int>
+	</listPart--1--write_xml-46listPart>
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">2</Int>
+	</listPart--1--write_xml-46listPart>
+	<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">4</Int>
+	</listPart--1--write_xml-46listPart>
+	<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">6</Int>
+	</listPart--1--write_xml-46listPart>
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">7</Int>
+	</listPart--1--write_xml-46listPart>
+	<listPart--1--write_xml-46listPart functor="listPart" type="write_xml.listPart" arity="1">
+		<Int type="int">8</Int>
+	</listPart--1--write_xml-46listPart>
+	<nothing--0--write_xml-46listPart functor="nothing" type="write_xml.listPart" arity="0" />
+</Array--array-46array-40write_xml-46listPart-41>
+Result 4:
+ok
+
+<?xml version="1.0"?>
+<!DOCTYPE List PUBLIC "test" "test.dtd">
+<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+	<Tag_Tag-45 functor="Tag-" type="write_xml.mytype" arity="1">
+		<Int type="int">44</Int>
+	</Tag_Tag-45>
+	<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+		<Tag_String functor="String" type="write_xml.mytype" arity="1">
+			<String type="string">a string</String>
+		</Tag_String>
+		<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+			<hello functor="hello" type="write_xml.mytype" arity="5">
+				<String type="string">this 
+
+is a <string>&</String>
+				<Int type="int">-123</Int>
+				<Char type="character"><</Char>
+				<Float type="float">1.12300000000000</Float>
+				<yes functor="yes" type="bool.bool" arity="0" />
+			</hello>
+			<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+				<a_tuple functor="a_tuple" type="write_xml.mytype" arity="1">
+					<Tuple functor="{}" type="{string, int, {character, float}}" arity="3">
+						<String type="string">some more stuf</String>
+						<Int type="int">123456</Int>
+						<Tuple functor="{}" type="{character, float}" arity="2">
+							<Char type="character">a</Char>
+							<Float type="float">1.23553225220000e-97</Float>
+						</Tuple>
+					</Tuple>
+				</a_tuple>
+				<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+					<Tag_List functor="List" type="write_xml.mytype" arity="1">
+						<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+							<listPart functor="listPart" type="write_xml.listPart" arity="1">
+								<Int type="int">1</Int>
+							</listPart>
+							<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+								<listPart functor="listPart" type="write_xml.listPart" arity="1">
+									<Int type="int">2</Int>
+								</listPart>
+								<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+									<nothing functor="nothing" type="write_xml.listPart" arity="0" />
+									<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+										<listPart functor="listPart" type="write_xml.listPart" arity="1">
+											<Int type="int">4</Int>
+										</listPart>
+										<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+											<nothing functor="nothing" type="write_xml.listPart" arity="0" />
+											<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+												<listPart functor="listPart" type="write_xml.listPart" arity="1">
+													<Int type="int">6</Int>
+												</listPart>
+												<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+													<listPart functor="listPart" type="write_xml.listPart" arity="1">
+														<Int type="int">7</Int>
+													</listPart>
+													<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+														<listPart functor="listPart" type="write_xml.listPart" arity="1">
+															<Int type="int">8</Int>
+														</listPart>
+														<List functor="[|]" type="list.list(write_xml.listPart)" arity="2">
+															<nothing functor="nothing" type="write_xml.listPart" arity="0" />
+															<Nil functor="[]" type="list.list(write_xml.listPart)" arity="0" />
+														</List>
+													</List>
+												</List>
+											</List>
+										</List>
+									</List>
+								</List>
+							</List>
+						</List>
+					</Tag_List>
+					<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+						<a_map functor="a_map" type="write_xml.mytype" arity="1">
+							<four functor="four" type="tree234.tree234(int, string)" arity="10">
+								<Int type="int">2</Int>
+								<String type="string">hello1</String>
+								<Int type="int">4</Int>
+								<String type="string">hello3</String>
+								<Int type="int">6</Int>
+								<String type="string">hello5</String>
+								<two functor="two" type="tree234.tree234(int, string)" arity="4">
+									<Int type="int">1</Int>
+									<String type="string">hello</String>
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+								</two>
+								<two functor="two" type="tree234.tree234(int, string)" arity="4">
+									<Int type="int">3</Int>
+									<String type="string">hello2</String>
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+								</two>
+								<two functor="two" type="tree234.tree234(int, string)" arity="4">
+									<Int type="int">5</Int>
+									<String type="string">hello4</String>
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+								</two>
+								<three functor="three" type="tree234.tree234(int, string)" arity="7">
+									<Int type="int">7</Int>
+									<String type="string">hello6</String>
+									<Int type="int">8</Int>
+									<String type="string">hello7</String>
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+									<empty functor="empty" type="tree234.tree234(int, string)" arity="0" />
+								</three>
+							</four>
+						</a_map>
+						<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+							<a-32-60-33-64-35-36-37-94-38-42-40-41-62-32functor-32name-33-33-33 functor="a <!@#$%^&*()> functor name!!!" type="write_xml.mytype" arity="1">
+								<Int type="int">999</Int>
+							</a-32-60-33-64-35-36-37-94-38-42-40-41-62-32functor-32name-33-33-33>
+							<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+								<a_pred functor="a_pred" type="write_xml.mytype" arity="1">
+									<Unknown functor="<<predicate>>" type="pred(int)" arity="0" />
+								</a_pred>
+								<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+									<t functor="t" type="write_xml.mytype" arity="1">
+										<Unknown functor="tree234" type="type_desc.type_desc" arity="2">
+											<Unknown functor="int" type="type_desc.type_desc" arity="0" />
+											<Unknown functor="string" type="type_desc.type_desc" arity="0" />
+										</Unknown>
+									</t>
+									<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+										<ctor functor="ctor" type="write_xml.mytype" arity="1">
+											<Unknown functor="tree234.tree234/2" type="type_desc.type_ctor_desc" arity="0" />
+										</ctor>
+										<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+											<foreign functor="foreign" type="write_xml.mytype" arity="1">
+												<Unknown functor="<<foreign>>" type="write_xml.ftype" arity="0" />
+											</foreign>
+											<List functor="[|]" type="list.list(write_xml.mytype)" arity="2">
+												<pointer functor="pointer" type="write_xml.mytype" arity="1">
+													<Unknown functor="<<c_pointer>>" type="c_pointer" arity="0" />
+												</pointer>
+												<Nil functor="[]" type="list.list(write_xml.mytype)" arity="0" />
+											</List>
+										</List>
+									</List>
+								</List>
+							</List>
+						</List>
+					</List>
+				</List>
+			</List>
+		</List>
+	</List>
+</List>
+Result 5:
+ok
+
+<?xml version="1.0"?>
+<!DOCTYPE X SYSTEM "test">
+<X>
+	<X>666</X>
+</X>
+Result 6:
+ok
+
+Result 7:
+duplicate_elements("X", [write_xml.listPart, write_xml.wrap(write_xml.listPart)])
+
+Result 8:
+multiple_functors_for_root
+
+<?xml version="1.0"?>
+<ext--1--write_xml-46ext functor="ext" type="write_xml.ext" arity="1">
+	<Int type="int">1</Int>
+</ext--1--write_xml-46ext>
+Result 9:
+ok
Diffing tests/hard_coded/exceptions
Diffing tests/hard_coded/purity
Diffing tests/hard_coded/sub-modules
Diffing tests/hard_coded/typeclasses
Diffing tests/invalid
Diffing tests/invalid/purity
Diffing tests/misc_tests
Diffing tests/mmc_make
Diffing tests/mmc_make/lib
Diffing tests/recompilation
Diffing tests/tabling
Diffing tests/term
Diffing tests/valid
Diffing tests/warnings
Diffing tools
Diffing trace
Diffing util
Diffing vim
Diffing vim/after
Diffing vim/ftplugin
Diffing vim/syntax
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list