[m-dev.] for review: MLDS back-end miscellaneous changes

Fergus Henderson fjh at cs.mu.OZ.AU
Fri Apr 21 00:22:15 AEST 2000


Estimated hours taken: 12

More work on the MLDS back-end.

compiler/rtti_to_mlds.m:
	Pass the module_name of the current module down, so that we
	can use it for the module qualifier when generating references
	to type_info and higher_order_type_info rtti constants.
	Ensure that we output properly nested initializers for the
	union fields of type_ctor_infos.

compiler/mercury_compile.m:
	Pass the module_name to rtti_to_mlds.m.

compiler/mlds.m:
	Delete the obsolete type_ctor/3 data_name; this has been replaced by
	the rtti/2 data_name.  Also delete mlds__base_type_info_type, and
	instead add mlds__pseudo_type_info_type.

compiler/mlds_to_c.m:
compiler/ml_unify_gen.m:
	Handle the changes to mlds.m.

runtime/mercury.h:
	Delete the obsolete MR_BaseTypeInfo type; we now use the
	MR_TypeCtorInfo_Struct type from mercury_type_info.h instead.
	Add typedefs for the various pointer and array types used
	for RTTI data structures; the MLDS->C back-end generates
	references to these typedefs.

runtime/mercury_type_info.h:
	Change the definitions of the MR_TypeCtorRep and MR_SecTag_Locn
	enumerations, so that they now define two names for each
	enumeration constant, one prefixed with
	`mercury__private_builtin__'; the MLDS->C back-end 
	generates references to these prefixed enumeration constants.
	(Doing it this way avoids the need to hard-code representations
	of these enumeration constants into the MLDS types.)

compiler/mlds_to_c.m:
compiler/ml_unify_gen.m:
compiler/rtti_to_mlds.m:
library/exception.m:
	Add some casts from `MR_Box' to `Word' or vice versa, so as to
	avoid assuming that `MR_Box' is the same type as `Word'.

compiler/mlds_to_c.m:
	Change mlds_output_data_addr so that it handles constants
	with array types (specifically some of the RTTI constants),
	i.e. don't output `&' for those.

library/benchmarking.m:
library/private_builtin.m:
runtime/mercury.h:
	Add some missing #includes.

library/builtin.m:
	Add `#ifndef MR_HIGHLEVEL_CODE' around some code that is
	specific to the low-level (LLDS) back-end.

Workspace: /home/pgrad/fjh/ws/hg
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.156
diff -u -d -r1.156 mercury_compile.m
--- compiler/mercury_compile.m	2000/04/18 16:41:37	1.156
+++ compiler/mercury_compile.m	2000/04/20 10:58:21
@@ -2269,8 +2269,8 @@
 
 mercury_compile__mlds_gen_rtti_data(HLDS, MLDS0, MLDS) :-
 	type_ctor_info__generate_rtti(HLDS, TypeCtorRtti),
-	TypeCtorDefns = rtti_data_list_to_mlds(TypeCtorRtti),
 	MLDS0 = mlds(ModuleName, ForeignCode, Imports, Defns0),
+	TypeCtorDefns = rtti_data_list_to_mlds(ModuleName, TypeCtorRtti),
 	list__append(TypeCtorDefns, Defns0, Defns),
 	MLDS = mlds(ModuleName, ForeignCode, Imports, Defns).
 
Index: compiler/mlds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds.m,v
retrieving revision 1.20
diff -u -d -r1.20 mlds.m
--- compiler/mlds.m	2000/04/18 17:57:17	1.20
+++ compiler/mlds.m	2000/04/19 08:28:54
@@ -487,6 +487,9 @@
 	;	mlds__ptr_type(mlds__type)
 
 		% Function types.
+		% For the C back-end, these are mapped to function
+		% pointer types, since C doesn't have first-class
+		% function types.
 	;	mlds__func_type(mlds__func_params)
 
 		% A generic type (e.g. `Word') that can hold any Mercury value.
@@ -502,7 +505,7 @@
 		% closures for higher-order code.
 	;	mlds__generic_env_ptr_type
 
-	;	mlds__base_type_info_type
+	;	mlds__pseudo_type_info_type
 	
 	;	mlds__rtti_type(rtti_name).
 
@@ -1012,12 +1015,9 @@
 			% global constants.  These are called "common"
 			% because they may be common sub-expressions.
 	%
-	% Stuff for handling polymorphism and type classes,
-	% and RTTI.
+	% Stuff for handling polymorphism/RTTI and type classes.
 	%
 	;	rtti(rtti_type_id, rtti_name)
-	;	type_ctor(mlds__base_data, string, arity)
-			% base_data, type name, type arity
 	;	base_typeclass_info(hlds_data__class_id, string)
 			% class name & class arity, names and arities of the
 			% types
Index: compiler/mlds_to_c.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_c.m,v
retrieving revision 1.25
diff -u -d -r1.25 mlds_to_c.m
--- compiler/mlds_to_c.m	2000/04/19 07:31:51	1.25
+++ compiler/mlds_to_c.m	2000/04/20 13:33:34
@@ -758,14 +758,6 @@
 mlds_output_data_name(rtti(RttiTypeId, RttiName)) -->
 	{ rtti__addr_to_string(RttiTypeId, RttiName, RttiAddrName) },
 	io__write_string(RttiAddrName).
-mlds_output_data_name(type_ctor(BaseData, Name, Arity)) -->
-	{ llds_out__name_mangle(Name, MangledName) },
-	io__write_string("base_type_"),
-	io__write(BaseData),
-	io__write_string("_"),
-	io__write_string(MangledName),
-	io__write_string("_"),
-	io__write_int(Arity).
 mlds_output_data_name(base_typeclass_info(_ClassId, _InstanceId)) -->
 	{ error("mlds_to_c.m: NYI: basetypeclass_info") }.
 mlds_output_data_name(module_layout) -->
@@ -823,8 +815,8 @@
 	io__write_string("MR_Box").
 mlds_output_type(mlds__generic_env_ptr_type) -->
 	io__write_string("void *").
-mlds_output_type(mlds__base_type_info_type) -->
-	io__write_string("MR_BaseTypeInfo").
+mlds_output_type(mlds__pseudo_type_info_type) -->
+	io__write_string("MR_PseudoTypeInfo").
 mlds_output_type(mlds__cont_type) -->
 	globals__io_lookup_bool_option(gcc_nested_functions, GCC_NestedFuncs),
 	( { GCC_NestedFuncs = yes } ->
@@ -1481,7 +1473,7 @@
 	mlds_output_lval(Target),
 	io__write_string(", "),
 	io__write_int(ArgNum),
-	io__write_string(") = "),
+	io__write_string(") = (Word) "),
 	mlds_output_boxed_rval(ArgType, Arg),
 	io__write_string(";\n"),
 	mlds_output_init_args(Args, ArgTypes, Context,
@@ -1496,6 +1488,11 @@
 :- mode mlds_output_lval(in, di, uo) is det.
 
 mlds_output_lval(field(MaybeTag, Rval, offset(OffsetRval), _, _)) -->
+	% XXX this generated code is ugly;
+	% it would be nicer to use a different macro
+	% than MR_field(), one which had type `MR_Box'
+	% rather than `Word'.
+	io__write_string("(* (MR_Box *) &"),
 	( { MaybeTag = yes(Tag) } ->
 		io__write_string("MR_field("),
 		mlds_output_tag(Tag),
@@ -1503,10 +1500,11 @@
 	;
 		io__write_string("MR_mask_field(")
 	),
+	io__write_string("(Word) "),
 	mlds_output_rval(Rval),
 	io__write_string(", "),
 	mlds_output_rval(OffsetRval),
-	io__write_string(")").
+	io__write_string("))").
 mlds_output_lval(field(MaybeTag, PtrRval, named_field(FieldId), _, _)) -->
 	( { MaybeTag = yes(0) } ->
 		( { PtrRval = mem_addr(Lval) } ->
@@ -1839,13 +1837,44 @@
 :- mode mlds_output_data_addr(in, di, uo) is det.
 
 mlds_output_data_addr(data_addr(ModuleName, DataName)) -->
-	% XXX the cast to (Word) is needed for base_type_infos,
-	% but it might not be right for other data_addr values.
-	io__write_string("((Word) &"),
+	(
+		% if its an array type, then we just use the name,
+		% otherwise we must prefix the name with `&'.
+		{ DataName = rtti(_, RttiName) },
+		{ rtti_name_has_array_type(RttiName) = yes }
+	->
+		mlds_output_data_var_name(ModuleName, DataName)
+	;
+		io__write_string("(&"),
+		mlds_output_data_var_name(ModuleName, DataName),
+		io__write_string(")")
+	).
+
+:- func rtti_name_has_array_type(rtti_name) = bool.
+rtti_name_has_array_type(exist_locns(_))		= yes.
+rtti_name_has_array_type(exist_info(_))			= no.
+rtti_name_has_array_type(field_names(_))		= yes.
+rtti_name_has_array_type(field_types(_))		= yes.
+rtti_name_has_array_type(enum_functor_desc(_))		= no.
+rtti_name_has_array_type(notag_functor_desc)		= no.
+rtti_name_has_array_type(du_functor_desc(_))		= no.
+rtti_name_has_array_type(enum_name_ordered_table)	= yes.
+rtti_name_has_array_type(enum_value_ordered_table)	= yes.
+rtti_name_has_array_type(du_name_ordered_table)		= yes.
+rtti_name_has_array_type(du_stag_ordered_table(_))	= yes.
+rtti_name_has_array_type(du_ptag_ordered_table)		= yes.
+rtti_name_has_array_type(type_ctor_info)		= no.
+rtti_name_has_array_type(pseudo_type_info(_))		= no.
+rtti_name_has_array_type(type_hashcons_pointer)		= no.
+
+:- pred mlds_output_data_var_name(mlds_module_name, mlds__data_name,
+		io__state, io__state).
+:- mode mlds_output_data_var_name(in, in, di, uo) is det.
+
+mlds_output_data_var_name(ModuleName, DataName) -->
 	mlds_output_module_name(mlds_module_name_to_sym_name(ModuleName)),
 	io__write_string("__"),
-	mlds_output_data_name(DataName),
-	io__write_string(")").
+	mlds_output_data_name(DataName).
 
 %-----------------------------------------------------------------------------%
 %
Index: compiler/ml_unify_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ml_unify_gen.m,v
retrieving revision 1.4
diff -u -d -r1.4 ml_unify_gen.m
--- compiler/ml_unify_gen.m	2000/03/30 05:41:50	1.4
+++ compiler/ml_unify_gen.m	2000/04/20 10:07:26
@@ -54,6 +54,7 @@
 
 :- import_module hlds_pred, hlds_module, hlds_out, builtin_ops.
 :- import_module ml_call_gen, prog_util, type_util, mode_util.
+:- import_module rtti.
 :- import_module code_util. % XXX needed for `code_util__cons_id_to_tag'.
 
 :- import_module int, string, list, require, std_util, term, varset.
@@ -245,10 +246,14 @@
 		ModuleName = ModuleName0
 	},
 	{ MLDS_Module = mercury_module_name_to_mlds(ModuleName) },
+	{ RttiTypeId = rtti_type_id(ModuleName, TypeName, TypeArity) },
 	{ DataAddr = data_addr(MLDS_Module,
-		type_ctor(info, TypeName, TypeArity)) },
+		rtti(RttiTypeId, type_ctor_info)) },
+	ml_variable_type(Var, VarType),
 	{ MLDS_Statement = ml_gen_assign(VarLval, 
-		const(data_addr_const(DataAddr)), Context) }.
+		unop(cast(mercury_type(VarType)),
+			const(data_addr_const(DataAddr))),
+		Context) }.
 ml_gen_construct_rep(base_typeclass_info_constant(ModuleName, ClassId,
 			Instance), _ConsId, Var, Args, _ArgModes, Context,
 		[], [MLDS_Statement]) -->
Index: compiler/rtti_to_mlds.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/rtti_to_mlds.m,v
retrieving revision 1.1
diff -u -d -r1.1 rtti_to_mlds.m
--- compiler/rtti_to_mlds.m	2000/04/18 16:41:55	1.1
+++ compiler/rtti_to_mlds.m	2000/04/20 12:36:06
@@ -16,11 +16,11 @@
 
 :- module rtti_to_mlds.
 :- interface.
-:- import_module rtti, mlds.
+:- import_module rtti, mlds, prog_data.
 :- import_module list.
 
 	% return a list of MLDS definitions for the given rtti_data list.
-:- func rtti_data_list_to_mlds(list(rtti_data)) = mlds__defns.
+:- func rtti_data_list_to_mlds(module_name, list(rtti_data)) = mlds__defns.
 
 	% return a name, consisting only of alphabetic characters,
 	% that would be suitable for the type name for the type
@@ -31,12 +31,12 @@
 :- import_module pseudo_type_info, ml_code_util, prog_util, prog_out.
 :- import_module bool, list, std_util, string, term, require.
 
-rtti_data_list_to_mlds(RttiDatas) =
-	list__condense(list__map(rtti_data_to_mlds, RttiDatas)).
+rtti_data_list_to_mlds(ModuleName, RttiDatas) =
+	list__condense(list__map(rtti_data_to_mlds(ModuleName), RttiDatas)).
 
 	% return a list of MLDS definitions for the given rtti_data.
-:- func rtti_data_to_mlds(rtti_data) = mlds__defns.
-rtti_data_to_mlds(RttiData) = MLDS_Defns :-
+:- func rtti_data_to_mlds(module_name, rtti_data) = mlds__defns.
+rtti_data_to_mlds(ModuleName, RttiData) = MLDS_Defns :-
 	( RttiData = pseudo_type_info(type_var(_)) ->
 		% These just get represented as integers,
 		% so we don't need to define them.
@@ -68,7 +68,7 @@
 		% i.e. the type and the initializer
 		%
 		MLDS_Type = rtti_type(RttiName),
-		Initializer = gen_init_rtti_data_defn(RttiData),
+		Initializer = gen_init_rtti_data_defn(RttiData, ModuleName),
 		DefnBody = mlds__data(MLDS_Type, Initializer),
 
 		%
@@ -98,36 +98,42 @@
 
 %-----------------------------------------------------------------------------%
 
-	% Return an MLDS initializer for the given RTTI definition.
-:- func gen_init_rtti_data_defn(rtti_data) = mlds__initializer.
+	% Return an MLDS initializer for the given RTTI definition
+	% occurring in the given module.
+:- func gen_init_rtti_data_defn(rtti_data, module_name) = mlds__initializer.
 
-gen_init_rtti_data_defn(exist_locns(_RttiTypeId, _Ordinal, Locns)) =
+gen_init_rtti_data_defn(exist_locns(_RttiTypeId, _Ordinal, Locns), _) =
 	gen_init_array(gen_init_exist_locn, Locns).
 gen_init_rtti_data_defn(exist_info(RttiTypeId, _Ordinal, Plain, InTci, Tci,
-		Locns)) =
+		Locns), ModuleName) =
 	init_struct([
 		gen_init_int(Plain),
 		gen_init_int(InTci),
 		gen_init_int(Tci),
-		gen_init_rtti_name(RttiTypeId, Locns)
+		gen_init_rtti_name(ModuleName, RttiTypeId, Locns)
 	]).
-gen_init_rtti_data_defn(field_names(_RttiTypeId, _Ordinal, MaybeNames)) =
+gen_init_rtti_data_defn(field_names(_RttiTypeId, _Ordinal, MaybeNames), _) =
 	gen_init_array(gen_init_maybe(gen_init_string), MaybeNames).
-gen_init_rtti_data_defn(field_types(_RttiTypeId, _Ordinal, Types)) =
-	gen_init_array(gen_init_cast_rtti_data, Types).
-gen_init_rtti_data_defn(enum_functor_desc(_RttiTypeId, FunctorName, Ordinal)) =
+gen_init_rtti_data_defn(field_types(_RttiTypeId, _Ordinal, Types),
+		ModuleName) =
+	gen_init_array(gen_init_cast_rtti_data(mlds__pseudo_type_info_type,
+		ModuleName), Types).
+gen_init_rtti_data_defn(enum_functor_desc(_RttiTypeId, FunctorName, Ordinal),
+		_ModuleName) =
 	init_struct([
 		gen_init_string(FunctorName),
 		gen_init_int(Ordinal)
 	]).
-gen_init_rtti_data_defn(notag_functor_desc(_RttiTypeId, FunctorName, ArgType)) =
+gen_init_rtti_data_defn(notag_functor_desc(_RttiTypeId, FunctorName, ArgType),
+		ModuleName) =
 	init_struct([
 		gen_init_string(FunctorName),
-		gen_init_cast_rtti_data(ArgType)
+		gen_init_cast_rtti_data(mlds__pseudo_type_info_type,
+			ModuleName, ArgType)
 	]).
 gen_init_rtti_data_defn(du_functor_desc(RttiTypeId, FunctorName, Ptag, Stag,
 		Locn, Ordinal, Arity, ContainsVarBitVector, ArgTypes,
-		MaybeNames, MaybeExist)) =
+		MaybeNames, MaybeExist), ModuleName) =
 	init_struct([
 		gen_init_string(FunctorName),
 		gen_init_int(Arity),
@@ -136,26 +142,34 @@
 		gen_init_int(Ptag),
 		gen_init_int(Stag),
 		gen_init_int(Ordinal),
-		gen_init_rtti_name(RttiTypeId, ArgTypes),
-		gen_init_maybe(gen_init_rtti_name(RttiTypeId), MaybeNames),
-		gen_init_maybe(gen_init_rtti_name(RttiTypeId), MaybeExist)
+		gen_init_rtti_name(ModuleName, RttiTypeId, ArgTypes),
+		gen_init_maybe(gen_init_rtti_name(ModuleName, RttiTypeId),
+			MaybeNames),
+		gen_init_maybe(gen_init_rtti_name(ModuleName, RttiTypeId),
+			MaybeExist)
 	]).
-gen_init_rtti_data_defn(enum_name_ordered_table(RttiTypeId, Functors)) =
-	gen_init_rtti_names_array(RttiTypeId, Functors).
-gen_init_rtti_data_defn(enum_value_ordered_table(RttiTypeId, Functors)) =
-	gen_init_rtti_names_array(RttiTypeId, Functors).
-gen_init_rtti_data_defn(du_name_ordered_table(RttiTypeId, Functors)) =
-	gen_init_rtti_names_array(RttiTypeId, Functors).
-gen_init_rtti_data_defn(du_stag_ordered_table(RttiTypeId, _Ptag, Sharers)) =
-	gen_init_rtti_names_array(RttiTypeId, Sharers).
-gen_init_rtti_data_defn(du_ptag_ordered_table(RttiTypeId, PtagLayouts)) =
-	gen_init_array(gen_init_ptag_layout_defn(RttiTypeId), PtagLayouts).
+gen_init_rtti_data_defn(enum_name_ordered_table(RttiTypeId, Functors),
+		ModuleName) =
+	gen_init_rtti_names_array(ModuleName, RttiTypeId, Functors).
+gen_init_rtti_data_defn(enum_value_ordered_table(RttiTypeId, Functors),
+		ModuleName) =
+	gen_init_rtti_names_array(ModuleName, RttiTypeId, Functors).
+gen_init_rtti_data_defn(du_name_ordered_table(RttiTypeId, Functors),
+		ModuleName) =
+	gen_init_rtti_names_array(ModuleName, RttiTypeId, Functors).
+gen_init_rtti_data_defn(du_stag_ordered_table(RttiTypeId, _Ptag, Sharers),
+		ModuleName) =
+	gen_init_rtti_names_array(ModuleName, RttiTypeId, Sharers).
+gen_init_rtti_data_defn(du_ptag_ordered_table(RttiTypeId, PtagLayouts),
+		ModuleName) =
+	gen_init_array(gen_init_ptag_layout_defn(ModuleName, RttiTypeId),
+		PtagLayouts).
 gen_init_rtti_data_defn(type_ctor_info(RttiTypeId, UnifyProc, CompareProc,
 		CtorRep, SolverProc, InitProc, Version, NumPtags, NumFunctors,
 		FunctorsInfo, LayoutInfo, _MaybeHashCons,
-		_PrettyprinterProc)) = Initializer :-
-	RttiTypeId = rtti_type_id(Module, Type, TypeArity),
-	prog_out__sym_name_to_string(Module, ModuleName),
+		_PrettyprinterProc), ModuleName) = Initializer :-
+	RttiTypeId = rtti_type_id(TypeModule, Type, TypeArity),
+	prog_out__sym_name_to_string(TypeModule, TypeModuleName),
 	Initializer = init_struct([
 		gen_init_int(TypeArity),
 		gen_init_maybe_proc_id(UnifyProc),
@@ -164,11 +178,18 @@
 		gen_init_type_ctor_rep(CtorRep),
 		gen_init_maybe_proc_id(SolverProc),
 		gen_init_maybe_proc_id(InitProc),
-		gen_init_string(ModuleName),
+		gen_init_string(TypeModuleName),
 		gen_init_string(Type),
 		gen_init_int(Version),
-		gen_init_functors_info(FunctorsInfo, RttiTypeId),
-		gen_init_layout_info(LayoutInfo, RttiTypeId),
+		% In the C back-end, these two "structs" are actually unions.
+		% We need to use `init_struct' here so that the initializers
+		% gets inclosed in curly braces.
+		init_struct([
+			gen_init_functors_info(FunctorsInfo, ModuleName, RttiTypeId)
+		]),
+		init_struct([
+			gen_init_layout_info(LayoutInfo, ModuleName, RttiTypeId)
+		]),
 		gen_init_int(NumFunctors),
 		gen_init_int(NumPtags)
 			% These two are commented out while the corresponding
@@ -178,33 +199,42 @@
 		%	MaybeHashCons),
 		% gen_init_maybe_proc_id(PrettyprinterProc)
 	]).
-gen_init_rtti_data_defn(pseudo_type_info(Pseudo)) =
-	gen_init_pseudo_type_info_defn(Pseudo).
-
-:- func gen_init_functors_info(type_ctor_functors_info, rtti_type_id) =
-	mlds__initializer.
+gen_init_rtti_data_defn(pseudo_type_info(Pseudo), ModuleName) =
+	gen_init_pseudo_type_info_defn(Pseudo, ModuleName).
 
-gen_init_functors_info(enum_functors(EnumFunctorsInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, EnumFunctorsInfo).
-gen_init_functors_info(notag_functors(NotagFunctorsInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, NotagFunctorsInfo).
-gen_init_functors_info(du_functors(DuFunctorsInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, DuFunctorsInfo).
-gen_init_functors_info(no_functors, _) =
+:- func gen_init_functors_info(type_ctor_functors_info, module_name,
+		rtti_type_id) = mlds__initializer.
+gen_init_functors_info(enum_functors(EnumFunctorsInfo), ModuleName,
+		RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type,
+		ModuleName, RttiTypeId, EnumFunctorsInfo).
+gen_init_functors_info(notag_functors(NotagFunctorsInfo), ModuleName,
+		RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type,
+		ModuleName, RttiTypeId, NotagFunctorsInfo).
+gen_init_functors_info(du_functors(DuFunctorsInfo), ModuleName,
+		RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type,
+		ModuleName, RttiTypeId, DuFunctorsInfo).
+gen_init_functors_info(no_functors, _, _) =
 	gen_init_null_pointer.
 
-:- func gen_init_layout_info(type_ctor_layout_info, rtti_type_id) =
-	mlds__initializer.
+:- func gen_init_layout_info(type_ctor_layout_info, module_name,
+		rtti_type_id) = mlds__initializer.
 
-gen_init_layout_info(enum_layout(EnumLayoutInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, EnumLayoutInfo).
-gen_init_layout_info(notag_layout(NotagLayoutInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, NotagLayoutInfo).
-gen_init_layout_info(du_layout(DuLayoutInfo), RttiTypeId) =
-	gen_init_cast_rtti_name(RttiTypeId, DuLayoutInfo).
-gen_init_layout_info(equiv_layout(EquivTypeInfo), _RttiTypeId) =
-	gen_init_cast_rtti_data(EquivTypeInfo).
-gen_init_layout_info(no_layout, _RttiTypeId) =
+gen_init_layout_info(enum_layout(EnumLayoutInfo), ModuleName, RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type, ModuleName, RttiTypeId,
+		EnumLayoutInfo).
+gen_init_layout_info(notag_layout(NotagLayoutInfo), ModuleName, RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type, ModuleName, RttiTypeId,
+		NotagLayoutInfo).
+gen_init_layout_info(du_layout(DuLayoutInfo), ModuleName, RttiTypeId) =
+	gen_init_cast_rtti_name(mlds__generic_type, ModuleName, RttiTypeId,
+		DuLayoutInfo).
+gen_init_layout_info(equiv_layout(EquivTypeInfo), ModuleName, _RttiTypeId) =
+	gen_init_cast_rtti_data(mlds__generic_type, ModuleName,
+		EquivTypeInfo).
+gen_init_layout_info(no_layout, _, _) =
 	gen_init_null_pointer.
 
 :- func gen_init_maybe_proc_id(maybe(rtti_proc_label)) = mlds__initializer.
@@ -212,95 +242,141 @@
 gen_init_maybe_proc_id(MaybeProcLabel) =
 	gen_init_maybe(gen_init_proc_id, MaybeProcLabel).
 
-:- func gen_init_pseudo_type_info_defn(pseudo_type_info) = mlds__initializer.
+:- func gen_init_pseudo_type_info_defn(pseudo_type_info, module_name) =
+	mlds__initializer.
 
-gen_init_pseudo_type_info_defn(type_var(_)) = _ :-
+gen_init_pseudo_type_info_defn(type_var(_), _) = _ :-
 	error("gen_init_pseudo_type_info_defn: type_var").
-gen_init_pseudo_type_info_defn(type_ctor_info(_)) = _ :-
+gen_init_pseudo_type_info_defn(type_ctor_info(_), _) = _ :-
 	error("gen_init_pseudo_type_info_defn: type_ctor_info").
-gen_init_pseudo_type_info_defn(type_info(RttiTypeId, ArgTypes)) = Init :-
+gen_init_pseudo_type_info_defn(type_info(RttiTypeId, ArgTypes), ModuleName) =
+		Init :-
 	ArgRttiDatas = list__map(func(P) = pseudo_type_info(P), ArgTypes),
 	Init = init_struct([
-		gen_init_rtti_name(RttiTypeId, type_ctor_info),
-		gen_init_cast_rtti_datas_array(ArgRttiDatas)
+		gen_init_rtti_name(ModuleName, RttiTypeId, type_ctor_info),
+		gen_init_cast_rtti_datas_array(mlds__pseudo_type_info_type,
+			ModuleName, ArgRttiDatas)
 	]).
 gen_init_pseudo_type_info_defn(higher_order_type_info(RttiTypeId,
-		Arity, ArgTypes)) = Init :-
+		Arity, ArgTypes), ModuleName) = Init :-
 	ArgRttiDatas = list__map(func(P) = pseudo_type_info(P), ArgTypes),
 	Init = init_struct([
-		gen_init_rtti_name(RttiTypeId, type_ctor_info),
+		gen_init_rtti_name(ModuleName, RttiTypeId, type_ctor_info),
 		gen_init_int(Arity),
-		gen_init_cast_rtti_datas_array(ArgRttiDatas)
+		gen_init_cast_rtti_datas_array(mlds__pseudo_type_info_type,
+			ModuleName, ArgRttiDatas)
 	]).
 
-:- func gen_init_ptag_layout_defn(rtti_type_id, du_ptag_layout) =
+:- func gen_init_ptag_layout_defn(module_name, rtti_type_id, du_ptag_layout) =
 	mlds__initializer.
 
-gen_init_ptag_layout_defn(RttiTypeId, DuPtagLayout) = Init :-
+gen_init_ptag_layout_defn(ModuleName, RttiTypeId, DuPtagLayout) = Init :-
 	DuPtagLayout = du_ptag_layout(NumSharers, Locn, Descriptors) ,
 	Init = init_struct([
 		gen_init_int(NumSharers),
 		gen_init_sectag_locn(Locn),
-		gen_init_rtti_name(RttiTypeId, Descriptors)
+		gen_init_rtti_name(ModuleName, RttiTypeId, Descriptors)
 	]).
 
 %-----------------------------------------------------------------------------%
 
-:- func gen_init_rtti_names_array(rtti_type_id, list(rtti_name)) =
-	mlds__initializer.
-gen_init_rtti_names_array(RttiTypeId, RttiNames) =
-	gen_init_array(gen_init_rtti_name(RttiTypeId), RttiNames).
+:- func gen_init_rtti_names_array(module_name, rtti_type_id,
+		list(rtti_name)) = mlds__initializer.
+gen_init_rtti_names_array(ModuleName, RttiTypeId, RttiNames) =
+	gen_init_array(gen_init_rtti_name(ModuleName, RttiTypeId), RttiNames).
 
-:- func gen_init_rtti_datas_array(list(rtti_data)) = mlds__initializer.
-gen_init_rtti_datas_array(RttiDatas) =
-	gen_init_array(gen_init_rtti_data, RttiDatas).
+:- func gen_init_rtti_datas_array(module_name, list(rtti_data)) =
+	mlds__initializer.
+gen_init_rtti_datas_array(ModuleName, RttiDatas) =
+	gen_init_array(gen_init_rtti_data(ModuleName), RttiDatas).
 
-:- func gen_init_cast_rtti_datas_array(list(rtti_data)) = mlds__initializer.
-gen_init_cast_rtti_datas_array(RttiDatas) =
-	gen_init_array(gen_init_cast_rtti_data, RttiDatas).
+:- func gen_init_cast_rtti_datas_array(mlds__type, module_name,
+		list(rtti_data)) = mlds__initializer.
+gen_init_cast_rtti_datas_array(Type, ModuleName, RttiDatas) =
+	gen_init_array(gen_init_cast_rtti_data(Type, ModuleName), RttiDatas).
 
 	% Generate the MLDS initializer comprising the rtti_name
 	% for a given rtti_data, converted to mlds__generic_type.
-:- func gen_init_cast_rtti_data(rtti_data) = mlds__initializer.
+:- func gen_init_cast_rtti_data(mlds__type, module_name, rtti_data) =
+	mlds__initializer.
 
-gen_init_cast_rtti_data(RttiData) = Initializer :-
+gen_init_cast_rtti_data(DestType, ModuleName, RttiData) = Initializer :-
 	( RttiData = pseudo_type_info(type_var(VarNum)) ->
 		% rtti_data_to_name/3 does not handle this case
-		Initializer = init_obj(unop(box(mlds__native_int_type),
+		SrcType = mlds__native_int_type,
+		Initializer = init_obj(unop(gen_cast(SrcType, DestType),
 			const(int_const(VarNum))))
 	;
 		rtti_data_to_name(RttiData, RttiTypeId, RttiName),
-		Initializer = gen_init_cast_rtti_name(RttiTypeId, RttiName)
+		Initializer = gen_init_cast_rtti_name(DestType,
+			ModuleName, RttiTypeId, RttiName)
 	).
 
+	% currently casts only store the destination type
+:- func gen_cast(mlds__type, mlds__type) = mlds__unary_op.
+gen_cast(_SrcType, DestType) = cast(DestType).
+
 	% Generate the MLDS initializer comprising the rtti_name
 	% for a given rtti_data.
-:- func gen_init_rtti_data(rtti_data) = mlds__initializer.
+:- func gen_init_rtti_data(module_name, rtti_data) = mlds__initializer.
 
-gen_init_rtti_data(RttiData) = Initializer :-
+gen_init_rtti_data(ModuleName, RttiData) = Initializer :-
 	rtti_data_to_name(RttiData, RttiTypeId, RttiName),
-	Initializer = gen_init_rtti_name(RttiTypeId, RttiName).
+	Initializer = gen_init_rtti_name(ModuleName, RttiTypeId, RttiName).
 
 	% Generate an MLDS initializer comprising just the
 	% the rval for a given rtti_name
-:- func gen_init_rtti_name(rtti_type_id, rtti_name) = mlds__initializer.
+:- func gen_init_rtti_name(module_name, rtti_type_id, rtti_name) =
+	mlds__initializer.
 
-gen_init_rtti_name(RttiTypeId, RttiName) =
-	init_obj(gen_rtti_name(RttiTypeId, RttiName)).
+gen_init_rtti_name(ModuleName, RttiTypeId, RttiName) =
+	init_obj(gen_rtti_name(ModuleName, RttiTypeId, RttiName)).
 
 	% Generate the MLDS initializer comprising the rtti_name
-	% for a given rtti_name, converted to mlds__generic_type.
-:- func gen_init_cast_rtti_name(rtti_type_id, rtti_name) = mlds__initializer.
+	% for a given rtti_name, converted to the given type.
+:- func gen_init_cast_rtti_name(mlds__type, module_name, rtti_type_id,
+	rtti_name) = mlds__initializer.
 
-gen_init_cast_rtti_name(RttiTypeId, RttiName) =
-	init_obj(unop(box(rtti_type(RttiName)), 
-		gen_rtti_name(RttiTypeId, RttiName))).
+gen_init_cast_rtti_name(DestType, ModuleName, RttiTypeId, RttiName) =
+	% SrcType = rtti_type(RttiName), 
+	init_obj(unop(cast(DestType),
+		gen_rtti_name(ModuleName, RttiTypeId, RttiName))).
 
 	% Generate the MLDS rval for an rtti_name.
-:- func gen_rtti_name(rtti_type_id, rtti_name) = mlds__rval.
+:- func gen_rtti_name(module_name, rtti_type_id, rtti_name) = mlds__rval.
 
-gen_rtti_name(RttiTypeId, RttiName) = Rval :-
-	RttiTypeId = rtti_type_id(ModuleName, _Type, _TypeArity),
+gen_rtti_name(ThisModuleName, RttiTypeId0, RttiName) = Rval :-
+	%
+	% Typeinfos are defined locally to each module.
+	% Other kinds of RTTI data are defining in the module
+	% corresponding to the type which they are for.
+	%
+	(
+		RttiName = pseudo_type_info(PseudoTypeInfo),
+		( PseudoTypeInfo = type_info(_, _)
+		; PseudoTypeInfo = higher_order_type_info(_, _, _)
+		)
+	->
+		ModuleName = ThisModuleName,
+		RttiTypeId = RttiTypeId0
+	;
+		RttiTypeId0 = rtti_type_id(RttiModuleName,
+			RttiTypeName, RttiTypeArity),
+		%
+		% Although the builtin types `int', `float', etc. are treated as part
+		% of the `builtin' module, for historical reasons they don't have
+		% any qualifiers at this point, so we need to add the `builtin'
+		% qualifier now.
+		%
+		( RttiModuleName = unqualified("") ->
+			mercury_public_builtin_module(ModuleName),
+			RttiTypeId = rtti_type_id(RttiModuleName,
+				RttiTypeName, RttiTypeArity)
+		;
+			ModuleName = RttiModuleName,
+			RttiTypeId = RttiTypeId0
+		)
+	),
 	MLDS_ModuleName = mercury_module_name_to_mlds(ModuleName),
 	MLDS_DataName = rtti(RttiTypeId, RttiName),
 	DataAddr = data_addr(MLDS_ModuleName, MLDS_DataName),
Index: library/benchmarking.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/benchmarking.m,v
retrieving revision 1.33
diff -u -d -r1.33 benchmarking.m
--- library/benchmarking.m	2000/04/11 11:33:27	1.33
+++ library/benchmarking.m	2000/04/20 12:41:49
@@ -88,6 +88,7 @@
 #include <stdlib.h>
 #include ""mercury_prof_mem.h""
 #include ""mercury_heap_profile.h""
+#include ""mercury_wrapper.h""		/* for time_at_last_stat */
 
 #ifdef PROFILE_MEMORY
 
Index: library/builtin.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/builtin.m,v
retrieving revision 1.31
diff -u -d -r1.31 builtin.m
--- library/builtin.m	2000/04/18 03:44:39	1.31
+++ library/builtin.m	2000/04/20 12:57:57
@@ -234,6 +234,8 @@
 
 :- pragma c_code("
 
+#ifndef HIGHLEVEL_CODE
+
 MR_DEFINE_BUILTIN_TYPE_CTOR_INFO_FULL(builtin, , int, 0,
 	MR_TYPECTOR_REP_INT,
 	mercury__builtin_unify_int_2_0,
@@ -345,6 +347,8 @@
 	MR_INIT_TYPE_CTOR_INFO_WITH_PRED(
 		mercury_data___type_ctor_info_void_0, mercury__unused_0_0);
 }
+
+#endif /* ! HIGHLEVEL_CODE */
 
 ").
 
Index: library/exception.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/exception.m,v
retrieving revision 1.18
diff -u -d -r1.18 exception.m
--- library/exception.m	2000/04/14 07:20:27	1.18
+++ library/exception.m	2000/04/20 13:08:00
@@ -579,7 +579,7 @@
 	typedef void FuncType(void *, MR_Box, MR_Box *);
 	FuncType *code = (FuncType *)
 		MR_field(MR_mktag(0), closure, (Integer) 1);
-	(*code)((void *) closure, exception, result);
+	(*code)((void *) closure, (MR_Box) exception, result);
 }
 
 static bool
@@ -589,7 +589,7 @@
 	typedef bool FuncType(void *, MR_Box, MR_Box *);
 	FuncType *code = (FuncType *)
 		MR_field(MR_mktag(0), closure, (Integer) 1);
-	return (*code)((void *) closure, exception, result);
+	return (*code)((void *) closure, (MR_Box) exception, result);
 }
 
 #ifdef MR_USE_GCC_NESTED_FUNCTIONS
@@ -601,7 +601,7 @@
 	typedef void FuncType(void *, MR_Box, MR_Box *, MR_NestedCont);
 	FuncType *code = (FuncType *)
 		MR_field(MR_mktag(0), closure, (Integer) 1);
-	(*code)((void *) closure, exception, result, cont);
+	(*code)((void *) closure, (MR_Box) exception, result, cont);
 }
 
 #else
@@ -613,7 +613,7 @@
 	typedef void FuncType(void *, MR_Box, MR_Box *, MR_Cont, void *);
 	FuncType *code = (FuncType *)
 		MR_field(MR_mktag(0), closure, (Integer) 1);
-	(*code)((void *) closure, exception, result, cont, cont_env);
+	(*code)((void *) closure, (MR_Box) exception, result, cont, cont_env);
 }
 
 #endif
Index: library/private_builtin.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/private_builtin.m,v
retrieving revision 1.47
diff -u -d -r1.47 private_builtin.m
--- library/private_builtin.m	2000/04/18 03:44:41	1.47
+++ library/private_builtin.m	2000/04/20 12:53:52
@@ -1137,7 +1137,8 @@
 
 :- pragma c_header_code("
 
-#include ""mercury_misc.h""	/* for fatal_error(); */
+#include ""mercury_misc.h""		/* for fatal_error(); */
+#include ""mercury_type_info.h""	/* for MR_TypeCtorInfo_Struct; */
 
 extern MR_STATIC_CODE_CONST struct MR_TypeCtorInfo_Struct
 	mercury_data___type_ctor_info_int_0;
Index: runtime/mercury.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury.h,v
retrieving revision 1.2
diff -u -d -r1.2 mercury.h
--- runtime/mercury.h	1999/12/21 10:28:05	1.2
+++ runtime/mercury.h	2000/04/20 13:53:06
@@ -25,8 +25,14 @@
 #include "mercury_grade.h"
 #include "mercury_thread.h"	/* for the MR_*_GLOBAL_LOCK() macros */
 #include "mercury_std.h"
+#include "mercury_type_info.h"
 
-#include "gc.h"
+#ifdef CONSERVATIVE_GC
+  #include "gc.h"
+  #ifdef INLINE_ALLOC
+    #include "gc_inl.h"
+  #endif
+#endif
 
 #include <setjmp.h>	/* for jmp_buf etc., which are used for commits */
 #include <string.h>	/* for strcmp(), which is used for =/2 on strings */
@@ -57,66 +63,100 @@
 typedef Word	MR_Word;
 
 /*
-** The MR_BaseTypeInfo struct holds information about
-** a type constructor.
-** This is essentially the same as MR_TypeCtorInfo
-** in runtime/mercury_type_info.h, but for the MLDS back-end
-** rather than the LLDS back-end.
+** Typedefs used for the types of RTTI data structures.
+** Many of these types are defined in mercury_type_info.h,
+** but the ones which are used only by the MLDS back-end
+** are defined here.
 */
-typedef struct MR_BaseTypeInfo_struct {
-	/*
-	** The unify, index, and compare fields hold pointers
-	** to functions which take N type_info arguments, followed
-	** by their other parameters, where the value of N is given
-	** by the type_arity field.
-	*/
-	Integer		type_arity;
-	MR_Box		unify;	 /* bool (*)(..., MR_Box, MR_Box); */
-	MR_Box		index;   /* void (*)(..., MR_Box, Integer *); */
-	MR_Box		compare; /* void (*)(..., Word *, MR_Box, MR_Box)' */
-	/*
-	** The type_ctor_rep holds an enumeration value
-	** (of type `enum MR_TypeCtorRepresentation') indicating
-	** what kind of type it is and how the type is represented.
-	*/
-	Integer		type_ctor_rep;
-	void *		base_type_functors; /* XXX currently always NULL */
-	void *		base_type_layout; /* XXX currently always NULL */
-	/*
-	** The module_name and type_name, together with the type_arity
-	** field above, serve to identify the type constructor.
-	*/
-	const char *	module_name;
-	const char *	type_name;
-	/*
-	** This field indicates which version of the various RRTI
-	** structures this is.
-	*/
-	Integer		rtti_version;
-} MR_BaseTypeInfo;
+typedef struct MR_TypeCtorInfo_Struct	MR_TypeCtorInfo_Struct;
+typedef MR_DuExistLocn			MR_DuExistLocnArray[];
+typedef ConstString			MR_ConstStringArray[];
+typedef MR_PseudoTypeInfo		MR_PseudoTypeInfoArray[];
+typedef const MR_EnumFunctorDesc *	MR_EnumFunctorDescPtrArray[];
+typedef const MR_DuFunctorDesc *	MR_DuFunctorDescPtrArray[];
+typedef MR_DuPtagLayout			MR_DuPtagLayoutArray[];
+typedef union MR_TableNode_Union * *	MR_TableNodePtrPtr[];
+
+/*
+** XXX Currently we hard-code the declarations of the first
+** few of these type-info struct types; this imposes a fixed
+** limit on the arity of types.  Fortunately types with a high
+** arity tend not to be used very often, so this is probably OK
+** for now...
+*/
+
+#ifndef MR_HO_PseudoTypeInfo_Struct1_GUARD
+#define MR_HO_PseudoTypeInfo_Struct1_GUARD
+MR_HIGHER_ORDER_PSEUDOTYPEINFO_STRUCT(MR_HO_PseudoTypeInfo_Struct1, 1);
+#endif
+
+#ifndef MR_HO_PseudoTypeInfo_Struct2_GUARD
+#define MR_HO_PseudoTypeInfo_Struct2_GUARD
+MR_HIGHER_ORDER_PSEUDOTYPEINFO_STRUCT(MR_HO_PseudoTypeInfo_Struct2, 2);
+#endif
 
+#ifndef MR_HO_PseudoTypeInfo_Struct3_GUARD
+#define MR_HO_PseudoTypeInfo_Struct3_GUARD
+MR_HIGHER_ORDER_PSEUDOTYPEINFO_STRUCT(MR_HO_PseudoTypeInfo_Struct3, 3);
+#endif
+
+#ifndef MR_HO_PseudoTypeInfo_Struct4_GUARD
+#define MR_HO_PseudoTypeInfo_Struct4_GUARD
+MR_HIGHER_ORDER_PSEUDOTYPEINFO_STRUCT(MR_HO_PseudoTypeInfo_Struct4, 4);
+#endif
+
+#ifndef MR_FO_PseudoTypeInfo_Struct1_GUARD
+#define MR_FO_PseudoTypeInfo_Struct1_GUARD
+MR_FIRST_ORDER_PSEUDOTYPEINFO_STRUCT(MR_FO_PseudoTypeInfo_Struct1, 1);
+#endif
+
+#ifndef MR_FO_PseudoTypeInfo_Struct2_GUARD
+#define MR_FO_PseudoTypeInfo_Struct2_GUARD
+MR_FIRST_ORDER_PSEUDOTYPEINFO_STRUCT(MR_FO_PseudoTypeInfo_Struct2, 2);
+#endif
+
+#ifndef MR_FO_PseudoTypeInfo_Struct3_GUARD
+#define MR_FO_PseudoTypeInfo_Struct3_GUARD
+MR_FIRST_ORDER_PSEUDOTYPEINFO_STRUCT(MR_FO_PseudoTypeInfo_Struct3, 3);
+#endif
+
+#ifndef MR_FO_PseudoTypeInfo_Struct4_GUARD
+#define MR_FO_PseudoTypeInfo_Struct4_GUARD
+MR_FIRST_ORDER_PSEUDOTYPEINFO_STRUCT(MR_FO_PseudoTypeInfo_Struct4, 4);
+#endif
+
+typedef struct MR_HO_PseudoTypeInfo_Struct1 MR_HO_PseudoTypeInfo_Struct1;
+typedef struct MR_HO_PseudoTypeInfo_Struct2 MR_HO_PseudoTypeInfo_Struct2;
+typedef struct MR_HO_PseudoTypeInfo_Struct3 MR_HO_PseudoTypeInfo_Struct3;
+typedef struct MR_HO_PseudoTypeInfo_Struct4 MR_HO_PseudoTypeInfo_Struct4;
+
+typedef struct MR_FO_PseudoTypeInfo_Struct1 MR_FO_PseudoTypeInfo_Struct1;
+typedef struct MR_FO_PseudoTypeInfo_Struct2 MR_FO_PseudoTypeInfo_Struct2;
+typedef struct MR_FO_PseudoTypeInfo_Struct3 MR_FO_PseudoTypeInfo_Struct3;
+typedef struct MR_FO_PseudoTypeInfo_Struct4 MR_FO_PseudoTypeInfo_Struct4;
+
 /*---------------------------------------------------------------------------*/
 /*
 ** Declarations of contants and variables
 */
 
-/* declare MR_BaseTypeInfos for the builtin types */
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_int_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_string_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_float_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_character_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_void_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_c_pointer_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_pred_0;
-extern const MR_BaseTypeInfo mercury__builtin__base_type_info_func_0;
-extern const MR_BaseTypeInfo mercury__array__base_type_info_array_1;
-extern const MR_BaseTypeInfo mercury__std_util__base_type_info_univ_0;
-extern const MR_BaseTypeInfo mercury__std_util__base_type_info_type_info_0;
-extern const MR_BaseTypeInfo
-	mercury__private_builtin__base_type_info_type_ctor_info_1,
-	mercury__private_builtin__base_type_info_type_info_1,
-	mercury__private_builtin__base_type_info_typeclass_info_1,
-	mercury__private_builtin__base_type_info_base_typeclass_info_1;
+/* declare MR_TypeCtorInfo_Structs for the builtin types */
+extern const MR_TypeCtorInfo_Struct
+	mercury__builtin__builtin__type_ctor_info_int_0,
+	mercury__builtin__builtin__type_ctor_info_string_0,
+	mercury__builtin__builtin__type_ctor_info_float_0,
+	mercury__builtin__builtin__type_ctor_info_character_0,
+	mercury__builtin__builtin__type_ctor_info_void_0,
+	mercury__builtin__builtin__type_ctor_info_c_pointer_0,
+	mercury__builtin__builtin__type_ctor_info_pred_0,
+	mercury__builtin__builtin__type_ctor_info_func_0,
+	mercury__array__array__type_ctor_info_array_1,
+	mercury__std_util__std_util__type_ctor_info_univ_0,
+	mercury__std_util__std_util__type_ctor_info_type_info_0,
+	mercury__private_builtin__private_builtin__type_ctor_info_type_ctor_info_1,
+	mercury__private_builtin__private_builtin__type_ctor_info_type_info_1,
+	mercury__private_builtin__private_builtin__type_ctor_info_typeclass_info_1,
+	mercury__private_builtin__private_builtin__type_ctor_info_base_typeclass_info_1;
 
 /*
 ** The compiler generates references to this constant.
Index: runtime/mercury_type_info.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_type_info.h,v
retrieving revision 1.48
diff -u -d -r1.48 mercury_type_info.h
--- runtime/mercury_type_info.h	2000/04/16 05:47:21	1.48
+++ runtime/mercury_type_info.h	2000/04/19 07:09:28
@@ -363,6 +363,19 @@
 */
 
 /*
+** For each enumeration constant, we define it using two names;
+** firstly we define the unqualified name, and then we define
+** another enumeration constant whose name is the unqualified name
+** prefixed with `mercury__private_builtin__' and whose value is
+** the same as that of the unqualified name.
+** The qualified versions are used by the MLDS->C back-end,
+** which generates references to them.
+*/
+#define MR_DEFINE_ENUM_CONST(x)	\
+	x,			\
+	MR_PASTE2(mercury__private_builtin__,x) = x
+
+/*
 ** MR_DataRepresentation is the representation for a particular type
 ** constructor.  For the cases of MR_TYPE_CTOR_REP_DU and
 ** MR_TYPE_CTOR_REP_DU_USEREQ, the exact representation depends on the tag
@@ -371,41 +384,41 @@
 */
 
 typedef enum {
-    MR_TYPECTOR_REP_ENUM,
-    MR_TYPECTOR_REP_ENUM_USEREQ,
-    MR_TYPECTOR_REP_DU,
-    MR_TYPECTOR_REP_DU_USEREQ,
-    MR_TYPECTOR_REP_NOTAG,
-    MR_TYPECTOR_REP_NOTAG_USEREQ,
-    MR_TYPECTOR_REP_EQUIV,
-    MR_TYPECTOR_REP_EQUIV_VAR,
-    MR_TYPECTOR_REP_INT,
-    MR_TYPECTOR_REP_CHAR,
-    MR_TYPECTOR_REP_FLOAT,
-    MR_TYPECTOR_REP_STRING,
-    MR_TYPECTOR_REP_PRED,
-    MR_TYPECTOR_REP_UNIV,
-    MR_TYPECTOR_REP_VOID,
-    MR_TYPECTOR_REP_C_POINTER,
-    MR_TYPECTOR_REP_TYPEINFO,
-    MR_TYPECTOR_REP_TYPECLASSINFO,
-    MR_TYPECTOR_REP_ARRAY,
-    MR_TYPECTOR_REP_SUCCIP,
-    MR_TYPECTOR_REP_HP,
-    MR_TYPECTOR_REP_CURFR,
-    MR_TYPECTOR_REP_MAXFR,
-    MR_TYPECTOR_REP_REDOFR,
-    MR_TYPECTOR_REP_REDOIP,
-    MR_TYPECTOR_REP_TRAIL_PTR,
-    MR_TYPECTOR_REP_TICKET,
-    MR_TYPECTOR_REP_NOTAG_GROUND,
-    MR_TYPECTOR_REP_NOTAG_GROUND_USEREQ,
-    MR_TYPECTOR_REP_EQUIV_GROUND,
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_ENUM),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_ENUM_USEREQ),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_DU),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_DU_USEREQ),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_NOTAG),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_NOTAG_USEREQ),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_EQUIV),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_EQUIV_VAR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_INT),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_CHAR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_FLOAT),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_STRING),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_PRED),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_UNIV),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_VOID),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_C_POINTER),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_TYPEINFO),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_TYPECLASSINFO),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_ARRAY),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_SUCCIP),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_HP),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_CURFR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_MAXFR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_REDOFR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_REDOIP),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_TRAIL_PTR),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_TICKET),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_NOTAG_GROUND),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_NOTAG_GROUND_USEREQ),
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_EQUIV_GROUND),
     /*
     ** MR_TYPECTOR_REP_UNKNOWN should remain the last alternative;
     ** MR_TYPE_CTOR_STATS depends on this.
     */
-    MR_TYPECTOR_REP_UNKNOWN
+    MR_DEFINE_ENUM_CONST(MR_TYPECTOR_REP_UNKNOWN)
 } MR_TypeCtorRep;
 
 /*
@@ -555,9 +568,9 @@
 */
 
 typedef enum {
-    MR_SECTAG_NONE,
-    MR_SECTAG_LOCAL,
-    MR_SECTAG_REMOTE
+    MR_DEFINE_ENUM_CONST(MR_SECTAG_NONE),
+    MR_DEFINE_ENUM_CONST(MR_SECTAG_LOCAL),
+    MR_DEFINE_ENUM_CONST(MR_SECTAG_REMOTE)
 } MR_Sectag_Locn;
 
 typedef struct {

-- 
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.
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list