[m-rev.] for review: More modifications to the Java back-end

Michael Wybrow mjwybrow at students.cs.mu.oz.au
Wed Feb 6 16:37:03 AEDT 2002


Probably for Fergus.


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

Estimated hours taken: 45
Branches: main


Bug fixes and additions to the Java back-end so that it will now successfully
compile and run mercury programs which contain higher order code as well as
non-deterministic code.
With some hacked up Mercury library code (in Java) I am able to compile 10 of
the 11 files in the tests/benchmarks directory into Java and run them to 
receive the correct output. 


mercury/compiler/mlds_to_java.m:
	Many small bug fixes.
	
	Disabled current (incomplete) name mangling code. All class, package
	and method names apart from java.* and mercury.runtime.* will be
	output as lowercase for the moment.
	
	Added code to prefix some classes/packages so we don't run into the 
	problem of having a class or package name which is also a Java reserved
	word. This is the case with the mercury library modules int and char. 
	
	Added code to implement commits.
	
	
mercury/compiler/java_util.m:
	Added a few missing Java reserved words.

mercury/compiler/ml_code_util.m:
	A small change so that in one case where they weren't, multiple return
	values are now generated in the MLDS.

mercury/java/Commit.java:
	Added this file, a throwable class used for the implementation of
	commits.

mercury/java/ProcAddr.java:
mercury/java/Compare.java:
mercury/java/Unify.java:
	Removed these files, they're now obsolete as they all use the standard 
	interface for method pointers provided by MethodPtr.java.


Index: compiler/java_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/java_util.m,v
retrieving revision 1.4
diff -u -r1.4 java_util.m
--- compiler/java_util.m	23 Jan 2002 22:23:14 -0000	1.4
+++ compiler/java_util.m	5 Feb 2002 00:53:41 -0000
@@ -176,6 +176,10 @@
 java_util__is_keyword("throws").
 java_util__is_keyword("transient").
 java_util__is_keyword("true").
+java_util__is_keyword("try").
+java_util__is_keyword("void").
+java_util__is_keyword("volatile").
+java_util__is_keyword("while").
 
 :- func this_file = string.
 this_file = "java_util.m".
Index: compiler/ml_code_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/ml_code_util.m,v
retrieving revision 1.53
diff -u -r1.53 ml_code_util.m
--- compiler/ml_code_util.m	1 Feb 2002 22:06:10 -0000	1.53
+++ compiler/ml_code_util.m	5 Feb 2002 01:50:46 -0000
@@ -801,7 +801,9 @@
 		MLDS_Statements0, MLDS_Statements) -->
 	( { CodeModel = model_semi } ->
 		ml_gen_test_success(Succeeded),
-		{ ReturnStmt = return([Succeeded]) },
+		{ CopiedOutputVarRvals = list__map(func(Lval) = lval(Lval),
+			CopiedOutputVarLvals) },
+		{ ReturnStmt = return([Succeeded | CopiedOutputVarRvals]) },
 		{ ReturnStatement = mlds__statement(ReturnStmt,
 			mlds__make_context(Context)) },
 		{ MLDS_Statements = list__append(MLDS_Statements0,
Index: compiler/mlds_to_java.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_java.m,v
retrieving revision 1.20
diff -u -r1.20 mlds_to_java.m
--- compiler/mlds_to_java.m	28 Jan 2002 05:30:27 -0000	1.20
+++ compiler/mlds_to_java.m	6 Feb 2002 05:21:37 -0000
@@ -10,21 +10,24 @@
 % DONE:
 %	det and semidet predicates
 %	multiple output arguments
-%       boxing and unboxing
-%       conjunctions
-%       disjunctions
+%	boxing and unboxing
+%	conjunctions
+%	disjunctions
 %	if-then-else's
-%       enumerations
+%	enumerations
 %	discriminated unions
-% TODO: 
+%	higher order functions
 %	multidet and nondet predicates
-%       RTTI
-%	handle foreign code written in Java
-%       higher order functions
-%       generate names of classes etc. correctly 
-%	generate optimized tailcalls
-%       handle foreign code written in C 
+%	test tests/benchmarks/*.m
+% TODO: 
+%	General code cleanup
 %	handle static ground terms
+%	RTTI (requires static ground terms)
+%	generate names of classes etc. correctly (mostly same as IL backend)
+%	generate optimized tailcalls
+%
+%	handle foreign code written in Java
+%	handle foreign code written in C 
 %
 % NOTES: 
 %       To avoid namespace conflicts all Java names must be fully qualified.
@@ -71,7 +74,9 @@
 
 mlds_to_java__output_mlds(MLDS) -->
 	{ ModuleName = mlds__get_module_name(MLDS) },
-	module_name_to_file_name(ModuleName, ".java", yes, JavaSourceFile),
+	{ JavaSafeModuleName = valid_module_name(ModuleName) },
+	module_name_to_file_name(JavaSafeModuleName, ".java", yes, 
+			JavaSourceFile),
 	{ Indent = 0 },
 	output_to_file(JavaSourceFile, output_java_src_file(Indent, MLDS)).
 
@@ -173,11 +178,9 @@
 :- pred interface_is_special(string).
 :- mode interface_is_special(in) is semidet.
 
-interface_is_special("Unify").
-interface_is_special("Compare").
-interface_is_special("ProcAddr").
 interface_is_special("MethodPtr").
 
+
 %-----------------------------------------------------------------------------%
 %
 % Code to mangle names, enforce Java code conventions regarding class names
@@ -227,14 +230,16 @@
 :- pred mangle_mlds_sym_name_for_java(sym_name, string, string).
 :- mode mangle_mlds_sym_name_for_java(in, in, out) is det.
 
-mangle_mlds_sym_name_for_java(unqualified(Name), _Qualifier, MangledName) :-
-	llds_out__name_mangle(Name, MangledName).
+mangle_mlds_sym_name_for_java(unqualified(Name), _Qualifier, JavaSafeName) :-
+	llds_out__name_mangle(Name, MangledName),
+	JavaSafeName = valid_symbol_name(MangledName).
 mangle_mlds_sym_name_for_java(qualified(ModuleName, PlainName), Qualifier,
 		MangledName) :-
 	mangle_mlds_sym_name_for_java(ModuleName, Qualifier,
 			MangledModuleName),
 	llds_out__name_mangle(PlainName, MangledPlainName),
-	java_qualify_mangled_name(MangledModuleName, MangledPlainName,
+	JavaSafePlainName = valid_symbol_name(MangledPlainName),
+	java_qualify_mangled_name(MangledModuleName, JavaSafePlainName,
 			Qualifier, MangledName).
 
 :- pred java_qualify_mangled_name(string, string, string, string).
@@ -243,6 +248,45 @@
 java_qualify_mangled_name(Module0, Name0, Qualifier, Name) :-
 	string__append_list([Module0, Qualifier, Name0], Name).
 
+
+%-----------------------------------------------------------------------------%
+%
+% Name mangling code to fix problem of mercury modules having the same name
+% as reserved Java words such as `char' and `int'. 
+% 
+
+	% If the given name conficts with a reserved Java word we must add a 
+	% prefix to it to avoid compilation errors.
+:- func valid_symbol_name(string) = string.
+:- mode valid_symbol_name(in) = out is det.
+
+valid_symbol_name(SymName) = ValidSymName :-
+	Prefix = "mr_",
+	( java_util__is_keyword(SymName) ->
+		% This is a reserved Java word, add the above prefix.
+		ValidSymName = Prefix ++ SymName
+	; string__append(Prefix, Suffix, SymName) ->
+		% This name already contains the prefix we are adding to 
+		% variables to avoid conficts, so add an additional '_'.
+		ValidSymName = Prefix ++ "_" ++ Suffix
+	; 
+		% Normal name; do nothing.
+		ValidSymName = SymName
+	).
+
+
+:- func valid_module_name(mercury_module_name) = mercury_module_name.
+:- mode valid_module_name(in) = out is det.
+
+valid_module_name(unqualified(String)) =  ValidModuleName :-
+	ValidString = valid_symbol_name(String),
+	ValidModuleName = unqualified(ValidString).
+valid_module_name(qualified(ModuleSpecifier, String)) =  ValidModuleName :-
+	ValidModuleSpecifier = valid_module_name(ModuleSpecifier),
+	ValidString = valid_symbol_name(String),
+	ValidModuleName = qualified(ValidModuleSpecifier, ValidString).
+
+
 %-----------------------------------------------------------------------------%
 %
 % Code to output imports.
@@ -267,12 +311,11 @@
 		unexpected(this_file, "foreign import in java backend")
 	},
 	{ SymName = mlds_module_name_to_sym_name(ImportName) },
-	{ prog_out__sym_name_to_string(SymName, ".", File) }, 
-	( { qualified_name_is_stdlib(SymName) } ->
-		{ enforce_java_names(File, ClassFile) }
-	;
-		{ ClassFile = File }
-	),
+	{ JavaSafeSymName = valid_module_name(SymName) },
+	{ prog_out__sym_name_to_string(JavaSafeSymName, ".", File) }, 
+	% XXX Name mangling code should be put here when we start enforcing
+	%     Java's naming conventions.
+	{ ClassFile = File },
 	io__write_strings(["import ", ClassFile, ";\n"]).
 
 %--------------------------------------------------------------------
@@ -644,9 +687,9 @@
 	OrigFuncSignature = mlds__func_signature(OrigArgTypes, OrigRetTypes),
 	% XXX We should fill in the Context properly.
 	Context = mlds__make_context(term__context_init),
-	ProcLabel = mlds__qual(ModuleName, EntityName),
+	ProcLabel = mlds__qual(ModuleName, _EntityName),
 	hlds_pred__initial_pred_id(PredID),
-	ProcID = snd(EntityName),
+	initial_proc_id(ProcID),
 	%
 	% Create new method name
 	%
@@ -826,17 +869,18 @@
 :- mode output_src_start(in, in, in, in, di, uo) is det.
 
 output_src_start(Indent, ModuleName, Imports, Defns) -->
+	{ JavaSafeModuleName = valid_module_name(ModuleName) },
 	output_auto_gen_comment(ModuleName),
 	indent_line(Indent),
 	io__write_string("/* :- module "),
-	prog_out__write_sym_name(ModuleName),
+	prog_out__write_sym_name(JavaSafeModuleName),
 	io__write_string(". */\n\n"),
-	output_package_info(ModuleName),	
-	output_imports(Imports),
+	output_package_info(JavaSafeModuleName),	
+	output_imports(Imports), 
 	io__write_string("public class "),
-	prog_out__write_sym_name(ModuleName),
+	prog_out__write_sym_name(JavaSafeModuleName),
 	io__write_string(" {\n"),
-	maybe_write_main_driver(Indent + 1, ModuleName, Defns).
+	maybe_write_main_driver(Indent + 1, JavaSafeModuleName, Defns).
 
 	% Output a `package' directive at the top of the Java source file,
 	% if necessary.
@@ -891,10 +935,11 @@
 :- mode output_src_end(in, in, di, uo) is det.
 
 output_src_end(Indent, ModuleName) -->
+	{ JavaSafeModuleName = valid_module_name(ModuleName) },
 	io__write_string("}\n"),
 	indent_line(Indent),
 	io__write_string("// :- end_module "),
-	prog_out__write_sym_name(ModuleName),
+	prog_out__write_sym_name(JavaSafeModuleName),
 	io__write_string(".\n").
 
 	% Output a Java comment saying that the file was automatically
@@ -1427,11 +1472,9 @@
 	{ SymName = mlds_module_name_to_sym_name(ModuleName) },
 	{ mangle_mlds_sym_name_for_java(SymName, Qualifier, 
 			MangledModuleName) },
-	( { qualified_name_is_stdlib(SymName) } ->
-		{ enforce_java_names(MangledModuleName, JavaMangledName) }
-	;
-		{ MangledModuleName = JavaMangledName }
-	),
+	% XXX Name mangling code should be put here when we start enforcing
+	%     Java's naming convention.
+	{ MangledModuleName = JavaMangledName},
 	io__write_string(JavaMangledName),
 	io__write_string(Qualifier),
 	OutputFunc(Name).
@@ -1582,7 +1625,7 @@
 	output_type(Type),
 	io__write_string("[]").
 output_type(mlds__func_type(_FuncParams)) -->
-	io__write_string("MethodPtr").
+	io__write_string("mercury.runtime.MethodPtr").
 output_type(mlds__generic_type) -->
 	io__write_string("java.lang.Object").	
 output_type(mlds__generic_env_ptr_type) -->
@@ -1590,12 +1633,11 @@
 output_type(mlds__pseudo_type_info_type) -->
 	io__write_string("mercury.runtime.PseudoTypeInfo").
 output_type(mlds__cont_type(_)) -->
-	% XXX Not yet implemented.
-	{ unexpected(this_file, 
-		"output_type: nondet code not yet implemented") }.
+	% XXX Should this actually be a class that extends MethodPtr? 
+	io__write_string("mercury.runtime.MethodPtr").
 output_type(mlds__commit_type) -->
-	% XXX Not yet implemented.
-	{ unexpected(this_file, "output_type: commits not yet implemented") }.
+	io__write_string("mercury.runtime.Commit").
+
 %
 % XXX The RTTI data should actually be static but it isn't being
 % generated as such.
@@ -1871,7 +1913,7 @@
 	%
 output_stmt(Indent, CallerFuncInfo, Call, Context) -->
 	{ Call = call(Signature, FuncRval, MaybeObject, CallArgs,
-		Results, IsTailCall) },
+		Results, _IsTailCall) },
 	{ CallerFuncInfo = func_info(_Name, _Params) },
 	{ Signature = mlds__func_signature(ArgTypes, RetTypes) },
 	indent_line(Indent),
@@ -1905,7 +1947,8 @@
 		% 
 		output_call_rval(FuncRval),
 		io__write_string("("),
-		io__write_list(CallArgs, ", ", output_rval)
+		io__write_list(CallArgs, ", ", output_rval),
+		io__write_string(")")
 	;
 		% This is a call using a method pointer.
 		%
@@ -1934,7 +1977,7 @@
 				io__write_string(") ")
 			)
 		;
-				io__write_string("((java.lang.Object[]) ")
+			io__write_string("((java.lang.Object[]) ")
 		),	
 		( { MaybeObject = yes(Object) } ->
 			output_bracketed_rval(Object),
@@ -1954,6 +1997,7 @@
 		%
 		% XXX This is a hack, see the above comment.
 		% 
+		io__write_string(")"),
 		( { RetTypes = [] } ->
 			[]
 		; { RetTypes = [RetType2] } ->
@@ -1968,10 +2012,10 @@
 				io__write_string(")")
 			)
 		;
-				io__write_string(")")
+			io__write_string(")")
 		)	
 	),
-	io__write_string(");\n"),
+	io__write_string(";\n"),
 
 	( { Results = [_, _ | _] } ->
 		% Copy the results from the "result" array into the Result
@@ -1980,12 +2024,16 @@
 	;
 		[]
 	),
-	( { IsTailCall = tail_call, Results = [] } ->
-		indent_line(Context, Indent + 1),
-		io__write_string("return;\n")
-	;
-		[]
-	),
+	% XXX Is this needed? If present, it causes compiler errors for a
+	%     couple of files in the benchmarks directory.  -mjwybrow
+	%
+	% ( { IsTailCall = tail_call, Results = [] } ->
+	%	indent_line(Context, Indent + 1),
+	%	io__write_string("return;\n")
+	% ;
+	%	[]
+	% ),
+	%
 	indent_line(Indent),
 	io__write_string("}\n").
 
@@ -2019,46 +2067,74 @@
 	).
 
 
-output_stmt(Indent, FuncInfo, return(Results), _Context) -->
-	indent_line(Indent),
-	io__write_string("return"),
+output_stmt(Indent, FuncInfo, return(Results0), _Context) -->
+	{ Results = remove_dummy_vars(Results0) },
 	( { Results = [] } ->
 		[]
 	; { Results = [Rval] } ->
-		io__write_char(' '),
-		% 
-		% Don't output `dummy_var'.
-		%
-		( 
-	   		{ Rval = mlds__lval(Lval) },
-	   		{ Lval = var(VarName, _) },
-	   		{ VarName = qual(_, UnqualName) },
-	   		{ UnqualName = var_name("dummy_var", no) } 
-		->
-			[]
-		;
-			output_rval(Rval)
-		)
+		indent_line(Indent),
+		io__write_string("return "),
+		output_rval(Rval),
+		io__write_string(";\n")
 	;
 		{ FuncInfo = func_info(_Name, Params) },
 		{ Params = mlds__func_params(_Args, ReturnTypes) },
 		{ TypesAndResults = assoc_list__from_corresponding_lists(
 			ReturnTypes, Results) },
-		io__write_string(" new java.lang.Object[] { "),
+		io__write_string("return new java.lang.Object[] { "),
 		io__write_list(TypesAndResults, ",\n ",
 			(pred((Type - Result)::in, di, uo) is det -->
 				output_boxed_rval(Type, Result))),
-		io__write_string("}")
-	),
+		io__write_string("};\n")
+	).
+
+output_stmt(Indent, _FuncInfo, do_commit(Ref), _) -->
+	indent_line(Indent),
+	output_rval(Ref),
+	io__write_string(" = new mercury.runtime.Commit();\n"),
+	indent_line(Indent),
+	io__write_string("throw "),
+	output_rval(Ref),
 	io__write_string(";\n").
-	
-	%
-	% commits
-	% XXX These are yet to be implemented.
-output_stmt(_Indent, _FuncInfo, do_commit(_Ref), _) -->
-	{ sorry(this_file, "output_stmt: commits not yet implemented") }.
-output_stmt(_Indent, _FuncInfo, try_commit(_Ref, _Stmt0, _Handler), _) -->
-	{ sorry(this_file, "output_stmt: commits not implemented") }.
+
+output_stmt(Indent, FuncInfo, try_commit(_Ref, Stmt, Handler), _) -->
+	indent_line(Indent),
+	io__write_string("try\n"),
+	indent_line(Indent),
+	io__write_string("{\n"),
+	output_statement(Indent + 1, FuncInfo, Stmt),
+	indent_line(Indent),
+	io__write_string("}\n"),
+	indent_line(Indent),
+	io__write_string("catch (mercury.runtime.Commit commit_variable)\n"),
+	indent_line(Indent),
+	io__write_string("{\n"),
+	indent_line(Indent + 1),
+	io__write_string("// java.util.Stack.pop();\n"),
+	output_statement(Indent + 1, FuncInfo, Handler),
+	indent_line(Indent),
+	io__write_string("}\n").
+
+
+
+:- func remove_dummy_vars(list(mlds__rval)) = list(mlds__rval).
+:- mode remove_dummy_vars(in) = out is det.
+
+remove_dummy_vars([]) = [].
+remove_dummy_vars([Var|Vars0]) = VarList :-
+	Vars = remove_dummy_vars(Vars0),
+	( 
+   		Var = mlds__lval(Lval),
+   		Lval = var(VarName, _),
+   		VarName = qual(_, UnqualName),
+   		UnqualName = var_name("dummy_var", no) 
+	->
+		VarList = Vars
+	;
+		VarList = [Var|Vars]	
+	).
+
+
 %-----------------------------------------------------------------------------%
 %
 % When returning multiple values,
@@ -2242,7 +2318,7 @@
 		output_type(Type)
 	),
 	(
-		{ Type = mlds__func_type(_FuncParams)
+		{ Type = mlds__array_type(_Type)
 		; Type = mlds__mercury_type(_Type, pred_type, _)
 		} 
 	->
@@ -2261,6 +2337,7 @@
 		output_init_args(Args, ArgTypes, 0),
 		io__write_string(");\n")
 	),
+	indent_line(Indent),
 	io__write_string("}\n").
 	
 
@@ -2304,21 +2381,26 @@
 	{ error("output_init_args: length mismatch") }.
 output_init_args([], [_|_], _) -->
 	{ error("output_init_args: length mismatch") }.
-output_init_args([Arg|Args], [_ArgType|ArgTypes], ArgNum) -->
-	( { ArgNum = 0 } ->
-		% Discard the first argument, as this will always be the 
-		% data_tag, which is now set by the class constructor. 
+output_init_args([Arg|Args], [ArgType|ArgTypes], ArgNum) -->
+	(
+		{ ArgNum = 0 },
+		{ ArgType = native_int_type },
+		{ Arg = const(int_const(_Val)) }
+	->
+		% This first argument is a `data_tag', It is set by
+		% the class constructor so this argument can be discarded.
 		[]
-	; 
-		( { ArgNum > 1 } ->
-			io__write_string(", ")
-		;
+	;
+		output_rval(Arg),
+		( { Args = [] } ->
 			[]
-		),
-		output_rval(Arg)
+		;
+			io__write_string(", ")
+		)
 	),
 	output_init_args(Args, ArgTypes, ArgNum + 1).
 
+
 %-----------------------------------------------------------------------------%
 %
 % Code to output expressions
@@ -2340,11 +2422,14 @@
 		% must be something that maps to MR_Box.
 		{ error("unexpected field type") }
 	),
-	io__write_string("("),
+	% XXX We shouldn't need this cast here, but there are cases where 
+	%     it is needed and the MLDS doesn't seem to generate it.
+	io__write_string("((java.lang.Object[]) "),
 	output_rval(Rval),
-	io__write_string("["),
+	io__write_string(")["),
 	output_rval(OffsetRval),
-	io__write_string("]))").
+	io__write_string(" - 1]").   % " - 1" because the field indexes begin
+				     % from 1, but array indexes from 0.
 
 
 
@@ -2553,6 +2638,10 @@
 		[], _), _, _).
 java_builtin_type(Type, "boolean", "java.lang.Boolean", "booleanValue") :-
 	Type = mlds__native_bool_type.
+java_builtin_type(Type, "int", "java.lang.Integer", "intValue") :-
+	Type = mlds__mercury_type(term__functor(term__atom(":"), _, _), _, _),
+	Type = mlds__mercury_type(MercuryType, _, _),
+	type_util__is_dummy_argument_type(MercuryType).
 
 :- pred output_std_unop(builtin_ops__unary_op, mlds__rval, 
 		io__state, io__state).
@@ -2680,7 +2769,9 @@
 	mlds_output_code_addr(CodeAddr, IsCall).
 
 output_rval_const(data_addr_const(DataAddr)) -->
-	mlds_output_data_addr(DataAddr).
+	io__write_string("new "),
+	mlds_output_data_addr(DataAddr),
+	io__write_string("()").
 
 output_rval_const(null(_)) -->
        io__write_string("null").
@@ -2696,9 +2787,9 @@
 		% Not a function call, so we are taking the address of the
 		% wrapper for that function (method).
 		% 
-		io__write_string("AddrOf__"),
+		io__write_string("new AddrOf__"),
 		output_fully_qualified_proc_label(Label, "__"),
-		io__write_string("_0")
+		io__write_string("_0()")
 	;
 		output_fully_qualified_proc_label(Label, ".")
 	).
@@ -2708,11 +2799,11 @@
 		% Not a function call, so we are taking the address of the
 		% wrapper for that function (method).
 		% 
-		io__write_string("AddrOf__"),
+		io__write_string("new AddrOf__"),
 		output_fully_qualified_proc_label(Label, "__"),
 		io__write_string("_"),
 		io__write_int(SeqNum),
-		io__write_string("_0")
+		io__write_string("_0()")
 	;
 		output_fully_qualified_proc_label(Label, "."),
 		io__write_string("_"),
@@ -2730,8 +2821,10 @@
 :- pred mlds_output_data_addr(mlds__data_addr, io__state, io__state).
 :- mode mlds_output_data_addr(in, di, uo) is det.
 
-mlds_output_data_addr(data_addr(ModuleName, DataName)) -->
-	output_module_name(mlds_module_name_to_sym_name(ModuleName)),
+mlds_output_data_addr(data_addr(ModuleQualifier, DataName)) -->
+	{ SymName = mlds_module_name_to_sym_name(ModuleQualifier) },	
+	{ mangle_mlds_sym_name_for_java(SymName, ".", ModuleName) },
+	io__write_string(ModuleName),
 	io__write_string("."),
 	output_data_name(DataName).
 
Index: java/Commit.java
===================================================================
RCS file: java/Commit.java
diff -N java/Commit.java
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ java/Commit.java	6 Feb 2002 04:33:43 -0000
@@ -0,0 +1,14 @@
+//
+// Copyright (C) 2002 The 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.
+//
+// This is a throwable class used for the Java implementation of commits.
+// 
+
+package mercury.runtime;
+
+public class Commit extends java.lang.Error {
+
+}
+
Index: java/Compare.java
===================================================================
RCS file: java/Compare.java
diff -N java/Compare.java
--- java/Compare.java	23 Feb 2001 01:11:02 -0000	1.1
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,17 +0,0 @@
-//
-// Copyright (C) 2001 The 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.
-//
-// This interface is implemented by classes that are wrapped around the
-// `compare' special predicate.  Instantitions of those classes are then
-// used as entries in the TypeCtorInfo_Struct's.
-//
-
-package mercury.runtime;
-
-public interface Compare {
-	public abstract mercury.Builtin.comparison_result_0 call(
-			java.lang.Object[] args); 
-}
-
Index: java/ProcAddr.java
===================================================================
RCS file: java/ProcAddr.java
diff -N java/ProcAddr.java
--- java/ProcAddr.java	23 Feb 2001 01:11:02 -0000	1.1
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,18 +0,0 @@
-//
-// Copyright (C) 2001 The 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.
-//
-// This interface is implemented by classes that have been wrapped around
-// any general predicate. We then use instantiations of those classes as
-// pseudo function pointers (which we don't have in Java).  The original
-// predicate can be called via the `call' method.  This interface should
-// not be used for the `compare' and `unify' special predicates as the
-// `Unify' and `Compare' interfaces perform as similar function for them.
-//
-
-package mercury.runtime;
-
-public interface ProcAddr {
-	public abstract java.lang.Object[] call(java.lang.Object[] Args);
-}
Index: java/Unify.java
===================================================================
RCS file: java/Unify.java
diff -N java/Unify.java
--- java/Unify.java	23 Feb 2001 01:11:02 -0000	1.1
+++ /dev/null	1 Jan 1970 00:00:00 -0000
@@ -1,15 +0,0 @@
-//
-// Copyright (C) 2001 The 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.
-//
-// This interface is implemented by classes that are wrapped around the
-// `unify' special predicate.  Instantitions of those classes are then
-// used as entries in the TypeCtorInfo_Struct's.
-//
-
-package mercury.runtime;
-
-public interface Unify {
-	public abstract boolean call(java.lang.Object[] args);
-}

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list