diff: add module qualifiers to type names.

Tyson Richard DOWD trd at cs.mu.oz.au
Tue Jul 29 19:40:28 AEST 1997


Hi.

Can someone review this please?

===================================================================

Estimated hours taken: 2

Add module qualifiers to names generated by the function
std_util:type_name/1.

compiler/base_type_info.m:
compiler/polymorphism.m:
library/mercury_builtin.m:
	Add module names to base_type_infos.

library/io.m:
library/term.m:
	Check module names as well as type names for special cases.
	Add module qualifiers to terms that represent types
	(That is, when converting type_infos to terms).

library/std_util.m:
	Add type_ctor_module_name/1, add an argument to
	type_ctor_name_and_arity for the module name.
	Add module qualifiers to the name returned by type_name.

runtime/type_info.h:
	Define the offset fo type module names, add
	MR_TYPECTOR_GET_HOT_MODULE_NAME and
	MR_BASE_TYPEINFO_GET_TYPE_MODULE_NAME

tests/hard_coded/higher_order_type_manip.exp:
tests/hard_coded/write.exp:
tests/hard_coded/write_.exp:
	Update test case expected output with module qualifiers where needed.

Index: compiler/base_type_info.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/base_type_info.m,v
retrieving revision 1.11
diff -u -r1.11 base_type_info.m
--- base_type_info.m	1997/07/27 14:59:49	1.11
+++ base_type_info.m	1997/07/29 04:31:56
@@ -157,8 +157,9 @@
 		base_type_info__construct_functors(ModuleInfo, TypeName,
 			TypeArity, FunctorsArg),
 		NameArg = yes(const(string_const(TypeName))),
-		list__append(PredAddrArgs, [LayoutArg, FunctorsArg, NameArg], 
-			FinalArgs)
+		ModuleArg = yes(const(string_const(ModuleName))),
+		list__append(PredAddrArgs, [LayoutArg, FunctorsArg, NameArg,
+			ModuleArg], FinalArgs)
 	;
 		FinalArgs = PredAddrArgs
 	),
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/compiler/polymorphism.m,v
retrieving revision 1.113
diff -u -r1.113 polymorphism.m
--- polymorphism.m	1997/07/27 15:01:22	1.113
+++ polymorphism.m	1997/07/29 07:36:02
@@ -43,6 +43,7 @@
 %	word 6		<string name of type>
 %			e.g. "int" for `int', "list" for `list(T)',
 %			"map" for `map(K,V)'
+%	word 7		<string name of module>
 %
 % The other cell is the new type_info structure, laid out like this:
 %
@@ -128,6 +129,7 @@
 %			'__Compare__'<list/1>,
 %			<base_type_layout for list/1>,
 %			<base_type_functors for list/1>,
+%			"list",
 %			"list"),
 %		TypeInfoT2 = type_info(
 %			BaseTypeInfoT2,
@@ -140,7 +142,8 @@
 %			builtin_compare_int,
 %			<base_type_layout for int/0>,
 %			<base_type_functors for int/0>,
-%			"int"),
+%			"int",
+%			"mercury_builtin"),
 %		r(TypeInfoT3, 0).
 %
 % Note that base_type_infos are actually generated as references to a
Index: library/io.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/io.m,v
retrieving revision 1.132
diff -u -r1.132 io.m
--- io.m	1997/07/27 15:06:50	1.132
+++ io.m	1997/07/29 09:22:22
@@ -1373,10 +1373,8 @@
 		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))) = "array" } ->
-		%
-		% XXX shouldn't type names be module-qualified?
-		%     shouldn't that be "array:array"?
+	; { type_ctor_name(type_ctor(univ_type(Univ))) = "array" },
+	  { type_ctor_module_name(type_ctor(univ_type(Univ))) = "array" } ->
 		%
 		% Note that we can't use univ_to_type above, because we
 		% want to match on a non-ground type `array(T)'
Index: library/mercury_builtin.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/mercury_builtin.m,v
retrieving revision 1.80
diff -u -r1.80 mercury_builtin.m
--- mercury_builtin.m	1997/07/27 15:06:56	1.80
+++ mercury_builtin.m	1997/07/29 08:30:36
@@ -437,6 +437,7 @@
 	const Word *f5;
 	const Word *f6;
 	const Word *f7;
+	const Word *f8;
 #endif
 } mercury_data___base_type_info_int_0 = {
 	((Integer) 0),
@@ -446,7 +447,8 @@
 #ifdef  USE_TYPE_LAYOUT
 	(const Word *) & mercury_data___base_type_layout_int_0,
 	(const Word *) & mercury_data___base_type_functors_int_0,
-	(const Word *) string_const(""int"", 3)
+	(const Word *) string_const(""int"", 3),
+	(const Word *) string_const(""mercury_builtin"", 15)
 #endif
 };
 
@@ -465,6 +467,7 @@
 	const Word *f5;
 	const Word *f6;
 	const Word *f7;
+	const Word *f8;
 #endif
 } mercury_data___base_type_info_character_0 = {
 	((Integer) 0),
@@ -474,7 +477,8 @@
 #ifdef  USE_TYPE_LAYOUT
 	(const Word *) & mercury_data___base_type_layout_character_0,
 	(const Word *) & mercury_data___base_type_functors_character_0,
-	(const Word *) string_const(""char"", 4)
+	(const Word *) string_const(""char"", 4),
+	(const Word *) string_const(""mercury_builtin"", 15)
 #endif
 };
 
@@ -492,6 +496,7 @@
 	const Word *f5;
 	const Word *f6;
 	const Word *f7;
+	const Word *f8;
 #endif
 } mercury_data___base_type_info_string_0 = {
 	((Integer) 0),
@@ -501,7 +506,8 @@
 #ifdef  USE_TYPE_LAYOUT
 	(const Word *) & mercury_data___base_type_layout_string_0,
 	(const Word *) & mercury_data___base_type_functors_string_0,
-	(const Word *) string_const(""string"", 6)
+	(const Word *) string_const(""string"", 6),
+	(const Word *) string_const(""mercury_builtin"", 15)
 #endif
 };
 
@@ -519,6 +525,7 @@
 	const Word *f5;
 	const Word *f6;
 	const Word *f7;
+	const Word *f8;
 #endif
 } mercury_data___base_type_info_float_0 = {
 	((Integer) 0),
@@ -528,7 +535,8 @@
 #ifdef  USE_TYPE_LAYOUT
 	(const Word *) & mercury_data___base_type_layout_float_0,
 	(const Word *) & mercury_data___base_type_functors_float_0,
-	(const Word *) string_const(""float"", 5)
+	(const Word *) string_const(""float"", 5),
+	(const Word *) string_const(""mercury_builtin"", 15)
 #endif
 };
 
@@ -544,6 +552,7 @@
 	const Word *f5;
 	const Word *f6;
 	const Word *f7;
+	const Word *f8;
 #endif
 } mercury_data___base_type_info_void_0 = {
 	((Integer) 0),
@@ -553,7 +562,8 @@
 #ifdef  USE_TYPE_LAYOUT
 	(const Word *) & mercury_data___base_type_layout_void_0,
 	(const Word *) & mercury_data___base_type_functors_void_0,
-	(const Word *) string_const(""void"", 4)
+	(const Word *) string_const(""void"", 4),
+	(const Word *) string_const(""mercury_builtin"", 15)
 #endif
 };
 
Index: library/std_util.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/std_util.m,v
retrieving revision 1.99
diff -u -r1.99 std_util.m
--- std_util.m	1997/07/28 05:32:01	1.99
+++ std_util.m	1997/07/29 08:25:18
@@ -207,9 +207,10 @@
 :- mode type_of(unused) = out is det.
 
 	% type_name(Type) returns the name of the specified type
-	% (e.g. type_name(type_of([2,3])) = "list(int)").
+	% (e.g. type_name(type_of([2,3])) = "list:list(int)").
 	% Any equivalence types will be fully expanded.
-	% XXX we should think about what happens with module qualifiers...
+	% Builtin types (those defined in mercury_builtin.m) will
+	% not have a module qualifier.
 	%
 :- func type_name(type_info) = string.
 
@@ -248,23 +249,29 @@
 	% type_ctor_name(TypeCtor) returns the name of specified
 	% type constructor.
 	% (e.g. type_ctor_name(type_ctor(type_of([2,3]))) = "list").
-	% XXX we should think about what happens with module qualifiers...
 	%
 :- func type_ctor_name(type_ctor_info) = string.
 
+	% type_ctor_module_name(TypeCtor) returns the module name of specified
+	% type constructor.
+	% (e.g. type_ctor_module_name(type_ctor(type_of(2))) =
+	% 		"mercury_builtin").
+	%
+:- func type_ctor_module_name(type_ctor_info) = string.
+
 	% type_ctor_arity(TypeCtor) returns the arity of specified
 	% type constructor.
 	% (e.g. type_ctor_arity(type_ctor(type_of([2,3]))) = 1).
 	%
 :- func type_ctor_arity(type_ctor_info) = int.
 
-	% type_ctor_name_and_arity(TypeCtor, Name, Arity) :-
+	% type_ctor_name_and_arity(TypeCtor, ModuleName, TypeName, Arity) :-
 	%	Name = type_ctor_name(TypeCtor),
+	%	ModuleName = type_ctor_module_name(TypeCtor),
 	%	Arity = type_ctor_arity(TypeCtor).
-	% XXX we should think about what happens with module qualifiers...
 	%
-:- pred type_ctor_name_and_arity(type_ctor_info, string, int).
-:- mode type_ctor_name_and_arity(in, out, out) is det.
+:- pred type_ctor_name_and_arity(type_ctor_info, string, string, int).
+:- mode type_ctor_name_and_arity(in, out, out, out) is det.
 
 	% make_type(TypeCtor, TypeArgs) = Type:
 	%	True iff `Type' is a type constructed by applying
@@ -1192,11 +1199,15 @@
 
 type_name(Type) = TypeName :-
 	type_ctor_and_args(Type, TypeCtor, ArgTypes),
-	type_ctor_name_and_arity(TypeCtor, Name, Arity),
+	type_ctor_name_and_arity(TypeCtor, ModuleName, Name, Arity),
 	( Arity = 0 ->
-		TypeName = Name
+		UnqualifiedTypeName = Name
 	;
-		( Name = "func" -> IsFunc = yes ; IsFunc = no ),
+		( ModuleName = "mercury_builtin", Name = "func" -> 
+			IsFunc = yes 
+		 ; 
+		 	IsFunc = no 
+		),
 		(
 			IsFunc = yes,
 			ArgTypes = [FuncRetType]
@@ -1204,12 +1215,18 @@
 			FuncRetTypeName = type_name(FuncRetType),
 			string__append_list(
 				["((func) = ", FuncRetTypeName, ")"],
-				TypeName)
+				UnqualifiedTypeName)
 		;
 			type_arg_names(ArgTypes, IsFunc, ArgTypeNames),
 			string__append_list([Name, "(" | ArgTypeNames], 
-				TypeName)
+				UnqualifiedTypeName)
 		)
+	),
+	( ModuleName = "mercury_builtin" ->
+		TypeName = UnqualifiedTypeName
+	;
+		string__append_list([ModuleName, ":", 
+			UnqualifiedTypeName], TypeName)
 	).
 
 :- pred type_arg_names(list(type_info), bool, list(string)).
@@ -1232,10 +1249,13 @@
 	type_ctor_and_args(Type, _TypeCtor, ArgTypes).
 
 type_ctor_name(TypeCtor) = Name :-
-	type_ctor_name_and_arity(TypeCtor, Name, _Arity).
+	type_ctor_name_and_arity(TypeCtor, _ModuleName, Name, _Arity).
+
+type_ctor_module_name(TypeCtor) = ModuleName :-
+	type_ctor_name_and_arity(TypeCtor, ModuleName, _Name, _Arity).
 
 type_ctor_arity(TypeCtor) = Arity :-
-	type_ctor_name_and_arity(TypeCtor, _Name, Arity).
+	type_ctor_name_and_arity(TypeCtor, _ModuleName, _Name, Arity).
 
 det_make_type(TypeCtor, ArgTypes) = Type :-
 	( make_type(TypeCtor, ArgTypes) = NewType ->
@@ -1396,18 +1416,23 @@
 }
 ").
 
-:- pragma c_code(type_ctor_name_and_arity(TypeCtor::in,
-	TypeCtorName::out, TypeCtorArity::out), will_not_call_mercury, "
+:- pragma c_code(type_ctor_name_and_arity(TypeCtor::in, 
+		TypeCtorModuleName::out, TypeCtorName::out, 
+		TypeCtorArity::out), will_not_call_mercury, "
 {
 	Word *type_ctor = (Word *) TypeCtor;
 
 	if (MR_TYPECTOR_IS_HIGHER_ORDER(type_ctor)) {
 		TypeCtorName = (String) (Word) 
 			MR_TYPECTOR_GET_HOT_NAME(type_ctor);
+		TypeCtorModuleName = (String) (Word) 
+			MR_TYPECTOR_GET_HOT_MODULE_NAME(type_ctor);
 		TypeCtorArity = MR_TYPECTOR_GET_HOT_ARITY(type_ctor);
 	} else {
 		TypeCtorName = MR_BASE_TYPEINFO_GET_TYPE_NAME(type_ctor);
 		TypeCtorArity = MR_BASE_TYPEINFO_GET_TYPE_ARITY(type_ctor);
+		TypeCtorModuleName = 
+			MR_BASE_TYPEINFO_GET_TYPE_MODULE_NAME(type_ctor);
 	}
 }
 ").
Index: library/term.m
===================================================================
RCS file: /home/staff/zs/imp/mercury/library/term.m,v
retrieving revision 1.76
diff -u -r1.76 term.m
--- term.m	1997/07/27 15:07:23	1.76
+++ term.m	1997/07/29 09:06:27
@@ -332,8 +332,9 @@
 	(
 		type_ctor_and_args(Type, TypeCtor, TypeArgs),
 		term__term_to_univ_special_case(
-			type_ctor_name(TypeCtor), TypeArgs,
-			Term, Type, Context, SpecialCaseResult)
+			type_ctor_module_name(TypeCtor),
+			type_ctor_name(TypeCtor), 
+			TypeArgs, Term, Type, Context, SpecialCaseResult)
 	->
 		Result = SpecialCaseResult
 	;
@@ -361,24 +362,29 @@
 		Result = error(type_error(Term, Type, TermContext, RevContext))
 	).
 
-:- pred term__term_to_univ_special_case(string::in, list(type_info)::in,
+:- pred term__term_to_univ_special_case(string::in, string::in, 
+		list(type_info)::in, 
 		term::in(bound(term__functor(ground, ground, ground))),
 		type_info::in, term_to_type_context::in,
 		term_to_type_result(univ)::out) is semidet.
-term__term_to_univ_special_case("character", [], Term, _, _, ok(Univ)) :-
+term__term_to_univ_special_case("mercury_builtin", "character", [],
+		Term, _, _, ok(Univ)) :-
 	Term = term__functor(term__atom(FunctorName), [], _),
 	string__first_char(FunctorName, Char, ""),
 	type_to_univ(Char, Univ).
-term__term_to_univ_special_case("int", [], Term, _, _, ok(Univ)) :-
+term__term_to_univ_special_case("mercury_builtin", "int", [],
+		Term, _, _, ok(Univ)) :-
 	Term = term__functor(term__integer(Int), [], _),
 	type_to_univ(Int, Univ).
-term__term_to_univ_special_case("string", [], Term, _, _, ok(Univ)) :-
+term__term_to_univ_special_case("mercury_builtin", "string", [],
+		Term, _, _, ok(Univ)) :-
 	Term = term__functor(term__string(String), [], _),
 	type_to_univ(String, Univ).
-term__term_to_univ_special_case("float", [], Term, _, _, ok(Univ)) :-
+term__term_to_univ_special_case("mercury_builtin", "float", [],
+		Term, _, _, ok(Univ)) :-
 	Term = term__functor(term__float(Float), [], _),
 	type_to_univ(Float, Univ).
-term__term_to_univ_special_case("array", [ElemType], Term, _Type,
+term__term_to_univ_special_case("array", "array", [ElemType], Term, _Type,
 		PrevContext, Result) :-
 	%
 	% arrays are represented as terms of the form
@@ -419,15 +425,16 @@
 		ArgResult = error(Error),
 		Result = error(Error)
 	).
-term__term_to_univ_special_case("c_pointer", _, _, _, _, _) :-
+term__term_to_univ_special_case("mercury_builtin", "c_pointer", _, _, _, 
+		_, _) :-
 	fail.
-term__term_to_univ_special_case("univ", _, _, _, _, _) :-
+term__term_to_univ_special_case("std_util", "univ", _, _, _, _, _) :-
 	% Implementing this properly would require keeping a
 	% global table mapping from type names to type_infos
 	% for all of the types in the program...
 	% so for the moment, we don't allow it.
 	fail.
-term__term_to_univ_special_case("type_info", _, _, _, _, _) :-
+term__term_to_univ_special_case("std_util", "type_info", _, _, _, _, _) :-
 	% ditto
 	fail.
 
@@ -549,8 +556,7 @@
 
 %-----------------------------------------------------------------------------%
 
-term__type_to_term(Val, Term) :-
-	type_to_univ(Val, Univ),
+term__type_to_term(Val, Term) :- type_to_univ(Val, Univ),
 	term__univ_to_term(Univ, Term).
 
 term__univ_to_term(Univ, Term) :-
@@ -561,8 +567,9 @@
 		(
 			type_ctor_and_args(Type, TypeCtor, TypeArgs),
 			TypeName = type_ctor_name(TypeCtor),
-			term__univ_to_term_special_case(TypeName, TypeArgs,
-				Univ, Context, SpecialCaseTerm)
+			ModuleName = type_ctor_module_name(TypeCtor),
+			term__univ_to_term_special_case(ModuleName, TypeName,
+				TypeArgs, Univ, Context, SpecialCaseTerm)
 		->
 			Term = SpecialCaseTerm
 		;
@@ -580,27 +587,28 @@
 			Context)
 	).
 
-:- pred term__univ_to_term_special_case(string::in, list(type_info)::in,
-		univ::in, term__context::in, term::out) is semidet.
+:- pred term__univ_to_term_special_case(string::in, string::in, 
+		list(type_info)::in, univ::in, term__context::in,
+		term::out) is semidet.
 
-term__univ_to_term_special_case("int", [], Univ, Context,
+term__univ_to_term_special_case("mercury_builtin", "int", [], Univ, Context,
 		term__functor(term__integer(Int), [], Context)) :-
 	det_univ_to_type(Univ, Int).
-term__univ_to_term_special_case("float", [], Univ, Context,
+term__univ_to_term_special_case("mercury_builtin", "float", [], Univ, Context,
 		term__functor(term__float(Float), [], Context)) :-
 	det_univ_to_type(Univ, Float).
-term__univ_to_term_special_case("character", [], Univ, Context,
-		term__functor(term__atom(CharName), [], Context)) :-
+term__univ_to_term_special_case("mercury_builtin", "character", [], Univ, 
+		Context, term__functor(term__atom(CharName), [], Context)) :-
 	det_univ_to_type(Univ, Character),
 	string__char_to_string(Character, CharName).
-term__univ_to_term_special_case("string", [], Univ, Context,
+term__univ_to_term_special_case("mercury_builtin", "string", [], Univ, Context,
 		term__functor(term__string(String), [], Context)) :-
 	det_univ_to_type(Univ, String).
-term__univ_to_term_special_case("type_info", [], Univ, Context,
+term__univ_to_term_special_case("std_util", "type_info", [], Univ, Context,
 		term__functor(term__atom("type_info"), [Term], Context)) :-
 	det_univ_to_type(Univ, TypeInfo),
 	type_info_to_term(Context, TypeInfo, Term).
-term__univ_to_term_special_case("univ", [], Univ, Context, Term) :-
+term__univ_to_term_special_case("std_util", "univ", [], Univ, Context, Term) :-
 	Term = term__functor(term__atom("univ"),
 			% XXX what operator should we use for type
 			% qualification?
@@ -618,7 +626,8 @@
 	type_info_to_term(Context, univ_type(UnivValue), TypeTerm),
 	term__univ_to_term(UnivValue, ValueTerm).
 
-term__univ_to_term_special_case("array", [ElemType], Univ, Context, Term) :-
+term__univ_to_term_special_case("array", "array", [ElemType], Univ, Context, 
+		Term) :-
 	Term = term__functor(term__atom("array"), [ArgsTerm], Context),
 	ListTypeCtor = type_ctor(type_of([0])),
 	ListType = det_make_type(ListTypeCtor, [ElemType]),
@@ -650,8 +659,18 @@
 type_info_to_term(Context, TypeInfo, Term) :-
 	type_ctor_and_args(TypeInfo, TypeCtor, ArgTypes),
 	TypeName = type_ctor_name(TypeCtor),
+	ModuleName = type_ctor_name(TypeCtor),
 	list__map(type_info_to_term(Context), ArgTypes, ArgTerms),
-	Term = term__functor(term__atom(TypeName), ArgTerms, Context).
+
+	( ModuleName = "mercury_builtin" ->
+		Term = term__functor(term__atom(TypeName), ArgTerms, Context)
+	;
+		Term = term__functor(term__atom(":"), % TYPE_QUAL_OP
+			[term__functor(term__atom(ModuleName), [], Context),
+			 term__functor(term__atom(TypeName), 
+			 	ArgTerms, Context)], Context)
+	).
+		
 
 :- pred require_equal(T::in, T::in) is det.
 require_equal(X, Y) :-
Index: runtime/type_info.h
===================================================================
RCS file: /home/staff/zs/imp/mercury/runtime/type_info.h,v
retrieving revision 1.29
diff -u -r1.29 type_info.h
--- type_info.h	1997/07/27 15:08:50	1.29
+++ type_info.h	1997/07/29 06:08:54
@@ -49,6 +49,7 @@
 #define OFFSET_FOR_BASE_TYPE_LAYOUT 4
 #define OFFSET_FOR_BASE_TYPE_FUNCTORS 5
 #define OFFSET_FOR_TYPE_NAME 6
+#define OFFSET_FOR_TYPE_MODULE_NAME 7
 
 /*
 ** Define offsets of fields in the type_info structure.
@@ -296,6 +297,8 @@
 	((Integer) (T) / 2 )
 #define MR_TYPECTOR_GET_HOT_NAME(T)				\
 	((ConstString) ( ( ((Integer) (T)) % 2 ) ? "func" : "pred" ))
+#define MR_TYPECTOR_GET_HOT_MODULE_NAME(T)				\
+	((ConstString) "mercury_builtin")
 #define MR_TYPECTOR_GET_HOT_BASE_TYPE_INFO(T)			\
 	((Word) ( ( ((Integer) (T)) % 2 ) ?		\
 		(const Word *) &mercury_data___base_type_info_func_0 :	\
@@ -706,6 +709,9 @@
 
 #define MR_BASE_TYPEINFO_GET_TYPE_NAME(BaseTypeInfo)			\
 		(((String *) (BaseTypeInfo))[OFFSET_FOR_TYPE_NAME])
+
+#define MR_BASE_TYPEINFO_GET_TYPE_MODULE_NAME(BaseTypeInfo)		\
+		(((String *) (BaseTypeInfo))[OFFSET_FOR_TYPE_MODULE_NAME])
 
 /*---------------------------------------------------------------------------*/
 
Index: tests/hard_coded/higher_order_type_manip.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/higher_order_type_manip.exp,v
retrieving revision 1.1
diff -u -r1.1 higher_order_type_manip.exp
--- higher_order_type_manip.exp	1997/07/16 15:56:59	1.1
+++ higher_order_type_manip.exp	1997/07/29 08:48:36
@@ -1,6 +1,6 @@
-func(type_info) = string
-pred(type_info, c_pointer, list(type_info))
+func(std_util:type_info) = string
+pred(std_util:type_info, c_pointer, list:list(std_util:type_info))
 int
-container(list(int))
-container(pred(state, state))
+higher_order_type_manip:container(list:list(int))
+higher_order_type_manip:container(pred(io:state, io:state))
 func(int) = int
Index: tests/hard_coded/write.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/write.exp,v
retrieving revision 1.6
diff -u -r1.6 write.exp
--- write.exp	1997/07/25 05:16:31	1.6
+++ write.exp	1997/07/29 07:42:34
@@ -34,7 +34,7 @@
 2.23954899000000e+23
 -65
 4
-univ(["hi! I\'m a univ!"] : list(string))
+univ(["hi! I\'m a univ!"] : list:list(string))
 '<<predicate>>'
 
 TESTING OTHER TYPES
Index: tests/hard_coded/write_reg1.exp
===================================================================
RCS file: /home/staff/zs/imp/tests/hard_coded/write_reg1.exp,v
retrieving revision 1.3
diff -u -r1.3 write_reg1.exp
--- write_reg1.exp	1997/05/26 07:57:56	1.3
+++ write_reg1.exp	1997/07/29 07:42:53
@@ -27,7 +27,7 @@
 2.23954899000000e+23
 -65
 4
-univ(["hi! I\'m a univ!"] : list(string))
+univ(["hi! I\'m a univ!"] : list:list(string))
 '<<predicate>>'
 
 TESTING OTHER TYPES

-- 
       Tyson Dowd           # 4.4: People keep saying the behavior is undefined,
                            # but I just tried it on an ANSI-conforming compiler
     trd at cs.mu.oz.au        # and got the results I expected.
http://www.cs.mu.oz.au/~trd # A: They were wrong. Flame them mercilessly. C-IAQ



More information about the developers mailing list