diff: changes to io.m

Fergus Henderson fjh at cs.mu.oz.au
Sun Apr 27 16:32:26 AEST 1997


Hi Tom,

Here's a new version of that diff for io.m that I sent the other day;
the difference from the previous one is that this new version fixes a
few problems with the handling of univ and uniq_array in io__write.
Also I've included changes to the test cases in this diff.

Can you please review this?

-----------------------------------------------------------------------------

Implement io__print.  Improvements to io__write and io__read.
Add stubs for io__read_binary and io__write_binary.

library/io.m:
	Change the implementation of `io__write':
	    - it now writes out terms using list syntax and infix notation
	      when appropriate, just like term_io__write_term
	      (but like term_io__write_term, it doesn't yet take operator
	      precedence into account, so it still outputs some redundant
	      parentheses)
	    - it properly quotes and escapes strings, characters, and atoms
	      (XXX but it does not yet properly parenthesize constants that
	      happen to have the same name as an operator)

	Add `io__print'.  This is similar to `io__write', except that
	if the argument is a single string or character, it is printed
	directly, rather than inside quotes with special characters escaped.

	Rename `io__read_anything' as `io__read', and improve the error
	messages slightly.  The implementation is still dependent on
	term_to_type which is not yet implemented.

	Add `io__write_binary' and `io__read_binary'.  (The current
	implementation is just a pair of stubs that call `io__write'
	and `io__read'; that works, but it kinda defeats the purpose...)

	For backwards compatibility with previous versions of Mercury,
	add versions of `io__read_anything' and `io__write_anything'
	that just call `io__read' and `io__write' respectively,
	but declare them as `pragma obsolete'.

test/hard_coded/construct.m:
test/hard_coded/expand.m:
	Use `io__print' rather than `io__write' for univs,
	so that it doesn't output the `univ(... : type)' wrappers.

tests/hard_coded/deep_copy_bug.exp:
tests/hard_coded/construct.exp:
tests/hard_coded/expand.exp:
tests/hard_coded/write.exp:
tests/hard_coded/write_reg1.exp:
	Change the expected output to use proper list notation
	rather than prefix `.', and to properly quote strings and atoms,
	but also to improperly quote equivalences types :-(

tests/hard_coded/Mmake:
	Add a comment explaining that deep_copy_bug.exp, write.exp, and
	write_reg1.exp are wrong, due to a bug in mercury_compare_type_info().


Index: io.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/io.m,v
retrieving revision 1.116
diff -u -r1.116 io.m
--- io.m	1997/04/21 03:34:05	1.116
+++ io.m	1997/04/27 06:16:35
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% Copyright (C) 1995 University of Melbourne.
+% Copyright (C) 1993-1997 University of Melbourne.
 % This file may only be copied under the terms of the GNU Library General
 % Public License - see the file COPYING.LIB in the Mercury distribution.
 %-----------------------------------------------------------------------------%
@@ -71,6 +71,7 @@
 :- type io__read_result(T)	--->	ok(T)
 				;	eof
 				;	error(string, int).
+					% error message, line number
 
 :- type io__error.	% Use io__error_message to decode it.
 
@@ -128,22 +129,24 @@
 %		You can put back as many characters as you like.
 %		You can even put back something that you didn't actually read.
 
-:- pred io__read_anything(io__read_result(T), io__state, io__state).
-:- mode io__read_anything(out, di, uo) is det.
-%		Reads its argument from the current input stream.
-%		The argument may be of (almost) any type. 
-%		The term read had better be of the right type!
-%		XXX io__read_anything is NOT YET IMPLEMENTED.
-%		It will also probably be renamed io__read.
-
-:- pred io__read_anything(io__input_stream, io__read_result(T),
-							io__state, io__state).
-:- mode io__read_anything(in, out, di, uo) is det.
-%		Reads its argument to the specified stream.
-%		The argument may be of (almost) any type.
-%		The term read had better be of the right type!
-%		XXX io__read_anything is NOT YET IMPLEMENTED.
-%		It will also probably be renamed io__read.
+:- pred io__read(io__read_result(T), io__state, io__state).
+:- mode io__read(out, di, uo) is det.
+:- pred io__read(io__input_stream, io__read_result(T), io__state, io__state).
+:- mode io__read(in, out, di, uo) is det.
+%		Reads a ground term of any type, written using standard
+%		Mercury syntax, from the current or specified input stream.
+%		The type of the term read is determined by the context
+%		in which `io__read' is used.
+%		If there are no more non-whitespace characters before the
+%		end of file, then `io__read' returns `eof'.
+%		If it can read in a syntactically correct ground term
+%		of the correct type, then it returns `ok(Term)'.
+%		If characters on the input stream (up to the next `.' that
+%		is followed by whitespace) do not form a syntactically
+%		correct term, or if the term read is not a ground term,
+%		if the term is not a valid term of the appropriate type,
+%		or if encounters an I/O error, then it returns
+%		`error(Message, LineNumber)'.
 
 :- pred io__ignore_whitespace(io__result, io__state, io__state).
 :- mode io__ignore_whitespace(out, di, uo) is det.
@@ -160,6 +163,45 @@
 
 % Text output predicates.
 
+:- pred io__print(T, io__state, io__state).
+:- mode io__print(in, di, uo) is det.
+:- pred io__print(io__output_stream, T, io__state, io__state).
+:- mode io__print(in, in, di, uo) is det.
+%		io__print/3 writes its argument to the current output stream.
+%		io__print/4 writes its argument to the specified output
+%		stream.  In either case, the argument may be of any type.
+%		The argument is written in a format that is intended to
+%		be human-readable. 
+%
+%		If the argument is just a single string or character, it
+%		will be printed out exactly as is (unquoted).
+%		If the argument is of type univ, then it will print out
+%		the value stored in the univ, but not the type.
+%		For higher-order types, or for types defined using the
+%		foreign language interface (pragma c_code), the text output
+%		will only describe the type that is being printed, not the
+%		value.
+
+:- pred io__write(T, io__state, io__state).
+:- mode io__write(in, di, uo) is det.
+:- pred io__write(io__output_stream, T, io__state, io__state).
+:- mode io__write(in, in, di, uo) is det.
+%		io__write/3 writes its argument to the current output stream.
+%		io__write/4 writes its argument to the specified output stream.
+%		The argument may be of any type.
+%		The argument is written in a format that is intended to
+%		be valid Mercury syntax whenever possible.
+%
+%		Strings and characters are always printed out in quotes,
+%		using backslash escapes if necessary.
+%		For higher-order types, or for types defined using the
+%		foreign language interface (pragma c_code), the text output
+%		will only describe the type that is being printed, not the
+%		value, and the result may not be parsable by io__read.
+%		But in all other cases the format used is standard Mercury
+%		syntax, and if you do append a period and newline (".\n"),
+%		then the results can be read in again using `io__read'.
+
 :- pred io__nl(io__state, io__state).
 :- mode io__nl(di, uo) is det.
 %		Writes a newline character to the current output stream.
@@ -174,7 +216,7 @@
 
 :- pred io__write_string(io__output_stream, string, io__state, io__state).
 :- mode io__write_string(in, in, di, uo) is det.
-%		Writes a string to the specified stream.
+%		Writes a string to the specified output stream.
 
 :- pred io__write_strings(list(string), io__state, io__state).
 :- mode io__write_strings(in, di, uo) is det.
@@ -183,7 +225,7 @@
 :- pred io__write_strings(io__output_stream, list(string),
 				io__state, io__state).
 :- mode io__write_strings(in, in, di, uo) is det.
-%		Writes a string to the specified stream.
+%		Writes a list of strings to the specified output stream.
 
 :- pred io__write_char(char, io__state, io__state).
 :- mode io__write_char(in, di, uo) is det.
@@ -191,7 +233,7 @@
 
 :- pred io__write_char(io__output_stream, char, io__state, io__state).
 :- mode io__write_char(in, in, di, uo) is det.
-%		Writes a character to the specified stream.
+%		Writes a character to the specified output stream.
 
 :- pred io__write_int(int, io__state, io__state).
 :- mode io__write_int(in, di, uo) is det.
@@ -199,7 +241,7 @@
 
 :- pred io__write_int(io__output_stream, int, io__state, io__state).
 :- mode io__write_int(in, in, di, uo) is det.
-%		Writes an integer to the specified stream.
+%		Writes an integer to the specified output stream.
 
 :- pred io__write_float(float, io__state, io__state).
 :- mode io__write_float(in, di, uo) is det.
@@ -209,14 +251,14 @@
 :- pred io__write_float(io__output_stream, float, io__state, io__state).
 :- mode io__write_float(in, in, di, uo) is det.
 %	io__write_float(Float, IO0, IO1).
-%		Writes a floating point number to the specified stream.
+%		Writes a floating point number to the specified output stream.
 
 :- pred io__format(string, list(io__poly_type), io__state, io__state).
 :- mode io__format(in, in, di, uo) is det.
 %	io__format(FormatString, Arguments, IO0, IO).
 %		Formats the specified arguments according to
 %		the format string, using string__format, and
-%		then writes the result to standard output.
+%		then writes the result to the current output stream.
 %		(See the documentation of string__format for details.)
 
 :- pred io__format(io__output_stream, string, list(io__poly_type),
@@ -233,25 +275,11 @@
 %	io__write_many(Arguments, IO0, IO).
 %		Writes the specified arguments to the current output stream.
 
-:- pred io__write_many(io__output_stream, list(io__poly_type), io__state, io__state).
+:- pred io__write_many(io__output_stream, list(io__poly_type),
+			io__state, io__state).
 :- mode io__write_many(in, in, di, uo) is det.
 %	io__write_many(Stream, Arguments, IO0, IO).
-%		Writes the specified arguments to the specified stream.
-
-:- pred io__write(T, io__state, io__state).
-:- mode io__write(in, di, uo) is det.
-%		Writes its argument to the current output stream.
-%		The argument may be of (almost) any type.
-%		(Any type except a higher-order predicate type,
-%		or some of the builtin types such as io__state itself.)
-%		XXX Not all quoting of atoms is done correctly.
-
-:- pred io__write(io__output_stream, T, io__state, io__state).
-:- mode io__write(in, in, di, uo) is det.
-%		Writes its argument to the specified stream.
-%		The argument may be of (almost) any type.
-%		(Any type except a higher-order predicate type,
-%		or some of the builtin types such as io__state itself.)
+%		Writes the specified arguments to the specified output stream.
 
 :- pred io__write_list(list(T), string, pred(T, io__state, io__state),
 	io__state, io__state).
@@ -291,7 +319,8 @@
 %		Closes the current input stream.
 %		The current input stream reverts to standard input.
 
-:- pred io__open_input(string, io__res(io__input_stream), io__state, io__state).
+:- pred io__open_input(string, io__res(io__input_stream),
+			io__state, io__state).
 :- mode io__open_input(in, out, di, uo) is det.
 %	io__open_input(File, Result, IO0, IO1).
 %		Attempts to open a file for input.
@@ -454,16 +483,33 @@
 
 % Binary input predicates.
 
+:- pred io__read_binary(io__result(T), io__state, io__state).
+:- mode io__read_binary(out, di, uo) is det.
+%		Reads a binary representation of a term of type T
+%		from the current binary input stream.
+
+:- pred io__read_binary(io__binary_input_stream, io__result(T),
+		io__state, io__state).
+:- mode io__read_binary(in, out, di, uo) is det.
+%		Reads a binary representation of a term of type T
+%		from the specified binary input stream.
+
+%		Note: if you attempt to read a binary representation written
+%		by a different program, or a different version of the same
+%		program, then the results are not guaranteed to be meaningful.
+%		Another caveat is that higher-order types cannot be read. 
+%		(If you try, you will get a runtime error.)
+
 :- pred io__read_byte(io__result(int), io__state, io__state).
 :- mode io__read_byte(out, di, uo) is det.
-%		Reads a single byte from the current binary input
-%		stream and returns it in the bottom 8 bits of an integer.
+%		Reads a single 8-bit byte from the current binary input
+%		stream.
 
 :- pred io__read_byte(io__binary_input_stream, io__result(int),
 				io__state, io__state).
 :- mode io__read_byte(in, out, di, uo) is det.
-%		Reads a single byte from the specified binary input
-%		stream and returns it in the bottom 8 bits of an integer.
+%		Reads a single 8-bit byte from the specified binary input
+%		stream.
 
 :- pred io__putback_byte(int, io__state, io__state).
 :- mode io__putback_byte(in, di, uo) is det.
@@ -485,6 +531,18 @@
 
 % XXX what about wide characters?
 
+:- pred io__write_binary(T, io__state, io__state).
+:- mode io__write_binary(in, di, uo) is det.
+%		Writes a binary representation of a term to the current
+%		binary output stream, in a format suitable for reading
+%		in again with io__read_binary.
+
+:- pred io__write_binary(io__binary_output_stream, T, io__state, io__state).
+:- mode io__write_binary(in, in, di, uo) is det.
+%		Writes a binary representation of a term to the specified
+%		binary output stream, in a format suitable for reading
+%		in again with io__read_binary.
+
 :- pred io__write_byte(int, io__state, io__state).
 :- mode io__write_byte(in, di, uo) is det.
 %		Writes a single byte to the current binary output stream.
@@ -718,7 +776,6 @@
 :- pred io__remove_file(string, io__res, io__state, io__state).
 :- mode io__remove_file(in, out, di, uo) is det.
 
-
 %-----------------------------------------------------------------------------%
 
 % Memory management predicates.
@@ -759,6 +816,36 @@
 %		code.
 
 %-----------------------------------------------------------------------------%
+:- implementation.
+
+% Everything below here is not intended to be part of the public interface,
+% and will not be included in the Mercury library reference manual.
+
+%-----------------------------------------------------------------------------%
+:- interface.
+
+% For backwards compatibility:
+
+:- pragma obsolete(io__read_anything/3).
+:- pred io__read_anything(io__read_result(T), io__state, io__state).
+:- mode io__read_anything(out, di, uo) is det.
+%		Same as io__read/3.
+
+:- pragma obsolete(io__read_anything/4).
+:- pred io__read_anything(io__output_stream, io__read_result(T),
+			io__state, io__state).
+:- mode io__read_anything(in, out, di, uo) is det.
+%		Same as io__read/4.
+
+:- pragma obsolete(io__write_anything/3).
+:- pred io__write_anything(T, io__state, io__state).
+:- mode io__write_anything(in, di, uo) is det.
+%		Same as io__write/3.
+
+:- pragma obsolete(io__write_anything/4).
+:- pred io__write_anything(io__output_stream, T, io__state, io__state).
+:- mode io__write_anything(in, in, di, uo) is det.
+%		Same as io__write/4.
 
 % For use by term_io.m:
 
@@ -781,7 +868,7 @@
 %-----------------------------------------------------------------------------%
 
 :- implementation.
-:- import_module map, dir, term_io, varset, require, time.
+:- import_module map, dir, term, term_io, varset, require, time, uniq_array.
 
 :- type io__state
 	---> 	io__state(
@@ -986,25 +1073,37 @@
 	io__binary_input_stream(Stream),
 	io__putback_byte(Stream, Char).
 
-io__read_anything(X) -->
+io__read_anything(Result) -->
+	io__read(Result).
+
+io__read(Result) -->
 	term_io__read_term(ReadResult),
-	(	{ ReadResult = term(_VarSet, Term) },
+	(	
+		{ ReadResult = term(_VarSet, Term) },
 		( { term_to_type(Term, Type) } ->
-			{ X = ok(Type) }
+			{ Result = ok(Type) }
 		;
-			{ X = error("io__read_anything : the term read was not a valid type", 0) }
+			io__get_line_number(LineNumber),
+			( { \+ term__is_ground(Term) } ->
+				{ Result = error("io__read: the term read was not a ground term", LineNumber) }
+			;
+				{ Result = error("io__read: the term read did not have the right type", LineNumber) }
+			)
 		)
 	;
 		{ ReadResult = eof },
-		{ X = eof }
+		{ Result = eof }
 	;
 		{ ReadResult = error(String, Int) },
-		{ X = error(String, Int) }
+		{ Result = error(String, Int) }
 	).
 
-io__read_anything(Stream, X) -->
+io__read_anything(Stream, Result) -->
+	io__read(Stream, Result).
+
+io__read(Stream, Result) -->
 	io__set_input_stream(Stream, OrigStream),
-	io__read_anything(X),
+	io__read(Result),
 	io__set_input_stream(OrigStream, _Stream).
 
 io__ignore_whitespace(Result) -->
@@ -1076,37 +1175,252 @@
 	io__write_float(Stream, F),
 	io__write_many(Stream, Rest).
 
+io__print(Stream, Term) -->
+	io__set_output_stream(Stream, OrigStream),
+	io__print(Term),
+	io__set_output_stream(OrigStream, _Stream).
+
+io__print(Term) -->
+	% `string', `char' and `univ' are special cases for io__print
+	{ type_to_univ(Term, Univ) },
+	( { univ_to_type(Univ, String) } ->
+		io__write_string(String)
+	; { univ_to_type(Univ, Char) } ->
+		io__write_char(Char)
+	; { univ_to_type(Univ, OrigUniv) } ->
+		io__write_univ(OrigUniv)
+	;
+		io__print_quoted(Term)
+	).
+
+:- pred io__print_quoted(T, io__state, io__state).
+:- mode io__print_quoted(in, di, uo) is det.
+
+io__print_quoted(Term) -->
+	io__write(Term).
+/*
+When we have type classes, then instead of io__write(Term),
+we will want to do something like
+	( { univ_to_type_class(Univ, Portrayable) } ->
+		portray(Portrayable)
+	;
+		... code like io__write, but which prints
+		    the arguments using io__print_quoted, rather than
+		    io__write ...
+	)
+*/
+
+io__write_anything(Anything) -->
+	io__write(Anything).
+
+io__write_anything(Stream, Anything) -->
+	io__write(Stream, Anything).
+
 io__write(Stream, X) -->
 	io__set_output_stream(Stream, OrigStream),
 	io__write(X),
 	io__set_output_stream(OrigStream, _Stream).
 
+io__write(Term) -->
+	{ type_to_univ(Term, Univ) },
+	io__write_univ(Univ).
+
+:- pred io__write_univ(univ, io__state, io__state).
+:- mode io__write_univ(in, di, uo) is det.
+
+io__write_univ(Univ) -->
+	%
+	% we need to special-case the builtin types:
+	%	int, char, float, string
+	%	type_info, univ, c_pointer, uniq_array
+	%
+	( { univ_to_type(Univ, String) } ->
+		term_io__quote_string(String)
+	; { univ_to_type(Univ, Char) } ->
+		term_io__quote_char(Char)
+	; { univ_to_type(Univ, Int) } ->
+		io__write_int(Int)
+	; { univ_to_type(Univ, Float) } ->
+		io__write_float(Float)
+	; { univ_to_type(Univ, TypeInfo) } ->
+		io__write_string(type_name(TypeInfo))
+	; { univ_to_type(Univ, OrigUniv) } ->
+		io__write_univ_as_univ(OrigUniv)
+	; { univ_to_type(Univ, C_Pointer) } ->
+		io__write_c_pointer(C_Pointer)
+	; { type_ctor_name(type_ctor(univ_type(Univ))) = "uniq_array" } ->
+		%
+		% XXX shouldn't type names be module-qualified?
+		%     shouldn't that be "uniq_array:uniq_array"?
+		%
+		% Note that we can't use univ_to_type above, because we
+		% want to match on a non-ground type `uniq_array(T)'
+		% (matching against `uniq_array(void)' isn't much use).
+		% Instead, we explicitly check the type name.
+		% That makes it tricky to get the value, so
+		% we can't use io__write_uniq_array below... instead we
+		% use the following, which is a bit of a hack.
+		%
+		{ type_to_term(Univ, Term) },
+		{ varset__init(VarSet) },
+		term_io__write_term(VarSet, Term)
+	;
+		io__write_ordinary_term(Univ)
+	).
+
+:- pred io__write_univ_as_univ(univ, io__state, io__state).
+:- mode io__write_univ_as_univ(in, di, uo) is det.
 
+io__write_univ_as_univ(Univ) -->
+	io__write_string("univ("),
+	io__write_univ(Univ),
+	% XXX what is the right TYPE_QUAL_OP to use here?
+	io__write_string(" : "),
+	io__write_string(type_name(univ_type(Univ))),
+	io__write_string(")").
 
-% We want to call io__write_args as a tail-call, and so that we only
-% put one stack frame up per level of traversal.
-% This is why the code is a little unusual.
-
-io__write(Anything) -->
-	{ expand(Anything, Functor, _Arity, Args) },
-	io__write_string(Functor),
+:- pred io__write_ordinary_term(T, io__state, io__state).
+:- mode io__write_ordinary_term(in, di, uo) is det.
+
+io__write_ordinary_term(Term) -->
+	{ expand(Term, Functor, _Arity, Args) },
+	io__get_op_table(OpTable),
 	(
-		{ Args = [Arg | Args1] }
+		{ Functor = "." },
+		{ Args = [ListHead, ListTail] }
+	->
+		io__write_char('['),
+		io__write_univ(ListHead),
+		io__write_list_tail(ListTail),
+		io__write_char(']')
+	;
+		{ Functor = "[]" },
+		{ Args = [] }
+	->
+		io__write_string("[]")
+	;
+		{ Functor = "{}" },
+		{ Args = [BracedTerm] }
+	->
+		io__write_string("{ "),
+		io__write_univ(BracedTerm),
+		io__write_string(" }")
+	;
+		{ Args = [PrefixArg] },
+		{ ops__lookup_prefix_op(OpTable, Functor, _, _) }
+	->
+		io__write_char('('),
+		term_io__quote_atom(Functor),
+		io__write_char(' '),
+		io__write_univ(PrefixArg),
+		io__write_char(')')
+	;
+		{ Args = [PostfixArg] },
+		{ ops__lookup_postfix_op(OpTable, Functor, _, _) }
+	->
+		io__write_char('('),
+		io__write_univ(PostfixArg),
+		io__write_char(' '),
+		term_io__quote_atom(Functor),
+		io__write_char(')')
+	;
+		{ Args = [Arg1, Arg2] },
+		{ ops__lookup_infix_op(OpTable, Functor, _, _, _) }
+	->
+		io__write_char('('),
+		io__write_univ(Arg1),
+		io__write_char(' '),
+		term_io__quote_atom(Functor),
+		io__write_char(' '),
+		io__write_univ(Arg2),
+		io__write_char(')')
+	;
+		{ Args = [Arg1, Arg2] },
+		{ ops__lookup_binary_prefix_op(OpTable, Functor, _, _, _) }
+	->
+		io__write_char('('),
+		term_io__quote_atom(Functor),
+		io__write_char(' '),
+		io__write_univ(Arg1),
+		io__write_char(' '),
+		io__write_univ(Arg2),
+		io__write_char(')')
+	;
+		term_io__quote_atom(Functor),
+		(
+			{ Args = [X|Xs] }
+		->
+			io__write_char('('),
+			io__write_univ(X),
+			io__write_term_args(Xs),
+			io__write_char(')')
+		;
+			[]
+		)
+	).
+
+:- pred io__write_list_tail(univ, io__state, io__state).
+:- mode io__write_list_tail(in, di, uo) is det.
+
+io__write_list_tail(Term) -->
+	( 
+		{ expand_univ(Term, ".", _Arity, [ListHead, ListTail]) }
 	->
-		io__write_string("("),
-		io__write(Arg),
-		io__write_args(Args1)
+		io__write_string(", "),
+		io__write_univ(ListHead),
+		io__write_list_tail(ListTail)
 	;
+		{ expand_univ(Term, "[]", _Arity, []) }
+	->
 		[]
+	;
+		io__write_string(" | "),
+		io__write_univ(Term)
 	).
 
-:- pred io__write_args(list(univ)::in, io__state::di, io__state::uo) is det.
-io__write_args([]) --> 
-	io__write_string(")").
-io__write_args([Arg | Args]) --> 
+	% XXX expand_univ should be in std_util.m
+:- pred expand_univ(univ, string, int, list(univ)).
+:- mode expand_univ(in, out, out, out) is det.
+
+expand_univ(Univ, Name, Arity, Args) :-
+	% XXX expand is currently broken; it doesn't handle
+	% `univ' properly.  The commented out code is what
+	% we ought to have to use; instead, we can call expand
+	% directly.
+/****
+	( expand(Univ, "univ", 1, [Arg]) ->
+		expand(Arg, Name, Arity, Args)
+	;
+		error("expand returns wrong results for type univ")
+	).
+***/
+	expand(Univ, Name, Arity, Args).
+
+:- pred io__write_term_args(list(univ), io__state, io__state).
+:- mode io__write_term_args(in, di, uo) is det.
+
+	% write the remaining arguments
+io__write_term_args([]) --> [].
+io__write_term_args([X|Xs]) -->
 	io__write_string(", "),
-	io__write(Arg),
-	io__write_args(Args).
+	io__write_univ(X),
+	io__write_term_args(Xs).
+
+:- pred io__write_uniq_array(uniq_array(T), io__state, io__state).
+:- mode io__write_uniq_array(in, di, uo) is det.
+
+io__write_uniq_array(UniqArray) -->
+	io__write_string("uniq_array("),
+	{ uniq_array__to_list(UniqArray, List) },
+	io__write(List),
+	io__write_string(")").
+
+:- pred io__write_c_pointer(c_pointer, io__state, io__state).
+:- mode io__write_c_pointer(in, di, uo) is det.
+
+io__write_c_pointer(_C_Pointer) -->
+	% XXX what should we do here?
+	io__write_string("<<c_pointer>>").
 
 %-----------------------------------------------------------------------------%
 
@@ -1125,6 +1439,39 @@
 	io__set_output_stream(Stream, OrigStream),
 	io__write_list(List, Separator, OutputPred),
 	io__set_output_stream(OrigStream, _Stream).
+
+%-----------------------------------------------------------------------------%
+
+io__write_binary(Stream, Term) -->
+	io__set_binary_output_stream(Stream, OrigStream),
+	io__write_binary(Term),
+	io__set_binary_output_stream(OrigStream, _Stream).
+
+io__read_binary(Stream, Result) -->
+	io__set_output_stream(Stream, OrigStream),
+	io__read_binary(Result),
+	io__set_output_stream(OrigStream, _Stream).
+
+io__write_binary(Term) -->
+	% a quick-and-dirty implementation... not very space-efficient
+	% (not really binary!)
+	io__binary_output_stream(Stream),
+	io__write(Stream, Term),
+	io__write_string(Stream, ".\n").
+
+io__read_binary(Result) -->
+	% a quick-and-dirty implementation... not very space-efficient
+	% (not really binary!)
+	io__binary_input_stream(Stream),
+	io__read(Stream, ReadResult),
+	{ io__convert_read_result(ReadResult, Result) }.
+
+:- pred io__convert_read_result(io__read_result(T), io__result(T)).
+:- mode io__convert_read_result(in, out) is det.
+
+io__convert_read_result(ok(T), ok(T)).
+io__convert_read_result(eof, eof).
+io__convert_read_result(error(Error, _Line), error(Error)).
 
 %-----------------------------------------------------------------------------%
 
cvs diff: Diffing .
Index: Mmake
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/Mmake,v
retrieving revision 1.42
diff -u -r1.42 Mmake
--- Mmake	1997/04/21 09:56:06	1.42
+++ Mmake	1997/04/27 05:15:56
@@ -16,6 +16,10 @@
 	ho_univ_to_type elim_special_pred division_test test_imported_no_tag \
 	name_mangling cycles deep_copy_bug construct
 
+# deep_copy_bug.exp and write.exp are broken; io__write doesn't write
+# equivalence types correctly, due to a bug in mercury_compare_type_info()
+# in library/std_util.m
+
 #-----------------------------------------------------------------------------#
 
 # some tests need to be compiled with particular options
Index: construct.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/construct.exp,v
retrieving revision 1.1
diff -u -r1.1 construct.exp
--- construct.exp	1997/04/21 08:32:59	1.1
+++ construct.exp	1997/04/27 04:31:12
@@ -184,9 +184,9 @@
 About to construct three/0
 Constructed: three
 About to construct apple/1
-Constructed: apple(.(1, .(2, .(3, []))))
+Constructed: apple([1, 2, 3])
 About to construct banana/1
-Constructed: banana(.(one, .(two, .(three, []))))
+Constructed: banana([one, two, three])
 About to construct foo/0
 Constructed: foo
 About to construct bar/1
Index: construct.m
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/construct.m,v
retrieving revision 1.1
diff -u -r1.1 construct.m
--- construct.m	1997/04/21 08:33:00	1.1
+++ construct.m	1997/04/27 04:14:33
@@ -109,7 +109,7 @@
 		{ Constructed = construct(TypeInfo, FunctorNumber, Args) }
 	->
 		io__write_string("Constructed: "),
-		io__write(Constructed),
+		io__print(Constructed),
 		newline
 	;
 		io__write_string("Construction failed.\n")
Index: deep_copy_bug.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/deep_copy_bug.exp,v
retrieving revision 1.1
diff -u -r1.1 deep_copy_bug.exp
--- deep_copy_bug.exp	1997/04/10 16:04:26	1.1
+++ deep_copy_bug.exp	1997/04/27 04:54:58
@@ -1 +1 @@
-.(1, .(2, .(3, .(4, .(5, .(6, .(7, .(8, .(9, .(10, []))))))))))
+['1', '2', '3', '4', '5', '6', '7', '8', '9', '10']
Index: expand.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/expand.exp,v
retrieving revision 1.1
diff -u -r1.1 expand.exp
--- expand.exp	1997/01/14 01:26:06	1.1
+++ expand.exp	1997/04/27 05:14:57
@@ -12,24 +12,24 @@
 expand: functor three arity 0 arguments []
 
 apple/1
-argument 1 of functor apple was:.(9, .(5, .(1, [])))
-expand: functor apple arity 1 arguments .(.(9, .(5, .(1, []))), [])
+argument 1 of functor apple was:[9, 5, 1]
+expand: functor apple arity 1 arguments [[9, 5, 1]]
 
 banana/1
-argument 1 of functor banana was:.(three, .(one, .(two, [])))
-expand: functor banana arity 1 arguments .(.(three, .(one, .(two, []))), [])
+argument 1 of functor banana was:[three, one, two]
+expand: functor banana arity 1 arguments [[three, one, two]]
 
 zop/2
 argument 2 of functor zop was:2.03000000000000
-expand: functor zop arity 2 arguments .(3.30000000000000, .(2.03000000000000, []))
+expand: functor zop arity 2 arguments [3.30000000000000, 2.03000000000000]
 
 zip/2
 argument 2 of functor zip was:2
-expand: functor zip arity 2 arguments .(3, .(2, []))
+expand: functor zip arity 2 arguments [3, 2]
 
 zap/2
 argument 2 of functor zap was:-2.11100000000000
-expand: functor zap arity 2 arguments .(3, .(-2.11100000000000, []))
+expand: functor zap arity 2 arguments [3, -2.11100000000000]
 
 wombat/0
 no arguments
@@ -43,15 +43,15 @@
 TESTING POLYMORPHISM
 poly_two/1
 argument 1 of functor poly_two was:3
-expand: functor poly_two arity 1 arguments .(3, [])
+expand: functor poly_two arity 1 arguments [3]
 
 poly_three/3
 argument 3 of functor poly_three was:poly_one(9.11000000000000)
-expand: functor poly_three arity 3 arguments .(3.33000000000000, .(4, .(poly_one(9.11000000000000), [])))
+expand: functor poly_three arity 3 arguments [3.33000000000000, 4, poly_one(9.11000000000000)]
 
 poly_one/1
-argument 1 of functor poly_one was:.(2399.30000000000, [])
-expand: functor poly_one arity 1 arguments .(.(2399.30000000000, []), [])
+argument 1 of functor poly_one was:[2399.30000000000]
+expand: functor poly_one arity 1 arguments [[2399.30000000000]]
 
 
 TESTING BUILTINS
@@ -103,7 +103,7 @@
 
 ./2
 argument 2 of functor . was:[]
-expand: functor . arity 2 arguments .("hi! I'm a univ!", .([], []))
+expand: functor . arity 2 arguments ["hi! I\'m a univ!", []]
 
 <<predicate>>/0
 no arguments
@@ -129,6 +129,6 @@
 
 qwerty/1
 argument 1 of functor qwerty was:4
-expand: functor qwerty arity 1 arguments .(4, [])
+expand: functor qwerty arity 1 arguments [4]
 
 
Index: expand.m
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/expand.m,v
retrieving revision 1.2
diff -u -r1.2 expand.m
--- expand.m	1997/03/14 05:24:23	1.2
+++ expand.m	1997/04/27 05:11:05
@@ -89,7 +89,7 @@
 		{ string__format("argument %d of functor %s was:", [i(Arity),
 			s(Functor)], Str) },
 		io__write_string(Str),
-		io__write(Argument)
+		io__print(Argument)
 	;
 		io__write_string("no arguments")
 	).
@@ -99,7 +99,9 @@
 	{ string__format("expand: functor %s arity %d arguments ", [s(Functor),
 		i(Arity)], Str) },
 	io__write_string(Str),
-	io__write(Arguments).
+	io__write_string("["),
+	io__write_list(Arguments, ", ", io__print),
+	io__write_string("]").
 
 
 test_polymorphism -->
Index: name_mangling.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/name_mangling.exp,v
retrieving revision 1.1
diff -u -r1.1 name_mangling.exp
--- name_mangling.exp	1997/04/05 07:11:35	1.1
+++ name_mangling.exp	1997/04/27 05:19:12
@@ -1,3 +1,3 @@
-a strange functor
-another strange functor
-.(a strange functor, .(another strange functor, []))
+'a strange functor'
+'another strange functor'
+['a strange functor', 'another strange functor']
Index: write.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/write.exp,v
retrieving revision 1.1
diff -u -r1.1 write.exp
--- write.exp	1996/12/18 01:00:12	1.1
+++ write.exp	1997/04/27 05:19:39
@@ -2,8 +2,8 @@
 one
 two
 three
-apple(.(9, .(5, .(1, []))))
-banana(.(three, .(one, .(two, []))))
+apple([9, 5, 1])
+banana([three, one, two])
 zop(3.30000000000000, 2.03000000000000)
 zip(3, 2)
 zap(3, -2.11100000000000)
@@ -11,16 +11,15 @@
 foo
 
 TESTING POLYMORPHISM
-poly_one(.(2399.30000000000, []))
+poly_one([2399.30000000000])
 poly_two(3)
 poly_three(3.33000000000000, 4, poly_one(9.11000000000000))
 
 TESTING BUILTINS
 ""
-"Hello, world
-"
+"Hello, world\n"
 "Foo%sFoo"
-"""
+"\""
 'a'
 '&'
 3.14159000000000
@@ -28,13 +27,13 @@
 2.23954899000000e+23
 -65
 4
-.("hi! I'm a univ!", [])
-<<predicate>>
+univ(["hi! I\'m a univ!"] : list(string))
+'<<predicate>>'
 
 TESTING OTHER TYPES
-1
-0
-1
+'1'
+'0'
+'1'
 empty
 qwerty(4)
 
Index: write_reg1.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/write_reg1.exp,v
retrieving revision 1.1
diff -u -r1.1 write_reg1.exp
--- write_reg1.exp	1997/01/14 01:36:21	1.1
+++ write_reg1.exp	1997/04/27 05:19:53
@@ -2,8 +2,8 @@
 one
 two
 three
-apple(.(9, .(5, .(1, []))))
-banana(.(three, .(one, .(two, []))))
+apple([9, 5, 1])
+banana([three, one, two])
 zop(3.30000000000000, 2.03000000000000)
 zip(3, 2)
 zap(3, -2.11100000000000)
@@ -11,16 +11,15 @@
 foo
 
 TESTING POLYMORPHISM
-poly_one(.(2399.30000000000, []))
+poly_one([2399.30000000000])
 poly_two(3)
 poly_three(3.33000000000000, 4, poly_one(9.11000000000000))
 
 TESTING BUILTINS
 ""
-"Hello, world
-"
+"Hello, world\n"
 "Foo%sFoo"
-"""
+"\""
 'a'
 '&'
 3.14159000000000
@@ -28,13 +27,13 @@
 2.23954899000000e+23
 -65
 4
-.("hi! I'm a univ!", [])
-<<predicate>>
+univ(["hi! I\'m a univ!"] : list(string))
+'<<predicate>>'
 
 TESTING OTHER TYPES
-1
-0
-1
+'1'
+'0'
+'1'
 empty
 qwerty(4)
 

-- 
Fergus Henderson <fjh at cs.mu.oz.au>   |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>   |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3         |     -- the last words of T. S. Garp.



More information about the developers mailing list