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

Julien Fischer juliensf at cs.mu.OZ.AU
Fri Dec 10 02:20:56 AEDT 2004


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?


> Index: library/term_to_xml.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/library/term_to_xml.m,v
> retrieving revision 1.1
> diff -u -r1.1 term_to_xml.m
> --- library/term_to_xml.m	7 Dec 2004 04:55:49 -0000	1.1
> +++ library/term_to_xml.m	9 Dec 2004 01:14:30 -0000
> @@ -14,31 +14,25 @@

...

> -	% write_xml_doc_cc(Term, MaybeStyleSheet, MaybeDTD, DTDResult, !IO).
> -	% Write Term to the current output stream as an XML document.
> +	% write_xml_doc_cc(Term, ElementMapping, MaybeStyleSheet, MaybeDTD,
> +	%	DTDResult, !IO).
> +	% Write Term to the current output stream as an XML document using
> +	% ElementMapping as the scheme to map functors to elements.
>  	% 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 was requested and
> -	% the type has more than one top level functor then
> -	% multiple_functors_for_root will be returned in DTDResult and nothing
> -	% will be written.
> -	%
> -:- pred write_xml_doc_cc(T::in, maybe_stylesheet::in, maybe_dtd::in,
> -	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/

> +	% 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.

> +:- pred write_xml_doc_cc(T::in, element_mapping::in(element_mapping),
> +	maybe_stylesheet::in, maybe_dtd::in, dtd_generation_result::out,
> +	io::di, io::uo) is cc_multi.
> +
> +	% write_xml_doc_cc(Stream, Term, ElementMapping, MaybeStyleSheet,
> +	%	 MaybeDTD, DTDResult, !IO).
> +	% Same as write_xml_doc/7 except write the XML doc to the given
>  	% output stream.
>  	%
> -:- pred write_xml_doc_cc(io.output_stream::in, T::in, maybe_stylesheet::in,
> +:- pred write_xml_doc_cc(io.output_stream::in, T::in,
> +	element_mapping::in(element_mapping), maybe_stylesheet::in,
>  	maybe_dtd::in, dtd_generation_result::out, io::di, io::uo) is cc_multi.
>
> -	% True if the given type doesn not have multiple top level functors.
> -	%
> -:- pred ok_to_generate_dtd(type_desc::in) is semidet.
> -
> -	% write_dtd(Term, DTDResult, !IO).
> -	% Write a DTD for the given term to the current output stream.  If the
> -	% type of Term has more than one top level functor then
> -	% multiple_functors_for_root will be returned in DTDResult and
> -	% nothing will be written, otherwise ok is returned in DTDResult.
> +	% check_ok_to_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'.
> +	%
> +:- 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.

> +
> +	% 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'.
>  	%
> -:- pred write_dtd(T::unused, dtd_generation_result::out, io::di, io::uo)
> -	is det.
> +:- pred write_dtd(T::unused, element_mapping::in(element_mapping),
> +	dtd_generation_result::out, io::di, io::uo) is det.
>
> -	% write_dtd(Stream, Term, DTDResult, !IO).
> -	% Write a DTD for the given term to the specified output stream. If the
> -	% type of Term has more than one top level functor then
> -	% multiple_functors_for_root will be returned in DTDResult and
> -	% nothing will be written, otherwise ok is returned in DTDResult.
> +	% write_dtd(Stream, Term, ElementMapping, DTDResult, !IO).
> +	% Same as write_dtd/5 except the DTD will be written to the given
> +	% output stream.
>  	%
> -:- pred write_dtd(io.output_stream::in, T::unused, dtd_generation_result::out,
> +:- pred write_dtd(io.output_stream::in, T::unused,
> +	element_mapping::in(element_mapping), dtd_generation_result::out,
>  	io::di, io::uo) is det.
>
> -	% write_dtd_for_type(Type, DTDResult, !IO).
> -	% Write a DTD for the given type to the current output stream. If the
> -	% type has more than one top level functor then
> -	% multiple_functors_for_root will be returned in DTDResult and nothing
> -	% will be written, otherwise ok is returned in DTDResult.
> +	% write_dtd_for_type(Type, ElementMapping, DTDResult, !IO).
> +	% 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'.
>  	%
> -:- pred write_dtd_from_type(type_desc::in, dtd_generation_result::out,
> +:- pred write_dtd_from_type(type_desc::in,
> +	element_mapping::in(element_mapping), dtd_generation_result::out,
>  	io::di, io::uo) is det.
>
> -	% write_dtd_for_type(Stream, Type, DTDResult, !IO).
> -	% Write a DTD for the given type to the given output stream. If the
> -	% type has more than one top level functor then
> -	% multiple_functors_for_root will be returned in DTDResult and nothing
> -	% will be written, otherwise ok is returned in DTDResult.
> +	% write_dtd_for_type(Stream, Type, ElementMapping, DTDResult, !IO).
> +	% Same as write_dtd_for_type/5 except the DTD will be written to the
> +	% given output stream.
>  	%
>  :- pred write_dtd_from_type(io.output_stream::in, type_desc::in,
> +	element_mapping::in(element_mapping),
>  	dtd_generation_result::out, io::di, io::uo) is det.
>
> -	% write_xml_element(NonCanon, IndentLevel, Term, !IO).
> +	% write_xml_element(NonCanon, MakeElement, IndentLevel, Term, !IO).
>  	% Write XML elements for the given term and all its descendents,
>  	% using IndentLevel as the initial indentation level (each
> -	% indentation level is one space character).  No <?xml ... ?>
> +	% indentation level is one tab character) and using the MakeElement
> +	% predicate to map functors to elements.  No <?xml ... ?>
>  	% header will be written.  Non-canonical terms will be handled
>  	% according to the value of NonCanon.  See the deconstruct
>  	% module in the standard library for more information on this argument.
>  	%
> -:- pred write_xml_element(deconstruct.noncanon_handling, int, T, io, io).
> -:- mode write_xml_element(in(do_not_allow), in, in, di, uo) is det.
> -:- mode write_xml_element(in(canonicalize), in, in,  di, uo) is det.
> -:- mode write_xml_element(in(include_details_cc), in, in, di, uo) is cc_multi.
> -:- mode write_xml_element(in, in, in, di, uo) is cc_multi.
> +:- pred write_xml_element(deconstruct.noncanon_handling,
> +	element_pred, int, T, io, io).
> +:- mode write_xml_element(in(do_not_allow), in(element_pred), in, in, di, uo)
> +	is det.
> +:- mode write_xml_element(in(canonicalize), in(element_pred), in, in,  di, uo)
> +	is det.
> +:- mode write_xml_element(in(include_details_cc), in(element_pred), in, in,
> +	di, uo) is cc_multi.
> +:- mode write_xml_element(in, in(element_pred), in, in, di, uo) is cc_multi.
> +
> +	% Deterministic procedures with the following signature can be used as
> +	% custom functor to element mappings.  The inputs to the procedure are
> +	% a type and some information about the required functor for that type
> +	% if the type is a discriminated union.  The output should be a well
> +	% formed XML element name and a list of attributes that should be set
> +	% for that element.  See the types `maybe_functor_info' and
> +	% `attribute' below.
> +	%
> +:- type element_pred == (pred(type_desc, maybe_functor_info, string,
> +	list(attribute))).
> +
> +:- inst element_pred == (pred(in, in, out, out) is det).
> +
> +	% 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'.

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

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

>
> +:- 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.

...
> -			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?

> +:- 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_types_ok(_, [], _, _, ok).
> +check_types_ok(MakeElement, [TypeDesc | TypeDescs], DoneTypeDescs,
> +		ElementsSoFar, Result) :-
> +	(
> +		(
> +			is_discriminated_union(TypeDesc, _)
> +		;
> +			is_array(TypeDesc, _)
> +		;
> +			is_primitive_type(TypeDesc, _)
> +		)
> +	->
> +		(
> +			map.search(DoneTypeDescs, TypeDesc, _)
> +		->
> +			check_types_ok(MakeElement, TypeDescs, DoneTypeDescs,
> +				ElementsSoFar, Result)
> +		;
> +			get_elements_and_args(MakeElement, TypeDesc, Elements,
> +				_, _, ArgLists, _),
> +			list.filter(map.contains(ElementsSoFar), Elements,
> +				DupElements),
> +			(
> +				DupElements = [DupElement | _],
> +				map.lookup(ElementsSoFar, DupElement,
> +					DupTypeDesc),
> +				DupTypes = [TypeDesc, DupTypeDesc],
> +				Result = duplicate_elements(DupElement,
> +					DupTypes)
> +			;
> +				DupElements = [],
> +				list.merge_and_remove_dups(
> +					list.condense(ArgLists),
> +					TypeDescs, NewTypeDescs),
> +				list.duplicate(length(Elements), TypeDesc,
> +					TypeDescList),
> +				map.det_insert_from_corresponding_lists(
> +					ElementsSoFar, Elements, TypeDescList,
> +					NewElementsSoFar),
> +				map.det_insert(DoneTypeDescs, TypeDesc, unit,
> +					NewDoneTypeDescs),
> +				check_types_ok(MakeElement, NewTypeDescs,
> +					NewDoneTypeDescs, NewElementsSoFar,
> +					Result)
> +			)
> +		)
> +	;
> +		Result = unsupported_dtd_type(TypeDesc)
> +	).
>

> +		MaybeArities, ArgTypeLists, AttributeLists, !IO).
> +
> +:- pred write_dtd_entries(element_pred::in(element_pred), type_desc::in,
> +	list(string)::in, list(maybe(string))::in, list(maybe(int))::in,
> +	list(list(type_desc))::in, list(list(attribute))::in,
>  	io::di, io::uo) is det.
>
...
> +			;
> +				Tail = [],
> +				(
> +					num_functors(Head) > 1
> +				->
> +					Braces = no
> +				;
> +					Braces = yes
> +				)
> +			),
> +
> +			% Put extra braces for arrays for the * at the end.
> +			( is_array(TypeDesc, _) -> io.write_string("(", !IO)
> +			; true ),
> +
> +			( 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 ),
> +
> +			( 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.

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 ;-)

Cheers,
Julien.
--------------------------------------------------------------------------
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