[m-dev.] for review: Java backend

Julien Fischer juliensf at students.cs.mu.oz.au
Wed Feb 14 18:12:29 AEDT 2001


For review by Fergus.

--------------------
Estimated hours taken: 190

Converts MLDS to Java source code.  The following features do not work/
have not been implemented yet:
* RTTI
* multidet and nondet predicates
* Higher-order functions
* Foreign Code
* Correct naming conventions for Java code

compiler/mlds_to_java.m:
Replaces the existing file.

Julien 

Index: compiler/mlds_to_java.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mlds_to_java.m,v
retrieving revision 1.1
diff -u -r1.1 mlds_to_java.m
--- compiler/mlds_to_java.m	2001/01/29 01:50:48	1.1
+++ compiler/mlds_to_java.m	2001/02/14 07:01:20
@@ -6,9 +6,32 @@
 %
 % mlds_to_java - Convert MLDS to Java code.
 % Main author: juliensf 
-% 
-% XXX Not yet implemented.  
+%
+% DONE:
+%	det and semidet predicates
+%	multiple output arguments
+%       boxing and unboxing
+%       conjunctions
+%       disjunctions
+%	if-then-else's
+%       enumerations
+%	discriminated unions
+% TODO: 
+%	multidet and nondet predicates
+%       RTTI
+%	handle foreign code written in Java
+%       higher order functions
+%       generate names of classes etc. correctly 
+% 	generate du constructors instead of directly assigning fields
+%	generate optimized tailcalls
+%       handle foreign code written in C 
+%
+% NOTES: 
+%       Strings in the generated Java source must be fully qualified 
+%       as `java.lang.String' to avoid conflicting with the library module
+%       `mercury.String'.
 %-----------------------------------------------------------------------------%
+
 :- module mlds_to_java.
 :- interface.
 
@@ -21,14 +44,2655 @@
 %-----------------------------------------------------------------------------%
 
 :- implementation.
+
+:- import_module ml_util.
+:- import_module llds.		% XXX needed for C interface types
+:- import_module llds_out.	% XXX needed for llds_out__name_mangle,
+				% llds_out__sym_name_mangle,
+				% llds_out__make_base_typeclass_info_name,
+:- import_module rtti.		% for rtti__addr_to_string.
+:- import_module rtti_to_mlds.	% for mlds_rtti_type_name.
+:- import_module hlds_pred.	% for pred_proc_id.
+:- import_module modules.       % for mercury_std_library_name.
+:- import_module ml_code_util.	% for ml_gen_mlds_var_decl, which is used by
+				% the code that handles derived classes
+:- import_module ml_type_gen.	% for ml_gen_type_name
+:- import_module export.	% for export__type_to_type_string
+:- import_module globals, options, passes_aux.
+:- import_module builtin_ops, c_util, modules.
+:- import_module prog_data, prog_out, type_util, error_util.
+
+:- import_module bool, int, string, library, list.
+:- import_module assoc_list, term, std_util, require.
+
+%-----------------------------------------------------------------------------%
+
+:- type output_type == pred(mlds__type, io__state, io__state).
+:- inst output_type = (pred(in, di, uo) is det).
+
+%-----------------------------------------------------------------------------%
+
+mlds_to_java__output_mlds(MLDS) -->
+	{ ModuleName = mlds__get_module_name(MLDS) },
+	module_name_to_file_name(ModuleName, ".java", yes, SourceFile),
+	{ Indent = 0 },
+	mlds_output_to_file(SourceFile, mlds_output_src_file(Indent, MLDS)).
+
+
+:- pred mlds_output_to_file(string, pred(io__state, io__state),
+				io__state, io__state).
+:- mode mlds_output_to_file(in, pred(di, uo) is det, di, uo) is det.
+
+mlds_output_to_file(FileName, Action) -->
+	globals__io_lookup_bool_option(verbose, Verbose),
+	globals__io_lookup_bool_option(statistics, Stats),
+	maybe_write_string(Verbose, "% Writing to file `"),
+	maybe_write_string(Verbose, FileName),
+	maybe_write_string(Verbose, "'...\n"),
+	maybe_flush_output(Verbose),
+	io__tell(FileName, Res),
+	( { Res = ok } ->
+		Action,
+		io__told,
+		maybe_write_string(Verbose, "% done.\n"),
+		maybe_report_stats(Stats)
+	;
+		maybe_write_string(Verbose, "\n"),
+		{ string__append_list(["can't open file `",
+			FileName, "' for output."], ErrorMessage) },
+		report_error(ErrorMessage)
+	).
+
+%-----------------------------------------------------------------------------%
+%
+% Utility predicates for various purposes. 
+%
+
+	% Succeeds iff the given qualified name is part of the standard
+	% library (as listed in compiler/modules.m).   
+	%
+:- pred qualified_name_is_stdlib(mercury_module_name).
+:- mode qualified_name_is_stdlib(in) is semidet.
+
+qualified_name_is_stdlib(unqualified(_)) :- fail.
+qualified_name_is_stdlib(qualified(Module, Name)) :-
+	 mercury_std_library_module(Name), Module = unqualified("mercury") ;
+	 qualified_name_is_stdlib(Module).
+
+	% Succeeds iff this definition is a function definition which
+	% defines a special predicate.
+	%
+:- pred defn_is_special_pred(mlds__defn).
+:- mode defn_is_special_pred(in) is semidet.
+
+defn_is_special_pred(Defn) :-
+	Defn  = mlds__defn(Name, _Context, _Flags, _Body),
+	Name  = function(Label, _ProcID, _MaybeSeqNum, _PredID),
+	Label = special_pred(_, _, _, _).
+	
+	% Succeeds iff this definition is a data definition which
+	% defines RTTI.
+	%
+:- pred defn_is_rtti_data(mlds__defn).
+:- mode defn_is_rtti_data(in) is semidet.
+
+defn_is_rtti_data(Defn) :-
+	Defn = mlds__defn(_Name, _Context, _Flags, Body),
+	Body = mlds__data(Type, _),
+	Type = mlds__rtti_type(_).
+
+	% Succeeds iff this type is a enumeration.
+	%
+:- pred type_is_enum(mlds__type).
+:- mode type_is_enum(in) is semidet.
+
+type_is_enum(Type) :-
+	Type = mercury_type(_, Builtin),
+	Builtin = enum_type.
+
+	%  Succeeds iff this type is something that 
+	%  the Java backend will represent as an object 
+	%  i.e. something created using the new operator.
+	%
+:- pred type_is_object(mlds__type).
+:- mode type_is_object(in) is semidet.
+
+type_is_object(Type) :-
+	Type = mercury_type(_, Builtin),
+	( Builtin = enum_type 
+	; Builtin = polymorphic_type
+	; Builtin = user_type ).
+
+	% Succeeds iff the Rval represents an integer constant.
+	%
+:- pred rval_is_int_const(mlds__rval).
+:- mode rval_is_int_const(in) is semidet.
+
+rval_is_int_const(Rval) :-
+	Rval = const(Type),
+	Type = int_const(_).
+
+	% Succeeds iff the Rval represents an enumeration
+	% object in the Java backend.
+	%
+:- pred rval_is_enum_var(mlds__rval).
+:- mode rval_is_enum_var(in) is semidet.
+
+rval_is_enum_var(Rval) :-
+	( Rval = lval(Lval),
+	  Lval = var(_, VarType),
+	  type_is_enum(VarType)
+	 ;
+	  Rval = unop(_, Rval1),
+	  rval_is_enum_var(Rval1)
+	).
+	
+	% Returns true iff and only if the string represents a reserved
+	% word in the Java language.
+	% XXX This isn't used yet but should be to prevent reserved words being
+	% used as class names, package names etc.
+	%
+:- pred is_java_keyword(string).
+:- mode is_java_keyword(in) is semidet.
+
+is_java_keyword("abstract").
+is_java_keyword("boolean").
+is_java_keyword("break").
+is_java_keyword("byte").
+is_java_keyword("case").
+is_java_keyword("catch").
+is_java_keyword("char").
+is_java_keyword("class").
+is_java_keyword("const").
+is_java_keyword("continue").
+is_java_keyword("default").
+is_java_keyword("do").
+is_java_keyword("double").
+is_java_keyword("else").
+is_java_keyword("extends").
+is_java_keyword("false").
+is_java_keyword("final").
+is_java_keyword("finally").
+is_java_keyword("float").
+is_java_keyword("for").
+is_java_keyword("goto").
+is_java_keyword("if").
+is_java_keyword("implements").
+is_java_keyword("import").
+is_java_keyword("instanceof").
+is_java_keyword("int").
+is_java_keyword("interface").
+is_java_keyword("long").
+is_java_keyword("native").
+is_java_keyword("new").
+is_java_keyword("null").
+is_java_keyword("package").
+is_java_keyword("private").
+is_java_keyword("protected").
+is_java_keyword("public").
+is_java_keyword("return").
+is_java_keyword("short").
+is_java_keyword("static").
+is_java_keyword("strictfp").
+is_java_keyword("super").
+is_java_keyword("switch").
+is_java_keyword("synchronized").
+is_java_keyword("this").
+is_java_keyword("throw").
+is_java_keyword("throws").
+is_java_keyword("transient").
+is_java_keyword("true").
+is_java_keyword("try").
+is_java_keyword("void").
+is_java_keyword("volatile").
+is_java_keyword("while").
+
+%------------------------------------------------------------------------------%
+%
+% Code to mangle names, enforce Java code conventions regarding class names
+% etc.
+% XXX None of this stuff works as it should. The idea is that class
+% names should be uppercase, while method names and package specifiers
+% should be lowercase.  The current implementation of the MLDS makes
+% this rather harder to achieve than it might initially seem.  The current
+% position is that coding conventions are only enforced on library modules.
+% This is need as Java compilers don't take too well to compiling
+% classes named char, int, float etc.
+% XXX It might be nice if the name mangling code was taken out of which
+% ever LLDS module it's hiding in and put in a seperate one.
+%
+
+	% XXX This won't work if we start using the Java
+	% coding conventions for all names.  At the moment
+	% it only affects library modules.  
+
+:- pred mlds_enforce_java_names(string, string).
+:- mode mlds_enforce_java_names(in, out) is det.
+
+mlds_enforce_java_names(Name, JavaName) :-
+	reverse_string(Name, RevName),
+	( string__sub_string_search(RevName, ".", Pos) ->
+		string__split(RevName, Pos, Head0, Tail0),
+		reverse_string(Tail0, Tail),
+		reverse_string(Head0, Head1),
+		string__capitalize_first(Head1, Head),
+		string__append(Tail, Head, JavaName)
+
+	;
+		reverse_string(RevName, JavaName)
+	).
+
+:- pred reverse_string(string, string).
+:- mode reverse_string(in, out) is det.
+
+reverse_string(In, Out) :-
+	string__to_char_list(In, InList),
+	string__from_rev_char_list(InList, Out).
+	
+:- pred mlds_sym_name_mangle_java(sym_name, string).
+:- mode mlds_sym_name_mangle_java(in, out) is det.
+
+mlds_sym_name_mangle_java(unqualified(Name), MangledName) :-
+	llds_out__name_mangle(Name, MangledName).
+mlds_sym_name_mangle_java(qualified(ModuleName, PlainName), MangledName) :-
+	mlds_sym_name_mangle_java(ModuleName, MangledModuleName),
+	llds_out__name_mangle(PlainName, MangledPlainName),
+	mlds_qualify_mangled_name(MangledModuleName, MangledPlainName, 
+		MangledName).
+
+:- pred mlds_qualify_mangled_name(string, string, string).
+:- mode mlds_qualify_mangled_name(in, in, out) is det.
+
+mlds_qualify_mangled_name(Module0, Name0, Name) :-
+	string__append_list([Module0,".",Name0], Name).
+%----------------------------------------------------------------------------
+%
+% Code to output imports.
+% 
+
+:- pred mlds_output_imports(mlds__imports, io__state, io__state).
+:- mode mlds_output_imports(in, di, uo) is det.
+
+mlds_output_imports(Imports) -->
+	list__foldl(mlds_output_import, Imports),
+	%
+	% We should always import the mercury.runtime classes.
+	%
+	io__write_string("import mercury.runtime.*;\n\n").
+
+:- pred mlds_output_import(mlds__import, io__state, io__state).
+:- mode mlds_output_import(in, di, uo) is det.
+
+mlds_output_import(Import) -->
+	{ SymName = mlds_module_name_to_sym_name(Import) },
+	{ prog_out__sym_name_to_string(SymName, ".", File) }, 
+	( { qualified_name_is_stdlib(SymName) } ->
+		{ mlds_enforce_java_names(File, ClassFile) }
+	;
+		{ ClassFile = File }
+	),
+	io__write_strings(["import ", ClassFile, ";\n"]).
+
+%--------------------------------------------------------------------
+%
+% Code to generate the `.java' file.
+% 
+
+:- pred mlds_output_src_file(indent, mlds, io__state, io__state).
+:- mode mlds_output_src_file(in, in, di, uo) is det.
+
+mlds_output_src_file(Indent, MLDS) -->
+	%
+	% Run further transformations on the MLDS. 
+	%	
+	{ MLDS = mlds(ModuleName, _ForeignCode, Imports, Defns0) },
+	{ MLDS_ModuleName = mercury_module_name_to_mlds(ModuleName) }, 
+	{ Defns1 = Defns0 },
+	% XXX The code to transform special precdicates isn't working yet.
+	% { transform_special_predicates(ModuleName, Defns0, Defns1) },
+	%
+	% Output transformed MLDS as Java souce.  
+	%
+	mlds_output_src_start(Indent, ModuleName, Imports, Defns1), 
+	{ list__filter(defn_is_rtti_data, Defns1, _RttiDefns, NonRttiDefns) },
+	% XXX Need to output RTTI data at this point.
+	mlds_output_defns(Indent + 1, MLDS_ModuleName, NonRttiDefns),
+	mlds_output_src_end(Indent, ModuleName).
+	% XXX Need to handle non-Java foriegn code at this point.
+	
+%------------------------------------------------------------------------------%
+%
+% MLDS->MLDS Transformations 
+%
+
+	% For each Unify and Compare predicate create a class that 
+	% implements either the Unify or Compare interface respectively.  
+	% The call function that is implemented in the class then 
+	% calls Unify and Compare.
+	%
+:- pred transform_special_predicates(mercury_module_name, mlds__defns, 
+		mlds__defns).
+:- mode transform_special_predicates(in, in, out) is det.
+
+transform_special_predicates(ModuleName, Defns0, Defns) :- 
+	list__filter(defn_is_special_pred, Defns0, SpecialPredDefns), 
+	wrap_predicates(ModuleName, SpecialPredDefns, WrappedDefns),
+	list__append(WrappedDefns, Defns0, Defns). 
+
+:- pred wrap_predicates(mercury_module_name, mlds__defns, mlds__defns).
+:- mode wrap_predicates(in, in, out) is det.
+
+wrap_predicates(_, [], []). 
+wrap_predicates(ModuleName, [Defn0 | Defns0], Defns) :-
+	wrap_predicate(ModuleName, Defn0, Defn), 
+	wrap_predicates(ModuleName, Defns0, Defns1),
+	list__append([Defn], Defns1, Defns).
+
+:- pred wrap_predicate(mercury_module_name, mlds__defn, mlds__defn).
+:- mode wrap_predicate(in, in, out) is det.
+
+wrap_predicate(ModuleName, Defn, ClassDefn) :-
+	Defn = mlds__defn(Name, _, _, _),
+	( 
+		Name = function(Label, _, _, _),
+   	 	Label = special_pred(PredName, _, _, _) 
+	  
+	->
+		
+		( PredName = "__Unify__" 
+		
+		-> 
+			InterfaceName = "Unify"
+		
+		; 	PredName = "__Compare__" 
+		
+		->
+			InterfaceName = "Compare"
+		;
+			InterfaceName = ""
+		
+		),
+		InterfaceModuleName = mercury_module_name_to_mlds(
+			qualified(unqualified("mercury"), "runtime")), 
+		Interface = qual(InterfaceModuleName, InterfaceName),
+		%
+		% XXX We don't want to do the transformations on anything other
+		% than Unify and Compare at the moment.
+		% When we support higher order functions this
+		% code will need to support wrapping classes around
+		% normal predicates as well.
+		%	
+		(InterfaceName = "" -> 
+			ClassDefn = Defn
+		;	
+			generate_wrapper_class(ModuleName, Interface, 
+				Defn, ClassDefn)
+		)
+	;
+		error("mlds_to_java.m: mlds_create_special_pred_class")
+	).
+
+:- pred generate_wrapper_class(mercury_module_name, mlds__class,
+	mlds__defn, mlds__defn).
+:- mode generate_wrapper_class(in, in, in, out) is det.
+
+generate_wrapper_class(ModuleName, Interface, MethodDefn, ClassDefn) :-
+	MethodDefn = mlds__defn(Name, Context, _DeclFlags, _DefnBody),
+	( 	
+		Name = function(Label, _ProcID, _MaybeSeqNum, _PredID),
+		Label = special_pred(PredName0, _, Type, Arity)
+	->
+	   
+		%
+		% Create class components. 
+		%
+		ClassImports  = [],
+		ClassExtends = [],
+		InterfaceDefn = mlds__class_type(Interface, 0, mlds__interface),
+		ClassImplements = [InterfaceDefn],
+		%
+		% Create a method that calls the orignal predicate.
+		%
+		generate_wrapper_method(ModuleName, MethodDefn, NewMethodDefn),
+		%
+		% Put it all together
+		%
+		string__append(PredName0, Type, PredName),
+		ClassMembers  = [NewMethodDefn],
+		ClassName     = type(PredName, Arity),
+		ClassContext  = Context,
+		ClassFlags    = ml_gen_type_decl_flags,
+		ClassBodyDefn = mlds__class_defn(mlds__class, ClassImports, 
+			ClassExtends, ClassImplements, ClassMembers),
+		ClassBody     = mlds__class(ClassBodyDefn)
+	;
+
+		error("mlds_to_java: generate_wrapper_class")
+	),
+	ClassDefn = mlds__defn(ClassName, ClassContext, ClassFlags, ClassBody).
+	
+
+:- pred generate_wrapper_method(mercury_module_name, mlds__defn, mlds__defn).
+:- mode generate_wrapper_method(in, in, out) is det.
+
+generate_wrapper_method(ModuleName, Defn0, Defn) :-
+	Defn0 = mlds__defn(Name0, Context, _Flags0, Body0),
+	(
+		Name0 = function(_Label0, ProcID, MaybeSeqNum, PredID),
+		Body0 = mlds__function(MaybeID, Params0, 
+			MaybeStatements0),
+		MaybeStatements0 = yes(Statements0),
+		Statements0 = mlds__statement(
+			block(BlockDefns0, _BlockList0), _) 
+	->
+		%
+		% Create new method name
+		%
+		Label = special_pred("call", no, "", 0),
+		Name = function(Label, ProcID, MaybeSeqNum, PredID),		
+		%
+		% Create new argument.
+		% There is only one as "call" takes an array of Object.
+		%
+	        Arg = data(var("args")) - mlds__array_type(mlds__generic_type),
+		Args = [Arg],
+		%
+		% Create new declarations for old arguments and assign
+		% the new arguments to them in the initializers.
+		%
+		Params0 = mlds__func_params(Args0, RetTypes),
+		generate_wrapper_decls(ModuleName, Context, Args0, 0, 
+			BlockDefns1), 
+		list__append(BlockDefns1, BlockDefns0, BlockDefns),
+		%
+		% Create call to original predicate
+		% XXX Not yet implemented. We need to insert a call
+		% to the original predicate and then return 
+		% what it returns
+		%
+		Block = block(BlockDefns, []),
+		Statements = mlds__statement(Block, Context), 
+		%
+		% Put it all together.
+		%
+		Params = mlds__func_params(Args, RetTypes),
+		Body   = mlds__function(MaybeID, Params, yes(Statements)),
+		Flags  = ml_gen_special_member_decl_flags,	
+		Defn   = mlds__defn(Name, Context, Flags, Body) 
+	;
+		error("mlds_to_java.m: cannot create new method")	
+	).
+	
+	%
+	% Transform a list of function arguments into a list of local
+	% variable declarations of the same name and type.  Create
+	% initializers that initalize each new local variable to the
+	% correct element in the `args' array.
+	%
+:- pred generate_wrapper_decls(mercury_module_name, mlds__context, 
+	mlds__arguments, int, mlds__defns).
+:- mode generate_wrapper_decls(in, in, in, in, out) is det.
+
+generate_wrapper_decls(_, _, [], _, []).
+generate_wrapper_decls(ModuleName, Context, [Arg | Args], Count, Defns) :-
+	Arg = Name - Type,
+	Flags = ml_gen_local_var_decl_flags,
+	string__int_to_string(Count, Index),
+	string__append("args[", Index, UnqualName0),
+	string__append(UnqualName0, "]", UnqualName),
+	NewVarName = qual(mercury_module_name_to_mlds(ModuleName), UnqualName),
+	%		
+	% Package everything together.
+	%
+	NewArgLval = var(NewVarName, mlds__generic_type),
+	Initializer = lval(NewArgLval),
+	Body = mlds__data(Type, init_obj(Initializer)),	
+	Defn = mlds__defn(Name, Context, Flags, Body),
+	%	
+	% Recrusively call ourself to process the next argument.		
+	%
+	generate_wrapper_decls(ModuleName, Context, Args, Count + 1, Defns0),
+	list__append([Defn], Defns0, Defns).
+		
+%------------------------------------------------------------------------------
+%
+% Code to output the start and end of a source file. 
+% 
+
+:- pred mlds_output_src_start(indent, mercury_module_name, mlds__imports, 
+	mlds__defns, io__state, io__state).
+
+:- mode mlds_output_src_start(in, in, in, in, di, uo) is det.
+
+mlds_output_src_start(Indent, ModuleName, Imports, Defns) -->
+	mlds_output_auto_gen_comment(ModuleName),
+	mlds_indent(Indent),
+	io__write_string("/* :- module "),
+	prog_out__write_sym_name(ModuleName),
+	io__write_string(". */\n\n"),
+	mlds_output_package_info(ModuleName),	
+	mlds_output_imports(Imports),
+	io__write_string("public class "),
+	prog_out__write_sym_name(ModuleName),
+	io__write_string(" {\n"),
+	mlds_maybe_write_main_driver(Indent + 1, ModuleName, Defns).
+
+	% Output a `package' directive at the top of the Java source file,
+	% if necessary.
+	%
+:- pred mlds_output_package_info(sym_name, io__state, io__state).
+:- mode mlds_output_package_info(in, di, uo) is det.
+
+mlds_output_package_info(unqualified(_)) --> [].
+mlds_output_package_info(qualified(Module, _)) -->
+	io__write_string("package "),
+	{ prog_out__sym_name_to_string(Module, ".", Package) },
+	io__write_string(Package),
+	io__write_string(";\n").
+
+	% Check if this module contains a main predicate and if it does insert
+	% a dummy main function in the resulting Java class that calls 
+	% the main predicate. Save the command line arguments in the class 
+	% variable `args' in the class `mercury.runtime.JavaInternal'.
+	%
+:- pred mlds_maybe_write_main_driver(indent, mercury_module_name,  
+	mlds__defns, io__state, io__state). 
+:- mode mlds_maybe_write_main_driver(in, in, in, di, uo) is det.
+
+mlds_maybe_write_main_driver(Indent, ModuleName, Defns) -->
+	(
+		{ list__member(Defn, Defns) },
+		{ Defn = mlds__defn(Name, _, _, _) },
+		{ Name = function(FuncName, _, _, _) },
+		{ FuncName = pred(predicate, _, "main", 2) } 
+	->
+		mlds_indent(Indent),
+		io__write_string("public static void main"),
+		io__write_string("(java.lang.String[] args)\n"),
+		mlds_indent(Indent),
+		io__write_string("{\n"), 
+		mlds_indent(Indent + 1),	
+		
+		% Save the command line arguments in the class variable
+		% `mercury.runtime.JavaInternal.args'.
+		
+		io__write_string("mercury.runtime.JavaInternal.args = args;\n"),
+		mlds_indent(Indent + 1),
+		prog_out__write_sym_name(ModuleName),
+		io__write_string(".main_2_p_0();\n"),
+		mlds_indent(Indent + 1),
+		io__write_string("return;\n"), 
+		mlds_indent(Indent),
+		io__write_string("}\n") 
+	;
+		[]
+	),
+	io__nl.
+
+:- pred mlds_output_src_end(indent, mercury_module_name, io__state, io__state).
+:- mode mlds_output_src_end(in, in, di, uo) is det.
+
+mlds_output_src_end(Indent, ModuleName) -->
+	io__write_string("}\n"),
+	mlds_indent(Indent),
+	io__write_string("/* :- end_module "),
+	prog_out__write_sym_name(ModuleName),
+	io__write_string(". */\n").
+
+	% Output a Java comment saying that the file was automatically
+	% generated and give details such as the compiler version.
+	%
+:- pred mlds_output_auto_gen_comment(module_name::in,
+		io__state::di, io__state::uo) is det.
+
+mlds_output_auto_gen_comment(ModuleName) --> 
+	{ library__version(Version) },
+	module_name_to_file_name(ModuleName, ".m", no, SourceFileName),
+	io__write_string("/*\n**\n** Automatically generated from "),
+	io__write_string(SourceFileName),
+	io__write_string(" by the Mercury Compiler,\n"),
+	io__write_string("** version "),
+	io__write_string(Version),io__nl,
+	io__write_string("**\n"),
+	io__write_string("*/\n"),
+	io__nl.
+%-----------------------------------------------------------------------------%
+%
+% Code to output declarations and definitions.
+%
+
+:- pred mlds_output_defns(indent, mlds_module_name, mlds__defns,
+		io__state, io__state).
+:- mode mlds_output_defns(in, in, in, di, uo) is det.
+
+mlds_output_defns(Indent, ModuleName, Defns) -->
+	{ OutputDefn = mlds_output_defn(Indent, ModuleName) },
+	list__foldl(OutputDefn, Defns).
+
+:- pred mlds_output_defn(indent, mlds_module_name, mlds__defn,
+		io__state, io__state).
+:- mode mlds_output_defn(in, in, in, di, uo) is det.
+
+mlds_output_defn(Indent, ModuleName, Defn) -->
+	{ Defn = mlds__defn(Name, Context, Flags, DefnBody) },
+	mlds_indent(Context, Indent),
+	mlds_output_decl_flags(Flags, Name),
+	mlds_output_defn_body(Indent, qual(ModuleName, Name), Context,
+		DefnBody).
+
+:- pred mlds_output_defn_body(indent, mlds__qualified_entity_name,
+		mlds__context, mlds__entity_defn, io__state, io__state).
+:- mode mlds_output_defn_body(in, in, in, in, di, uo) is det.
+
+mlds_output_defn_body(_, Name, _, mlds__data(Type, Initializer)) -->
+	mlds_output_data_defn(Name, Type, Initializer).
+mlds_output_defn_body(Indent, Name, Context, 
+		mlds__function(MaybePredProcId, Signature, MaybeBody)) -->
+	mlds_output_maybe(MaybePredProcId, mlds_output_pred_proc_id),
+	mlds_output_func(Indent, Name, Context, Signature, MaybeBody).
+mlds_output_defn_body(Indent, Name, Context, mlds__class(ClassDefn)) -->
+	mlds_output_class(Indent, Name, Context, ClassDefn).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output classes.
+%
+
+:- pred mlds_output_class(indent, mlds__qualified_entity_name, mlds__context,
+		mlds__class_defn, io__state, io__state).
+:- mode mlds_output_class(in, in, in, in, di, uo) is det.
+
+mlds_output_class(Indent, Name, _Context, ClassDefn) -->
+	{ Name = qual(ModuleName, UnqualName) },
+	({ UnqualName = type(_, _) } ->
+		[]	
+	;
+		{error("mlds_to_java.m: mlds_output_class")}
+	),
+	{ ClassDefn = class_defn(Kind, _Imports, BaseClasses, Implements,
+		AllMembers) },
+	( { Kind = mlds__interface } -> 
+		io__write_string("interface ")
+	;
+		io__write_string("class ")
+	),
+	mlds_output_class_name(UnqualName),
+	mlds_output_extends_list(BaseClasses),
+	mlds_output_implements_list(Implements),
+	io__write_string(" {\n"),
+	mlds_output_class_body(Indent + 1, Kind, Name, AllMembers, ModuleName),
+	mlds_indent(Indent),
+	io__write_string("}\n\n").
+
+	% Output superclass that this class extends.  Java does
+	% not support multiple inheritance, so more than one superclass
+	% is an error.
+	%
+:- pred mlds_output_extends_list(list(mlds__class_id), io__state, io__state).
+:- mode mlds_output_extends_list(in, di, uo) is det.
+
+mlds_output_extends_list([]) --> [].
+mlds_output_extends_list([SuperClass]) -->
+	io__write_string(" extends "),
+	mlds_output_type(SuperClass).
+mlds_output_extends_list([_, _ | _]) -->
+	{ error("mlds_to_java.m: multiple inheritance not supported in Java") }.
+
+	% Output list of interfaces that this class implements.
+	%
+:- pred mlds_output_implements_list(list(mlds__interface_id), 
+		io__state, io__state).
+:- mode mlds_output_implements_list(in, di, uo) is det.
+
+mlds_output_implements_list(InterfaceList) --> 
+	( { InterfaceList = [] }  ->
+		[]
+	;
+		io__write_string(" implements "),
+		io__write_list(InterfaceList, ",", mlds_output_interface) 
+	).
+
+:- pred mlds_output_interface(mlds__interface_id, io__state, io__state).
+:- mode mlds_output_interface(in, di, uo) is det.
+
+mlds_output_interface(Interface) -->
+	 ( { Interface = class_type(qual(ModuleQualifier, Name), Arity, _) } ->
+		{ SymName = mlds_module_name_to_sym_name(ModuleQualifier) },	
+		{ mlds_sym_name_mangle_java(SymName, ModuleName) },
+		io__write_string(ModuleName),
+		io__write_string("."),
+		io__write_string(Name),
+		io__write_string("_"),
+		io__write_int(Arity)
+	;
+		{ unexpected(this_file, 
+			"mlds_output_interface: interface was not a class.") }
+	).
+	
+
+:- pred mlds_output_class_body(indent, mlds__class_kind, 
+	mlds__qualified_entity_name, mlds__defns, mlds_module_name, io__state, 
+	io__state).
+:- mode mlds_output_class_body(in, in, in, in, in, di, uo) is det.
+
+mlds_output_class_body(Indent, mlds__class, _Name, AllMembers, Module) -->
+	mlds_output_defns(Indent, Module, AllMembers).	
+
+mlds_output_class_body(_Indent, mlds__package, _Name, _AllMembers, _) -->
+	{ error("mlds_to_java.m: cannot use package as a type.") }.
+
+mlds_output_class_body(Indent, mlds__interface, _, AllMembers, Module) --> 
+	mlds_output_defns(Indent, Module, AllMembers). 
+
+mlds_output_class_body(_Indent, mlds__struct, _, _AllMembers, _) -->	
+	{ error("mlds_to_java.m: structs not supported in Java.") }.
+
+mlds_output_class_body(Indent, mlds__enum, Name, AllMembers, _) -->
+	{ list__filter(defn_is_const, AllMembers, EnumConsts) },
+	{ Name = qual(ModuleName, UnqualName) },
+	mlds_output_enum_constants(Indent + 1, ModuleName, EnumConsts),
+	mlds_indent(Indent + 1),
+	io__write_string("public int value;\n\n"),  
+	mlds_output_enum_ctor(Indent + 1, UnqualName).
+
+%-----------------------------------------------------------------------------%
+%
+% Additional code for generating enumerations
+%
+
+%
+% Enumerations are a bit different from normal classes because although the 
+% ml code generator generates them as classes, it treats them as integers.  
+% Here we treat them as objects (instantiations of the classes) rather than 
+% just integers.  
+%
+
+:- pred defn_is_const(mlds__defn).
+:- mode defn_is_const(in) is semidet.
+
+defn_is_const(Defn) :-
+	Defn = mlds__defn(_Name, _Context, Flags, _DefnBody),
+	constness(Flags) = const.
 	
+	% Output a (Java) constructor for the class representing
+	% the enumeration. 
+	%
+:- pred mlds_output_enum_ctor(indent, mlds__entity_name, io__state, io__state).
+:- mode mlds_output_enum_ctor(in, in, di, uo) is det.
+
+mlds_output_enum_ctor(Indent, UnqualName) -->
+	mlds_indent(Indent),
+	io__write_string("public "),
+	mlds_output_name(UnqualName),
+	io__write_string("(int val) {\n"),
+	mlds_indent(Indent + 1),
+	%	
+	% The use of `value' is hardcoded into ml_type_gen.m.  Any
+	% changes there should probably be reflected here.
 	%
-	% the mlds to java code generator
+	io__write_string("this.value = val;\n"),
+	mlds_indent(Indent + 1),
+	io__write_string("return;\n"),
+	mlds_indent(Indent),
+	io__write_string("}\n").
+		
+:- pred mlds_output_enum_constants(indent, mlds_module_name,
+		mlds__defns, io__state, io__state).
+:- mode mlds_output_enum_constants(in, in, in, di, uo) is det.
+
+mlds_output_enum_constants(Indent, EnumModuleName, EnumConsts) -->
+	io__write_list(EnumConsts, "\n",
+		mlds_output_enum_constant(Indent, EnumModuleName)),
+	io__nl.
+
+:- pred mlds_output_enum_constant(indent, mlds_module_name, mlds__defn,
+		io__state, io__state).
+:- mode mlds_output_enum_constant(in, in, in, di, uo) is det.
+
+mlds_output_enum_constant(Indent, EnumModuleName, Defn) -->
+	{ Defn = mlds__defn(Name, _Context, _Flags, DefnBody) },
+	(
+		{ DefnBody = data(Type, Initializer) }
+	->
+		mlds_indent(Indent),
+		io__write_string("public static final int "),
+		mlds_output_fully_qualified_name(qual(EnumModuleName, Name)),
+		mlds_output_initializer(Type, Initializer),
+		io__write_char(';')
+	;
+		{ error("mlds_to_java.m: mlds_output_enum_constant: definition body was not data.") }
+	).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output data declarations/definitions
+%
+
+:- pred mlds_output_data_decl(mlds__qualified_entity_name, mlds__type,
+			initializer_array_size, io__state, io__state).
+:- mode mlds_output_data_decl(in, in, in, di, uo) is det.
+
+mlds_output_data_decl(Name, Type, InitializerSize) -->
+	mlds_output_data_decl_ho(mlds_output_type,
+			(pred(Tp::in, di, uo) is det -->
+				mlds_output_type_suffix(Tp, InitializerSize)),
+			Name, Type).
+
+:- pred mlds_output_data_decl_ho(output_type, output_type,
+		mlds__qualified_entity_name, mlds__type, io__state, io__state).
+:- mode mlds_output_data_decl_ho(in(output_type), in(output_type),
+		in, in, di, uo) is det.
+
+mlds_output_data_decl_ho(OutputPrefix, OutputSuffix, Name, Type) -->
+	OutputPrefix(Type),
+	io__write_char(' '),
+	mlds_output_fully_qualified_name(Name),
+	OutputSuffix(Type).
+
+:- pred mlds_output_data_defn(mlds__qualified_entity_name, mlds__type,
+			mlds__initializer, io__state, io__state).
+:- mode mlds_output_data_defn(in, in, in, di, uo) is det.
+
+mlds_output_data_defn(Name, Type, Initializer) -->
+	mlds_output_data_decl(Name, Type, initializer_array_size(Initializer)),
+	mlds_output_initializer(Type, Initializer),
+	io__write_string(";\n").
+
+	% We need to provide initializers for local variables
+	% to avoid problems with definite assignment.  This mirrors
+	% the default Java initializers for class and instance variables.
 	%
+:- func get_java_type_initializer(mlds__type) = string.
+:- mode get_java_type_initializer(in) = out is det.
+
+get_java_type_initializer(mercury_type(_, int_type)) = "0".
+get_java_type_initializer(mercury_type(_, char_type)) = "0".
+get_java_type_initializer(mercury_type(_, float_type)) = "0".
+get_java_type_initializer(mercury_type(_, str_type)) = "null".
+get_java_type_initializer(mercury_type(_, pred_type)) = "null".
+get_java_type_initializer(mercury_type(_, tuple_type)) = "null".
+get_java_type_initializer(mercury_type(_, enum_type)) = "null".
+get_java_type_initializer(mercury_type(_, polymorphic_type)) = "null".
+get_java_type_initializer(mercury_type(_, user_type)) = "null".
+get_java_type_initializer(mlds__cont_type(_)) = "null".
+get_java_type_initializer(mlds__commit_type) = "null".
+get_java_type_initializer(mlds__native_bool_type) = "false".
+get_java_type_initializer(mlds__native_int_type) = "0".
+get_java_type_initializer(mlds__native_float_type) = "0".
+get_java_type_initializer(mlds__native_char_type) = "0".
+get_java_type_initializer(mlds__class_type(_, _, _)) = "null".
+get_java_type_initializer(mlds__array_type(_)) = "null".
+get_java_type_initializer(mlds__ptr_type(_)) = "null".
+get_java_type_initializer(mlds__func_type(_)) = "null".
+get_java_type_initializer(mlds__generic_type) = "null".
+get_java_type_initializer(mlds__generic_env_ptr_type) = "null".
+get_java_type_initializer(mlds__pseudo_type_info_type) = "null".
+get_java_type_initializer(mlds__rtti_type(_)) = "null".
+get_java_type_initializer(mlds__unknown_type) = _ :-
+	unexpected(this_file, 
+		"get_type_initializer: variable has unknown_type"). 
+
+:- pred mlds_output_maybe(maybe(T), pred(T, io__state, io__state),
+		io__state, io__state).
+:- mode mlds_output_maybe(in, pred(in, di, uo) is det, di, uo) is det.
+
+mlds_output_maybe(MaybeValue, OutputAction) -->
+	( { MaybeValue = yes(Value) } ->
+		OutputAction(Value)
+	;
+		[]
+	).
+
+:- pred mlds_output_initializer(mlds__type, mlds__initializer,
+		io__state, io__state).
+:- mode mlds_output_initializer(in, in, di, uo) is det.
+
+mlds_output_initializer(Type, Initializer) -->
+	io__write_string(" = "),
+	( { mlds_needs_initialization(Initializer) = yes } ->
+			( { Initializer = init_obj(Rval) }
+			
+			->
+				( 	{ type_is_object(Type),
+					rval_is_int_const(Rval) } 
+				->
+					%
+					% If it is a enumeration object
+					% create new object.
+					%
+					io__write_string("new "),
+					mlds_output_type(Type),
+					io__write_char('('),
+					mlds_output_initializer_body(
+						Initializer),
+					io__write_char(')')
+				;
+					% If it is an non-enumeration
+					% object, insert appropriate
+					% cast.
+					% XXX The logic of this is a bit
+					% wrong.  Fixing it would eliminate
+					% some of the unecessary casting
+					% that happens
+					%
+					io__write_string("("),
+					mlds_output_type(Type),
+					io__write_string(") "),
+					mlds_output_initializer_body(
+						Initializer)
+				)
+			;
+				mlds_output_initializer_body(Initializer)
+			)
+	;
+		%
+		% If we are not provided with an initializer we just, 
+		% supply the default java values -- note: this is strictly
+		% only necessary for local variables, but it's not going
+		% to hurt anything else.  
+		% The reason for doing this is to prevent the Java compiler
+		% failing due to definite assignment.  This happens in
+		% switch statements where the default case is unreachable
+		% and we terminate execution at that point.  The compiler's
+		% definite assignment analysis cannot take this into account
+		% and declares this to be an error.
+		% XXX We should catalog exactly which constructs are causing
+		%     this to happen.
+		% XXX If we ever need to use final local variables this
+		%     will need to be fixed.
+		%
+		io__write_string(get_java_type_initializer(Type))
+	).
+
+:- func mlds_needs_initialization(mlds__initializer) = bool.
+:- mode mlds_needs_initialization(in) = out is det.
+
+mlds_needs_initialization(no_initializer) = no.
+mlds_needs_initialization(init_obj(_)) = yes.
+mlds_needs_initialization(init_struct([])) = no.
+mlds_needs_initialization(init_struct([_|_])) = yes.
+mlds_needs_initialization(init_array(_)) = yes.
+
+:- pred mlds_output_initializer_body( 
+		mlds__initializer, io__state, io__state).
+:- mode mlds_output_initializer_body(in,di, uo) is det.
+
+mlds_output_initializer_body(no_initializer) --> [].
+mlds_output_initializer_body(init_obj(Rval)) -->
+	mlds_output_rval_maybe_with_enum(Rval).
+mlds_output_initializer_body(init_struct(FieldInits)) --> 
+	io__write_list(FieldInits, ",\n\t\t", 
+		mlds_output_initializer_body).
+mlds_output_initializer_body(init_array(ElementInits)) -->
+	io__write_string("{\n\t\t"),
+	io__write_list(ElementInits,
+		",\n\t\t", mlds_output_initializer_body),
+	io__write_string("}").
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output function declarations/definitions
+%
 
-mlds_to_java__output_mlds(_MLDS) -->
-	io__stderr_stream(Stream),
-	io__write_string(Stream, "mlds_to_java.m: Java backend not yet implemented.\n").
+:- pred mlds_output_pred_proc_id(pred_proc_id, io__state, io__state).
+:- mode mlds_output_pred_proc_id(in, di, uo) is det.
 
+mlds_output_pred_proc_id(proc(PredId, ProcId)) -->
+	globals__io_lookup_bool_option(auto_comments, AddComments),
+	( { AddComments = yes } ->
+		io__write_string("/* pred_id: "),
+		{ pred_id_to_int(PredId, PredIdNum) },
+		io__write_int(PredIdNum),
+		io__write_string(", proc_id: "),
+		{ proc_id_to_int(ProcId, ProcIdNum) },
+		io__write_int(ProcIdNum),
+		io__write_string(" */\n")
+	;
+		[]
+	).
+
+:- pred mlds_output_func(indent, qualified_entity_name, mlds__context,
+		func_params, maybe(statement), io__state, io__state).
+:- mode mlds_output_func(in, in, in, in, in, di, uo) is det.
+
+mlds_output_func(Indent, Name, Context, Signature, MaybeBody) -->
+	mlds_output_func_decl(Indent, Name, Context, Signature),
+	(
+		{ MaybeBody = no },
+		io__write_string(";\n")
+	;
+		{ MaybeBody = yes(Body) },
+		io__write_string("\n"),
+
+		mlds_indent(Context, Indent),
+		io__write_string("{\n"),
+
+		{ FuncInfo = func_info(Name, Signature) },
+		
+		mlds_output_statement(Indent + 1, FuncInfo, Body),
+
+		mlds_indent(Context, Indent),
+		io__write_string("}\n")	% end the function
+	).
+
+:- pred mlds_output_func_decl(indent, qualified_entity_name, mlds__context,
+		func_params, io__state, io__state).
+:- mode mlds_output_func_decl(in, in, in, in, di, uo) is det.
+
+mlds_output_func_decl(Indent, QualifiedName, Context, Signature) -->
+	mlds_output_func_decl_ho(Indent, QualifiedName, Context, Signature,
+			mlds_output_type, mlds_output_type_suffix).
+
+:- pred mlds_output_func_decl_ho(indent, qualified_entity_name, mlds__context,
+		func_params, output_type, output_type, io__state, io__state).
+:- mode mlds_output_func_decl_ho(in, in, in, in, in(output_type),
+		in(output_type), di, uo) is det.
+
+mlds_output_func_decl_ho(Indent, QualifiedName, Context, Signature,
+		OutputPrefix, OutputSuffix) -->
+	{ Signature = mlds__func_params(Parameters, RetTypes) },
+	( { RetTypes = [] } ->
+		io__write_string("void")
+	; { RetTypes = [RetType] } ->
+		OutputPrefix(RetType)
+	;
+		% for multiple outputs, we return an array of objects.
+		io__write_string("java.lang.Object []")
+	),
+	io__write_char(' '),
+	{ QualifiedName = qual(ModuleName, Name) },
+	mlds_output_name(Name),	
+	mlds_output_params(OutputPrefix, OutputSuffix,
+			Indent, ModuleName, Context, Parameters),
+	( { RetTypes = [RetType2] } ->
+		OutputSuffix(RetType2)
+	;
+		[]
+	).
+
+:- pred mlds_output_params(output_type, output_type,
+		indent, mlds_module_name, mlds__context,
+		mlds__arguments, io__state, io__state).
+:- mode mlds_output_params(in(output_type), in(output_type),
+		in, in, in, in, di, uo) is det.
+
+mlds_output_params(OutputPrefix, OutputSuffix, Indent, ModuleName,
+		Context, Parameters) -->
+	io__write_char('('),
+	( { Parameters = [] } ->
+		[]
+	;
+		io__nl,
+		io__write_list(Parameters, ",\n",
+			mlds_output_param(OutputPrefix, OutputSuffix,
+				Indent + 1, ModuleName, Context))
+	),
+	io__write_char(')').
+
+:- pred mlds_output_param(output_type, output_type,
+		indent, mlds_module_name, mlds__context,
+		pair(mlds__entity_name, mlds__type), io__state, io__state).
+:- mode mlds_output_param(in(output_type), in(output_type),
+		in, in, in, in, di, uo) is det.
+
+mlds_output_param(OutputPrefix, OutputSuffix, Indent,
+		ModuleName, Context, Name - Type) -->
+	mlds_indent(Context, Indent),
+	mlds_output_data_decl_ho(OutputPrefix, OutputSuffix,
+			qual(ModuleName, Name), Type).
+
+:- pred mlds_output_func_type_prefix(func_params, io__state, io__state).
+:- mode mlds_output_func_type_prefix(in, di, uo) is det.
+
+mlds_output_func_type_prefix(Params) -->
+	{ Params = mlds__func_params(_Parameters, RetTypes) },
+	( { RetTypes = [] } ->
+		io__write_string("void")
+	; { RetTypes = [RetType] } ->
+		mlds_output_type(RetType)
+	;
+		{ error("mlds_output_func_type_prefix: multiple return types") }
+	).
+
+:- pred mlds_output_func_type_suffix(func_params, io__state, io__state).
+:- mode mlds_output_func_type_suffix(in, di, uo) is det.
+
+mlds_output_func_type_suffix(Params) -->
+	{ Params = mlds__func_params(Parameters, _RetTypes) },
+	io__write_string(")"),
+	mlds_output_param_types(Parameters).
+
+:- pred mlds_output_param_types(mlds__arguments, io__state, io__state).
+:- mode mlds_output_param_types(in, di, uo) is det.
+
+mlds_output_param_types(Parameters) -->
+	io__write_char('('),
+	( { Parameters = [] } ->
+		io__write_string("void")
+	;
+		io__write_list(Parameters, ", ", mlds_output_param_type)
+	),
+	io__write_char(')').
+
+:- pred mlds_output_param_type(pair(mlds__entity_name, mlds__type),
+		io__state, io__state).
+:- mode mlds_output_param_type(in, di, uo) is det.
+
+mlds_output_param_type(_Name - Type) -->
+	mlds_output_type(Type).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output names of various entities
+% XXX Much of the code in this section will not work when we 
+%     start enforcing names properly.
+
+:- pred mlds_output_fully_qualified_name(mlds__qualified_entity_name,
+		io__state, io__state).
+:- mode mlds_output_fully_qualified_name(in, di, uo) is det.
+
+mlds_output_fully_qualified_name(QualifiedName) -->
+	{ QualifiedName = qual(_ModuleName, Name) },
+	(
+		(
+			{ Name = export(_) } 
+		;
+			{ Name = data(_) }
+		)
+	->
+		mlds_output_name(Name)
+	;
+		mlds_output_fully_qualified(QualifiedName, mlds_output_name)
+	).
+
+:- pred mlds_output_fully_qualified_proc_label(mlds__qualified_proc_label,
+		io__state, io__state).
+:- mode mlds_output_fully_qualified_proc_label(in, di, uo) is det.
+
+mlds_output_fully_qualified_proc_label(QualifiedName) -->
+		mlds_output_fully_qualified(QualifiedName,
+			mlds_output_proc_label).
+
+:- pred mlds_output_fully_qualified(mlds__fully_qualified_name(T),
+		pred(T, io__state, io__state), io__state, io__state).
+:- mode mlds_output_fully_qualified(in, pred(in, di, uo) is det,
+		di, uo) is det.
+
+mlds_output_fully_qualified(qual(ModuleName, Name), OutputFunc) -->
+	{ SymName = mlds_module_name_to_sym_name(ModuleName) },
+	{ mlds_sym_name_mangle_java(SymName, MangledModuleName) },
+	( { qualified_name_is_stdlib(SymName) } ->
+		{ mlds_enforce_java_names(MangledModuleName, JavaMangledName) }
+	;
+		{ MangledModuleName = JavaMangledName }
+	),
+	io__write_string(JavaMangledName),
+	io__write_string("."),
+	OutputFunc(Name).
+
+:- pred mlds_output_module_name(mercury_module_name, io__state, io__state).
+:- mode mlds_output_module_name(in, di, uo) is det.
+
+mlds_output_module_name(ModuleName) -->
+	{ llds_out__sym_name_mangle(ModuleName, MangledModuleName) },
+	io__write_string(MangledModuleName).
+
+:- pred mlds_output_class_name(mlds__entity_name, io__state, io__state).
+:- mode mlds_output_class_name(in, di, uo) is det.
+
+mlds_output_class_name(type(Name, Arity)) -->
+	{ llds_out__name_mangle(Name, MangledName) },
+	io__format("%s_%d", [s(MangledName), i(Arity)]).
+
+mlds_output_class_name(data(_)) --> []. 
+mlds_output_class_name(function(_, _, _, _)) --> [].
+mlds_output_class_name(export(_)) --> [].
+
+:- pred mlds_output_name(mlds__entity_name, io__state, io__state).
+:- mode mlds_output_name(in, di, uo) is det.
+
+mlds_output_name(type(Name, Arity)) -->
+	{ llds_out__name_mangle(Name, MangledName) },
+	io__format("%s_%d", [s(MangledName), i(Arity)]).
+mlds_output_name(data(DataName)) -->
+	mlds_output_data_name(DataName).
+mlds_output_name(function(PredLabel, ProcId, MaybeSeqNum, _PredId)) -->
+	mlds_output_pred_label(PredLabel),
+	{ proc_id_to_int(ProcId, ModeNum) },
+	io__format("_%d", [i(ModeNum)]),
+	( { MaybeSeqNum = yes(SeqNum) } ->
+		io__format("_%d", [i(SeqNum)])
+	;
+		[]
+	).
+mlds_output_name(export(Name)) -->
+	io__write_string(Name).
+
+:- pred mlds_output_pred_label(mlds__pred_label, io__state, io__state).
+:- mode mlds_output_pred_label(in, di, uo) is det.
+
+mlds_output_pred_label(pred(PredOrFunc, MaybeDefiningModule, Name, Arity)) -->
+	( { PredOrFunc = predicate, Suffix = "p" }
+	; { PredOrFunc = function, Suffix = "f" }
+	),
+	{ llds_out__name_mangle(Name, MangledName) },
+	io__format("%s_%d_%s", [s(MangledName), i(Arity), s(Suffix)]),
+	( { MaybeDefiningModule = yes(DefiningModule) } ->
+		io__write_string("_in__"),
+		mlds_output_module_name(DefiningModule)
+	;
+		[]
+	).
+
+mlds_output_pred_label(special_pred(PredName, MaybeTypeModule,
+		TypeName, TypeArity)) -->
+	{ llds_out__name_mangle(PredName, MangledPredName) },
+	{ llds_out__name_mangle(TypeName, MangledTypeName) },
+	io__write_string(MangledPredName),
+	io__write_string("__"),
+	( { MaybeTypeModule = yes(TypeModule) } ->
+		mlds_output_module_name(TypeModule),
+		io__write_string("__")
+	;
+		[]
+	),
+	io__write_string(MangledTypeName),
+	io__write_string("_"),
+	io__write_int(TypeArity).
+
+:- pred mlds_output_data_name(mlds__data_name, io__state, io__state).
+:- mode mlds_output_data_name(in, di, uo) is det.
+
+mlds_output_data_name(var(Name)) -->
+	mlds_output_mangled_name(Name).
+mlds_output_data_name(common(Num)) -->
+	io__write_string("common_"),
+	io__write_int(Num).
+%==============================================================================%
+% XXX Most of this code doesn't yet work/hasn't been implemented in the Java
+% backend.
+%
+mlds_output_data_name(rtti(RttiTypeId, RttiName)) -->
+	{ rtti__addr_to_string(RttiTypeId, RttiName, RttiAddrName) },
+	io__write_string(RttiAddrName).
+mlds_output_data_name(base_typeclass_info(ClassId, InstanceStr)) -->
+        { llds_out__make_base_typeclass_info_name(ClassId, InstanceStr,
+		Name) },
+	io__write_string(Name).
+mlds_output_data_name(module_layout) -->
+	{ error("mlds_to_java.m: NYI: module_layout") }.
+mlds_output_data_name(proc_layout(_ProcLabel)) -->
+	{ error("mlds_to_java.m: NYI: proc_layout") }.
+mlds_output_data_name(internal_layout(_ProcLabel, _FuncSeqNum)) -->
+	{ error("mlds_to_java.m: NYI: internal_layout") }.
+mlds_output_data_name(tabling_pointer(ProcLabel)) -->
+	io__write_string("table_for_"),
+	mlds_output_proc_label(ProcLabel).
+%=============================================================================%
+%-----------------------------------------------------------------------------%
+%
+% Code to output types
+%
+
+:- pred mlds_output_type(mlds__type, io__state, io__state).
+:- mode mlds_output_type(in, di, uo) is det.
+
+mlds_output_type(mercury_type(Type, TypeCategory)) -->
+	mlds_output_mercury_type(Type, TypeCategory).
+mlds_output_type(mlds__native_int_type)   --> io__write_string("int").
+mlds_output_type(mlds__native_float_type) --> io__write_string("double").
+mlds_output_type(mlds__native_bool_type) --> io__write_string("boolean").
+mlds_output_type(mlds__native_char_type)  --> io__write_string("char").
+mlds_output_type(mlds__class_type(Name, Arity, ClassKind)) -->
+	( { ClassKind = mlds__enum } ->
+		mlds_output_fully_qualified(Name, mlds_output_mangled_name),
+		io__format("_%d", [i(Arity)])
+	;
+		mlds_output_fully_qualified(Name, mlds_output_mangled_name),
+		io__format("_%d", [i(Arity)])
+	).
+mlds_output_type(mlds__ptr_type(Type)) -->
+	({ Type = mlds__class_type(Name, Arity, _Kind) } ->
+		mlds_output_fully_qualified(Name, mlds_output_mangled_name),
+		io__format("_%d", [i(Arity)])
+	;
+		mlds_output_type(Type)
+	).
+mlds_output_type(mlds__array_type(Type)) -->
+	mlds_output_type(Type),
+	io__write_string("[]").
+mlds_output_type(mlds__func_type(FuncParams)) -->
+	mlds_output_func_type_prefix(FuncParams).
+mlds_output_type(mlds__generic_type) -->
+	io__write_string("java.lang.Object").	
+mlds_output_type(mlds__generic_env_ptr_type) -->
+	io__write_string("java.lang.Object").
+%==============================================================================%
+% XXX The following code isn't working/hasn't been implemented yet in Java.
+%
+mlds_output_type(mlds__pseudo_type_info_type) -->
+	io__write_string("mercury.runtime.PseudoTypeInfo").
+mlds_output_type(mlds__cont_type(ArgTypes)) -->
+	( { ArgTypes = [] } ->
+		io__write_string("MR_Cont")
+	;
+		% This case only happens for --nondet-copy-out
+		io__write_string("void (*")
+	).
+mlds_output_type(mlds__commit_type) -->
+		io__write_string("__label__").
+%
+% XXX The rtti data should actually be static but it isn't being
+% generated as such.
+%
+mlds_output_type(mlds__rtti_type(RttiName)) -->
+	io__write_string("static mercury.runtime."),
+	io__write_string(mlds_rtti_type_name(RttiName)).
+%==============================================================================%
+mlds_output_type(mlds__unknown_type) -->
+	{ unexpected(this_file, "mlds_output_type: unknown type") }.
+
+:- pred mlds_output_mercury_type(mercury_type, builtin_type,
+		io__state, io__state).
+:- mode mlds_output_mercury_type(in, in, di, uo) is det.
+
+mlds_output_mercury_type(Type, TypeCategory) -->
+	(
+		{ TypeCategory = char_type }, 
+		 io__write_string("char")
+	;
+		{ TypeCategory = int_type }, 
+		 io__write_string("int")
+	;
+		{ TypeCategory = str_type }, 
+		io__write_string("java.lang.String")
+	;
+		{ TypeCategory = float_type }, 
+		io__write_string("double")
+	;
+		{ TypeCategory = polymorphic_type }, 
+		io__write_string("java.lang.Object")
+	;
+		{ TypeCategory = tuple_type }, 
+		io__write_string("java.lang.Object")
+	;
+		% XXX Not yet implemented.
+		{ TypeCategory = pred_type },
+		io__write_string("MR_ClosurePtr")
+	;
+		{ TypeCategory = enum_type },
+		mlds_output_mercury_user_type(Type, TypeCategory)
+	;
+		{ TypeCategory = user_type },
+		mlds_output_mercury_user_type(Type, TypeCategory)
+	).
+
+:- pred mlds_output_mercury_user_type(mercury_type, builtin_type,
+		io__state, io__state).
+:- mode mlds_output_mercury_user_type(in, in, di, uo) is det.
+
+mlds_output_mercury_user_type(Type, TypeCategory) -->
+		( { type_to_type_id(Type, TypeId, _ArgsTypes) } ->
+			{ ml_gen_type_name(TypeId, ClassName, ClassArity) },
+			{ TypeCategory = enum_type ->
+				MLDS_Type = mlds__class_type(ClassName,
+					ClassArity, mlds__enum)
+			;
+				MLDS_Type = mlds__class_type(
+					ClassName, ClassArity, mlds__class)
+			},
+			mlds_output_type(MLDS_Type)
+		;
+			{ error("mlds_output_mercury_user_type") }
+		).
+
+
+	%
+	% XXX This should be renamed, but I'm not sure to what.
+	%
+:- pred mlds_output_type_suffix(mlds__type, io__state, io__state).
+:- mode mlds_output_type_suffix(in, di, uo) is det.
+
+mlds_output_type_suffix(Type) -->
+	mlds_output_type_suffix(Type, no_size).
+
+:- type initializer_array_size
+	--->	array_size(int)
+	;	no_size.	
+
+:- func initializer_array_size(mlds__initializer) = initializer_array_size.
+initializer_array_size(no_initializer) = no_size.
+initializer_array_size(init_obj(_)) = no_size.
+initializer_array_size(init_struct(_)) = no_size.
+initializer_array_size(init_array(Elems)) = array_size(list__length(Elems)).
+
+:- pred mlds_output_type_suffix(mlds__type, initializer_array_size,
+		io__state, io__state).
+:- mode mlds_output_type_suffix(in, in, di, uo) is det.
+
+mlds_output_type_suffix(mercury_type(_, _), _) --> [].
+mlds_output_type_suffix(mlds__native_int_type, _) --> [].
+mlds_output_type_suffix(mlds__native_float_type, _) --> [].
+mlds_output_type_suffix(mlds__native_bool_type, _) --> [].
+mlds_output_type_suffix(mlds__native_char_type, _) --> [].
+mlds_output_type_suffix(mlds__class_type(_, _, _), _) --> [].
+mlds_output_type_suffix(mlds__ptr_type(_), _) --> [].
+mlds_output_type_suffix(mlds__array_type(_), _ArraySize) --> [].
+mlds_output_type_suffix(mlds__func_type(FuncParams), _) -->
+	mlds_output_func_type_suffix(FuncParams).
+mlds_output_type_suffix(mlds__generic_type, _) --> [].
+mlds_output_type_suffix(mlds__generic_env_ptr_type, _) --> [].
+mlds_output_type_suffix(mlds__pseudo_type_info_type, _) --> [].
+mlds_output_type_suffix(mlds__cont_type(ArgTypes), _) -->
+	( { ArgTypes = [] } ->
+		[]
+	;
+		% This case only happens for --nondet-copy-out
+		io__write_string(")("),
+		io__write_list(ArgTypes, ", ", mlds_output_type),
+		io__write_string(")")
+	).
+mlds_output_type_suffix(mlds__commit_type, _) --> [].
+mlds_output_type_suffix(mlds__rtti_type(RttiName), ArraySize) -->
+	( { rtti_name_has_array_type(RttiName) = yes } ->
+		mlds_output_array_type_suffix(ArraySize)
+	;
+		[]
+	).
+mlds_output_type_suffix(mlds__unknown_type, _) -->
+	{ error("mlds_to_java.m: suffix has unknown type") }.
+
+:- pred mlds_output_array_type_suffix(initializer_array_size::in,
+		io__state::di, io__state::uo) is det.
+mlds_output_array_type_suffix(no_size) -->
+	io__write_string("[]").
+mlds_output_array_type_suffix(array_size(_Size)) -->
+	io__write_string("[]").  % For Java we don't need to know the size.
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output declaration specifiers
+%
+
+:- pred mlds_output_decl_flags(mlds__decl_flags, 
+		mlds__entity_name, io__state, io__state).
+:- mode mlds_output_decl_flags(in, in, di, uo) is det.
+
+mlds_output_decl_flags(Flags, _Name) -->
+	mlds_output_access(access(Flags)),
+	mlds_output_per_instance(per_instance(Flags)),
+	mlds_output_virtuality(virtuality(Flags)),
+	mlds_output_finality(finality(Flags)),
+	mlds_output_constness(constness(Flags)),
+	mlds_output_abstractness(abstractness(Flags)).
+
+:- pred mlds_output_access(access, io__state, io__state).
+:- mode mlds_output_access(in, di, uo) is det.
+
+mlds_output_access(public)    --> io__write_string("public ").
+mlds_output_access(private)   --> io__write_string("private ").
+mlds_output_access(protected) --> io__write_string("protected ").
+mlds_output_access(default)   --> []. 
+mlds_output_access(local)     --> [].
+
+:- pred mlds_output_per_instance(per_instance, io__state, io__state).
+:- mode mlds_output_per_instance(in, di, uo) is det.
+
+mlds_output_per_instance(per_instance) --> [].
+mlds_output_per_instance(one_copy)     --> io__write_string("static ").
+
+:- pred mlds_output_virtuality(virtuality, io__state, io__state).
+:- mode mlds_output_virtuality(in, di, uo) is det.
+
+mlds_output_virtuality(virtual)     --> io__write_string("abstract ").
+mlds_output_virtuality(non_virtual) --> [].
+
+:- pred mlds_output_finality(finality, io__state, io__state).
+:- mode mlds_output_finality(in, di, uo) is det.
+
+mlds_output_finality(final)       --> []. 
+mlds_output_finality(overridable) --> [].
+
+:- pred mlds_output_constness(constness, io__state, io__state).
+:- mode mlds_output_constness(in, di, uo) is det.
+
+mlds_output_constness(const)      --> [].
+mlds_output_constness(modifiable) --> [].
+
+:- pred mlds_output_abstractness(abstractness, io__state, io__state).
+:- mode mlds_output_abstractness(in, di, uo) is det.
+
+mlds_output_abstractness(abstract) --> []. 
+mlds_output_abstractness(concrete) --> [].
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output statements
+%
+
+:- type func_info
+	--->	func_info(mlds__qualified_entity_name, mlds__func_params).
+
+:- pred mlds_output_statements(indent, func_info, list(mlds__statement),
+		io__state, io__state).
+:- mode mlds_output_statements(in, in, in, di, uo) is det.
+
+mlds_output_statements(Indent, FuncInfo, Statements) -->
+	list__foldl(mlds_output_statement(Indent, FuncInfo), Statements).
+
+:- pred mlds_output_statement(indent, func_info, mlds__statement,
+		io__state, io__state).
+:- mode mlds_output_statement(in, in, in, di, uo) is det.
+
+mlds_output_statement(Indent, FuncInfo, mlds__statement(Statement, Context)) -->
+	mlds_output_context(Context),
+	mlds_output_stmt(Indent, FuncInfo, Statement, Context).
+
+:- pred mlds_output_stmt(indent, func_info, mlds__stmt, mlds__context,
+		io__state, io__state).
+:- mode mlds_output_stmt(in, in, in, in, di, uo) is det.
+
+	%
+	% sequence
+	%
+mlds_output_stmt(Indent, FuncInfo, block(Defns, Statements), Context) -->
+	mlds_indent(Indent),
+	io__write_string("{\n"),
+	( { Defns \= [] } ->
+		{ FuncInfo = func_info(FuncName, _) },
+		{ FuncName = qual(ModuleName, _) },
+		mlds_output_defns(Indent + 1, ModuleName, Defns),
+		io__write_string("\n")
+	;
+		[]
+	),
+	mlds_output_statements(Indent + 1, FuncInfo, Statements),
+	mlds_indent(Context, Indent),
+	io__write_string("}\n").
+
+	%
+	% iteration
+	%
+mlds_output_stmt(Indent, FuncInfo, while(Cond, Statement, no), _) -->
+	mlds_indent(Indent),
+	io__write_string("while ("),
+	mlds_output_rval(Cond),
+	io__write_string(")\n"),
+	mlds_output_statement(Indent + 1, FuncInfo, Statement).
+mlds_output_stmt(Indent, FuncInfo, while(Cond, Statement, yes), Context) -->
+	mlds_indent(Indent),
+	io__write_string("do\n"),
+	mlds_output_statement(Indent + 1, FuncInfo, Statement),
+	mlds_indent(Context, Indent),
+	io__write_string("while ("),
+	mlds_output_rval(Cond),
+	io__write_string(");\n").
+
+	%
+	% selection (if-then-else)
+	%
+mlds_output_stmt(Indent, FuncInfo, if_then_else(Cond, Then0, MaybeElse),
+		Context) -->
+	%
+	% we need to take care to avoid problems caused by the
+	% dangling else ambiguity
+	%
+	{
+		%
+		% For examples of the form
+		%
+		%	if (...)
+		%		if (...)
+		%			...
+		%	else
+		%		...
+		%
+		% we need braces around the inner `if', otherwise
+		% they wouldn't parse they way we want them to:
+		% Java would match the `else' with the inner `if'
+		% rather than the outer `if'.
+		%
+		MaybeElse = yes(_),
+		Then0 = statement(if_then_else(_, _, no), ThenContext)
+	->
+		Then = statement(block([], [Then0]), ThenContext)
+	;
+		%
+		% For examples of the form
+		%
+		%	if (...)
+		%		if (...)
+		%			...
+		%		else
+		%			...
+		%
+		% we don't _need_ braces around the inner `if',
+		% since Java will match the else with the inner `if'.
+		%
+		MaybeElse = no,
+		Then0 = statement(if_then_else(_, _, yes(_)), ThenContext)
+	->
+		Then = statement(block([], [Then0]), ThenContext)
+	;
+		Then = Then0
+	},
+
+	mlds_indent(Indent),
+	io__write_string("if ("),
+	mlds_output_rval(Cond),
+	io__write_string(")\n"),
+	mlds_output_statement(Indent + 1, FuncInfo, Then),
+	( { MaybeElse = yes(Else) } ->
+		mlds_indent(Context, Indent),
+		io__write_string("else\n"),
+		mlds_output_statement(Indent + 1, FuncInfo, Else)
+	;
+		[]
+	).
+
+
+	%
+	% selection (switch)
+	%
+mlds_output_stmt(Indent, FuncInfo, switch(_Type, Val, _Range, Cases, Default),
+		Context) -->
+	mlds_indent(Context, Indent),
+	io__write_string("switch ("),
+	mlds_output_rval_maybe_with_enum(Val),
+	io__write_string(") {\n"),
+	list__foldl(mlds_output_switch_case(Indent + 1, FuncInfo, Context),
+		Cases),
+	mlds_output_switch_default(Indent + 1, FuncInfo, Context, Default),
+	mlds_indent(Context, Indent),
+	io__write_string("}\n").
+
+	%
+	% transfer of control
+	% 
+mlds_output_stmt(_Indent, _FuncInfo, label(_LabelName), _) --> 
+	{ error("mlds_to_java.m: Labels not supported in Java.") }.
+mlds_output_stmt(_Indent, _FuncInfo, goto(_LabelName), _) --> 
+	{ error("mlds_to_java.m: gotos not supported in Java.") }.
+mlds_output_stmt(_Indent, _FuncInfo, computed_goto(_Expr, _Labels), 
+	_Context) --> 
+	{ error("mlds_to_java.m: computed gotos not supported in Java.") }.
+	
+	%
+	% function call/return
+	%
+mlds_output_stmt(Indent, CallerFuncInfo, Call, Context) -->
+	{ Call = call(Signature, FuncRval, MaybeObject, CallArgs,
+		Results, IsTailCall) },
+	{ CallerFuncInfo = func_info(_Name, _Params) },
+	mlds_indent(Indent),
+	io__write_string("{\n"),
+
+	mlds_indent(Context, Indent + 1),
+	( { Results = [] } ->
+		[]
+	; { Results = [Lval] } ->
+		mlds_output_lval(Lval),
+		io__write_string(" = ")
+	;
+		% for multiple return values,
+		% we generate the following code:
+		%	{ java.lang.Object [] result = <func>(<args>);
+		%	  <output1> = (<type1>) result[0];
+		%	  <output2> = (<type2>) result[1];
+		%	  ...
+		%	}
+		%
+		io__write_string("java.lang.Object [] result = ")
+	),
+	( { MaybeObject = yes(Object) } ->
+		mlds_output_bracketed_rval(Object),
+		io__write_string(".")
+	;
+		[]
+	),
+	mlds_output_bracketed_rval(FuncRval),
+	io__write_string("("),
+	io__write_list(CallArgs, ", ", mlds_output_rval),
+	io__write_string(");\n"),
+
+	( { Results = [_, _ | _] } ->
+		% Copy the results from the "result" array into the Result
+		% lvals (unboxing them as we go).
+		{ Signature = mlds__func_signature(_Arguments, RetTypes) },
+		mlds_output_assign_results(Results, RetTypes, 0,
+			Indent + 1, Context)
+	;
+		[]
+	),
+	( { IsTailCall = tail_call, Results = [] } ->
+		mlds_indent(Context, Indent + 1),
+		io__write_string("return;\n")
+	;
+		[]
+	),
+	mlds_indent(Indent),
+	io__write_string("}\n").
+
+mlds_output_stmt(Indent, FuncInfo, return(Results), _) -->
+	mlds_indent(Indent),
+	io__write_string("return"),
+	( { Results = [] } ->
+		[]
+	; { Results = [Rval] } ->
+		io__write_char(' '),
+		% XXX the ml code generator should not generate these.
+		( { Rval = mlds__lval(Lval),
+		    Lval = var(VarName, _),
+		    VarName = qual(_, UnqualName),
+		    UnqualName = "dummy_var" } 
+		
+		->
+			[]
+		;
+			mlds_output_rval(Rval)
+		)
+	;
+		{ 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_list(TypesAndResults, ",\n ",
+			(pred((Type - Result)::in, di, uo) is det -->
+				mlds_output_boxed_rval(Type, Result))),
+		io__write_string("}")
+	),
+	io__write_string(";\n").
+%=============================================================================%
+% XXX This hasn't been implemented yet in the Java backend.  The code
+%      below is from the C backend.
+
+	%
+	% commits
+	%
+mlds_output_stmt(Indent, _FuncInfo, do_commit(Ref), _) -->
+	mlds_indent(Indent),
+	globals__io_lookup_bool_option(gcc_local_labels, GCC_LocalLabels),
+	( { GCC_LocalLabels = yes } ->
+		% output "goto <Ref>"
+		io__write_string("goto "),
+		mlds_output_rval(Ref)
+	;
+		% output "longjmp(<Ref>, 1)"
+		io__write_string("longjmp("),
+		mlds_output_rval(Ref),
+		io__write_string(", 1)")
+	),
+	io__write_string(";\n").
+mlds_output_stmt(Indent, FuncInfo, try_commit(Ref, Stmt0, Handler), Context) -->
+	globals__io_lookup_bool_option(gcc_local_labels, GCC_LocalLabels),
+	(
+		{ GCC_LocalLabels = yes },
+	
+		% Output the following:
+		%
+		%               <Stmt>
+		%               goto <Ref>_done;
+		%       <Ref>:
+		%               <Handler>
+		%       <Ref>_done:
+		%               ;
+
+		% Note that <Ref> should be just variable name,
+		% not a complicated expression.  If not, the
+		% C compiler will catch it.
+
+		mlds_output_statement(Indent, FuncInfo, Stmt0),
+
+		mlds_indent(Context, Indent),
+		io__write_string("goto "),
+		mlds_output_lval(Ref),
+		io__write_string("_done;\n"),
+
+		mlds_indent(Context, Indent - 1),
+		mlds_output_lval(Ref),
+		io__write_string(":\n"),
+
+		mlds_output_statement(Indent, FuncInfo, Handler),
+
+		mlds_indent(Context, Indent - 1),
+		mlds_output_lval(Ref),
+		io__write_string("_done:\t;\n")
+
+	;
+		{ GCC_LocalLabels = no },
+
+		% Output the following:
+		%
+		%	if (setjmp(<Ref>) == 0)
+		%               <Stmt>
+		%       else
+		%               <Handler>
+
+		%
+		% XXX we need to declare the local variables as volatile,
+		% because of the setjmp()!
+		%
+
+		%
+		% we need to take care to avoid problems caused by the
+		% dangling else ambiguity
+		%
+		{
+			Stmt0 = statement(if_then_else(_, _, no), Context)
+		->
+			Stmt = statement(block([], [Stmt0]), Context)
+		;
+			Stmt = Stmt0
+		},
+
+		mlds_indent(Indent),
+		io__write_string("if (setjmp("),
+		mlds_output_lval(Ref),
+		io__write_string(") == 0)\n"),
+
+		mlds_output_statement(Indent + 1, FuncInfo, Stmt),
+
+		mlds_indent(Context, Indent),
+		io__write_string("else\n"),
+
+		mlds_output_statement(Indent + 1, FuncInfo, Handler)
+	).
+%=============================================================================%
+%-----------------------------------------------------------------------------%
+%
+% When returning multiple values,
+% we generate the following code:
+%	{ java.lang.Object [] result = <func>(<args>);
+%	  <output1> = (<type1>) result[0];
+%	  <output2> = (<type2>) result[1];
+%	  ...
+%	}
+%
+
+% This procedure generates the assignments to the outputs.
+%
+:- pred mlds_output_assign_results(list(mlds__lval), list(mlds__type), int,
+		indent, mlds__context, io__state, io__state).
+:- mode mlds_output_assign_results(in, in, in, in, in, di, uo) is det.
+
+mlds_output_assign_results([], [], _, _, _) --> [].
+mlds_output_assign_results([Lval|Lvals], [Type|Types], ResultIndex,
+		Indent, Context) -->
+	mlds_indent(Context, Indent),
+	mlds_output_lval(Lval),
+	io__write_string(" = "),
+	mlds_output_unboxed_result(Type, ResultIndex),
+	io__write_string(";\n"),
+	mlds_output_assign_results(Lvals, Types, ResultIndex + 1,
+		Indent, Context).
+mlds_output_assign_results([_|_], [], _, _, _) -->
+	{ error("mlds_output_assign_results: list length mismatch") }.
+mlds_output_assign_results([], [_|_], _, _, _) -->
+	{ error("mlds_output_assign_results: list length mismatch") }.
+				
+:- pred mlds_output_unboxed_result(mlds__type, int, io__state, io__state).
+:- mode mlds_output_unboxed_result(in, in, di, uo) is det.
+
+mlds_output_unboxed_result(Type, ResultIndex) -->
+	(
+		{ java_builtin_type(Type, _JavaName, JavaBoxedName,
+			UnboxMethod) }
+	->
+		io__write_string("(("),
+		io__write_string(JavaBoxedName),
+		io__write_string(") "),
+		io__format("result[%d]).%s()", [i(ResultIndex), s(UnboxMethod)])
+	;
+		io__write_string("("),
+		mlds_output_type(Type),
+		io__write_string(") "),
+		io__format("result[%d]", [i(ResultIndex)])
+	).
+
+%-----------------------------------------------------------------------------%
+%
+% Extra code for outputting switch statements
+%
+
+:- pred mlds_output_switch_case(indent, func_info, mlds__context,
+		mlds__switch_case, io__state, io__state).
+:- mode mlds_output_switch_case(in, in, in, in, di, uo) is det.
+
+mlds_output_switch_case(Indent, FuncInfo, Context, Case) -->
+	{ Case = (Conds - Statement) },
+	list__foldl(mlds_output_case_cond(Indent, Context), Conds),
+	mlds_output_statement(Indent + 1, FuncInfo, Statement),
+	mlds_indent(Context, Indent + 1),
+	io__write_string("break;\n").
+
+:- pred mlds_output_case_cond(indent, mlds__context,
+		mlds__case_match_cond, io__state, io__state).
+:- mode mlds_output_case_cond(in, in, in, di, uo) is det.
+
+mlds_output_case_cond(Indent, Context, match_value(Val)) -->
+	mlds_indent(Context, Indent),
+	io__write_string("case "),
+	mlds_output_rval(Val),
+	io__write_string(":\n").
+mlds_output_case_cond(Indent, Context, match_range(Low, High)) -->
+	% This uses the GNU C extension `case <Low> ... <High>:'.
+	mlds_indent(Context, Indent),
+	io__write_string("case "),
+	mlds_output_rval(Low),
+	io__write_string(" ... "),
+	mlds_output_rval(High),
+	io__write_string(":\n").
+
+:- pred mlds_output_switch_default(indent, func_info, mlds__context,
+		mlds__switch_default, io__state, io__state).
+:- mode mlds_output_switch_default(in, in, in, in, di, uo) is det.
+
+mlds_output_switch_default(Indent, _FuncInfo, Context, default_is_unreachable) -->
+	mlds_indent(Context, Indent),
+	io__write_string("default: /*NOTREACHED*/\n"), 
+	mlds_indent(Context, Indent + 1),
+	io__write_string("java.lang.System.exit(0);\n").
+mlds_output_switch_default(_Indent, _FuncInfo, _Context, default_do_nothing) --> [].
+mlds_output_switch_default(Indent, FuncInfo, Context, default_case(Statement)) -->
+	mlds_indent(Context, Indent),
+	io__write_string("default:\n"),
+	mlds_output_statement(Indent + 1, FuncInfo, Statement).
+
+%-----------------------------------------------------------------------------%
+	%
+	% Does the rval represent a special procedure for which a
+	% code address doesn't exist.
+	%
+:- pred no_code_address(mlds__rval::in) is semidet.
+
+no_code_address(const(code_addr_const(proc(qual(Module, PredLabel - _), _)))) :-
+	SymName = mlds_module_name_to_sym_name(Module),
+	SymName = qualified(unqualified("mercury"), "private_builtin"),
+	PredLabel = pred(predicate, _, "unsafe_type_cast", 2).
+
+%-----------------------------------------------------------------------------%
+
+	%
+	% exception handling
+	%
+
+	/* XXX not yet implemented */
+
+
+	%
+	% atomic statements
+	%
+mlds_output_stmt(Indent, FuncInfo, atomic(AtomicStatement), Context) -->
+	mlds_output_atomic_stmt(Indent, FuncInfo, AtomicStatement, Context).
+
+:- pred mlds_output_label_name(mlds__label, io__state, io__state).
+:- mode mlds_output_label_name(in, di, uo) is det.
+
+mlds_output_label_name(LabelName) -->
+	mlds_output_mangled_name(LabelName).
+
+:- pred mlds_output_atomic_stmt(indent, func_info,
+		mlds__atomic_statement, mlds__context, io__state, io__state).
+:- mode mlds_output_atomic_stmt(in, in, in, in, di, uo) is det.
+
+	%
+	% comments
+	%
+mlds_output_atomic_stmt(Indent, _FuncInfo, comment(Comment), _) -->
+	% XXX we should escape any "*/"'s in the Comment.
+	%     we should also split the comment into lines and indent
+	%     each line appropriately.
+	mlds_indent(Indent),
+	io__write_string("/* "),
+	io__write_string(Comment),
+	io__write_string(" */\n").
+
+	%
+	% assignment
+	%
+mlds_output_atomic_stmt(Indent, _FuncInfo, assign(Lval, Rval), _) -->
+	mlds_indent(Indent),
+	mlds_output_lval(Lval),
+	io__write_string(" = "),
+	( { Lval = var(_, VarType), 
+	    type_is_object(VarType) } 
+	    
+	 ->
+		% If the Lval is a an object.	
+		
+		( { rval_is_int_const(Rval) } ->
+			io__write_string("new "),
+			mlds_output_type(VarType),
+			io__write_string("("),
+			mlds_output_rval(Rval),
+			io__write_string(")")
+		;		
+			%( { rval_is_enum_var(Rval) } ->
+				mlds_output_rval(Rval)
+			%;
+			%	io__write_string("("),
+			%	mlds_output_type(VarType),
+			%	io__write_string(") "),
+			%	mlds_output_rval_maybe_with_enum(Rval)
+			%)
+		)
+	;
+		mlds_output_rval_maybe_with_enum(Rval)
+	),	
+	io__write_string(";\n").
+
+	%
+	% heap management
+	%
+mlds_output_atomic_stmt(_Indent, _FuncInfo, delete_object(_Lval), _) -->
+	{ error("mlds_to_java.m: delete_object not supported in Java.") }.
+
+mlds_output_atomic_stmt(Indent, _FuncInfo, NewObject, Context) -->
+	{ NewObject = new_object(Target, _MaybeTag, Type, _MaybeSize,
+		MaybeCtorName, Args, ArgTypes) },
+	
+	mlds_indent(Indent),
+	io__write_string("{\n"),
+	mlds_indent(Context, Indent + 1),
+	mlds_output_lval(Target),
+	io__write_string(" = new "),
+	%
+	% All derived classes are also static member classes of their
+	% bases classes.  So the correct way to call their constructors
+	% is `<module_name>.<base_class>.<derived_class>()'.
+	% The names of the derived classes are stored in the MaybeCtorName
+	% field.  
+	% XXX We should actually generate (Java) contructors for each class.  
+	% This would make the treatment of discriminated unions more consistent
+	% with the way we treat enumeations.  At the moment we just assign the
+	% values directly to the fields.
+	%
+	( { MaybeCtorName = yes(QualifiedCtorId) } ->
+		mlds_output_type(Type),
+		io__write_char('.'),
+		{ QualifiedCtorId = qual(_ModuleName, CtorDefn) },
+		{ CtorDefn = ctor_id(CtorName, CtorArity) },
+		{ llds_out__name_mangle(CtorName, MangledCtorName) },
+		io__write_string(MangledCtorName),
+		io__write_string("_"),
+		io__write_int(CtorArity)
+	;
+		% XXX This probably isn't right.
+		io__write_string("null"),
+		{ CtorDefn = ctor_id("null", 0) }
+	),
+	io__write_string("();\n"),
+	mlds_output_init_args(Args, ArgTypes, CtorDefn, Context, 0, Target, 0,
+		Indent + 1),
+	mlds_indent(Context, Indent),
+	io__write_string("}\n").
+
+%==============================================================================%
+% XXX This hasn't been implemented yet in the Java backend.  The code
+%      below is from the C backend.
+
+mlds_output_atomic_stmt(Indent, _FuncInfo, mark_hp(Lval), _) -->
+	mlds_indent(Indent),
+	io__write_string("MR_mark_hp("),
+	mlds_output_lval(Lval),
+	io__write_string(");\n").
+
+mlds_output_atomic_stmt(Indent, _FuncInfo, restore_hp(Rval), _) -->
+	mlds_indent(Indent),
+	io__write_string("MR_restore_hp("),
+	mlds_output_rval(Rval),
+	io__write_string(");\n").
+
+	%
+	% trail management
+	%
+mlds_output_atomic_stmt(_Indent, _FuncInfo, trail_op(_TrailOp), _) -->
+	{ error("mlds_to_java.m: sorry, trail_ops not implemented") }.
+%==============================================================================%
+%==============================================================================%
+% XXX This hasn't been implemented yet in the Java backend.  The code
+%      below is from the C backend.
+
+	%
+	% foreign language interfacing
+	%
+mlds_output_atomic_stmt(_Indent, _FuncInfo, 
+	target_code(TargetLang, Components), Context) -->
+
+	( { TargetLang = lang_C } ->
+		list__foldl(
+			mlds_output_target_code_component(Context),
+			Components)
+	;
+		{ error("mlds_to_java.m: sorry, target_code only works for lang_java") }
+	).
+
+:- pred mlds_output_target_code_component(mlds__context, target_code_component,
+		io__state, io__state).
+:- mode mlds_output_target_code_component(in, in, di, uo) is det.
+
+mlds_output_target_code_component(Context,
+		user_target_code(CodeString, MaybeUserContext)) -->
+	( { MaybeUserContext = yes(UserContext) } ->
+		mlds_output_context(mlds__make_context(UserContext))
+	;
+		mlds_output_context(Context)
+	),
+	io__write_string(CodeString),
+	io__write_string("\n").
+mlds_output_target_code_component(Context, raw_target_code(CodeString)) -->
+	mlds_output_context(Context),
+	io__write_string(CodeString).
+mlds_output_target_code_component(Context, target_code_input(Rval)) -->
+	mlds_output_context(Context),
+	mlds_output_rval(Rval),
+	io__write_string("\n").
+mlds_output_target_code_component(Context, target_code_output(Lval)) -->
+	mlds_output_context(Context),
+	mlds_output_lval(Lval),
+	io__write_string("\n").
+mlds_output_target_code_component(_Context, name(Name)) -->
+	% Note: `name(Name)' target_code_components are used to
+	% generate the #define for `MR_PROC_LABEL'.
+	% The fact that they're used in a #define means that we can't do
+	% an mlds_output_context(Context) here, since #line directives
+	% aren't allowed inside #defines.
+	mlds_output_fully_qualified_name(Name),
+	io__write_string("\n").
+%==============================================================================%
+
+	% Output initial values of an object's fields.
+	%
+:- pred mlds_output_init_args(list(mlds__rval), list(mlds__type), mlds__ctor_id, 		mlds__context, int, mlds__lval, mlds__tag, indent, io__state, 
+		io__state).
+:- mode mlds_output_init_args(in, in, in, in, in, in, in, in, di, uo) is det.
+
+mlds_output_init_args([], [], _, _, _, _, _, _) --> [].
+mlds_output_init_args([_|_], [], _, _, _, _, _, _) -->
+	{ error("mlds_output_init_args: length mismatch") }.
+mlds_output_init_args([], [_|_], _, _, _, _, _, _) -->
+	{ error("mlds_output_init_args: length mismatch") }.
+mlds_output_init_args([Arg|Args], [ArgType|ArgTypes], CtorId, Context,
+		ArgNum, Target, Tag, Indent) -->
+	mlds_indent(Context, Indent),
+	( { ArgNum = 0 } ->
+		
+		%
+		% If it's just the data tag, no casting is necessary since
+		% it is a member of the base class anyway.  Note: the
+		% argument number of the data_tag is always going to be
+		% zero as the numbering of other fields starts at 1.
+		%
+		mlds_output_lval(Target),
+		io__write_string(".data_tag = "),
+		mlds_output_rval(Arg)
+	;
+		
+		%
+		% Otherwise do the approriate downcasting to the derived
+		% class
+		%
+		( 
+			{ Target = var(_, TargetType),
+		    	CtorId = ctor_id(CtorName, CtorArity) } 
+		->
+			io__write_string("(("),
+			mlds_output_type(TargetType),
+			io__write_string("."),
+			mlds_output_mangled_name(CtorName),	
+			io__write_string("_"),
+			io__write_int(CtorArity),
+			io__write_string(") "),
+			mlds_output_lval(Target),
+			io__write_string(").F"),
+			io__write_int(ArgNum),	
+			io__write_string(" = "),
+			
+			% If the Target type is the same as the argument
+			% type then we just need to output the rval.
+			% Otherwise we will need to output a boxed rval.
+			% XXX The Context information in the ArgTypes is
+			% not being filled out correctly, which is why
+			% TargetType = ArgType sometimes fails when it
+			% shouldn't.
+			%
+			( 
+				( 
+				    { TargetType = ArgType }
+			  	; 
+			    	    { TargetType = 
+					mercury_type(_, TargetBuiltinType),
+			      	      ArgType = mercury_type(_, ArgBuiltinType),
+			      	      TargetBuiltinType = ArgBuiltinType }
+			  	) 
+			
+			->
+				mlds_output_rval(Arg)
+			;	
+				mlds_output_boxed_rval(ArgType, Arg)
+			)
+		;
+		
+		%
+		% Otherwise don't do the downcasting.
+		%
+		
+			mlds_output_lval(Target),
+			io__write_string(".F"),
+			io__write_int(ArgNum),
+			io__write_string(" = "),
+			mlds_output_rval(Arg)
+		)
+	),
+	io__write_string(";\n"),
+	mlds_output_init_args(Args, ArgTypes, CtorId, Context,
+		ArgNum + 1, Target, Tag, Indent).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to output expressions
+%
+
+:- pred mlds_output_lval(mlds__lval, io__state, io__state).
+:- mode mlds_output_lval(in, di, uo) is det.
+
+mlds_output_lval(field(_MaybeTag, _Rval, offset(_OffsetRval),
+		_FieldType, _ClassType)) -->
+	{ error("mlds_to_java.m : mlds_output_lval") }.
+
+mlds_output_lval(field(_MaybeTag, PtrRval, named_field(FieldName, CtorType),
+		_FieldType, _PtrType)) -->
+	( { FieldName = qual(_, UnqualFieldName), 
+	    llds_out__name_mangle(UnqualFieldName, MangledFieldName),
+	    MangledFieldName = "data_tag" } 
+	
+	->
+		mlds_output_bracketed_rval(PtrRval),
+		io__write_string(".")
+	;
+		io__write_string("(("),
+		mlds_output_type(CtorType),
+		io__write_string(") "),
+		mlds_output_bracketed_rval(PtrRval),  % the actual variable
+		io__write_string(").")
+	),
+	{ FieldName = qual(_, UnqualFieldName) },
+	mlds_output_mangled_name(UnqualFieldName).    % the field name
+
+mlds_output_lval(mem_ref(Rval, _Type)) -->
+	mlds_output_bracketed_rval(Rval).
+
+mlds_output_lval(var(VarName, _VarType)) -->
+	mlds_output_var(VarName).
+
+:- pred mlds_output_var(mlds__var, io__state, io__state).
+:- mode mlds_output_var(in, di, uo) is det.
+
+mlds_output_var(qual(_ModuleName, Name)) -->
+	io__write_string(Name).
+		
+:- pred mlds_output_mangled_name(string, io__state, io__state).
+:- mode mlds_output_mangled_name(in, di, uo) is det.
+
+mlds_output_mangled_name(Name) -->
+	{ llds_out__name_mangle(Name, MangledName) },
+	io__write_string(MangledName).
+
+:- pred mlds_output_bracketed_lval(mlds__lval, io__state, io__state).
+:- mode mlds_output_bracketed_lval(in, di, uo) is det.
+
+mlds_output_bracketed_lval(Lval) -->
+	(
+		% if it's just a variable name, then we don't need parentheses
+		{ Lval = var(_,_) }
+	->
+		mlds_output_lval(Lval)
+	;
+		io__write_char('('),
+		mlds_output_lval(Lval),
+		io__write_char(')')
+	).
+
+:- pred mlds_output_bracketed_rval(mlds__rval, io__state, io__state).
+:- mode mlds_output_bracketed_rval(in, di, uo) is det.
+
+mlds_output_bracketed_rval(Rval) -->
+	(
+		% if it's just a variable name, then we don't need parentheses
+		{ Rval = lval(var(_,_))
+		; Rval = const(code_addr_const(_))
+		}
+	->
+		mlds_output_rval(Rval)
+	;
+		io__write_char('('),
+		mlds_output_rval(Rval),
+		io__write_char(')')
+	).
+
+:- pred mlds_output_rval(mlds__rval, io__state, io__state).
+:- mode mlds_output_rval(in, di, uo) is det.
+
+mlds_output_rval(lval(Lval)) -->
+	mlds_output_lval(Lval).
+		
+mlds_output_rval(mkword(Tag, Rval)) -->
+	io__write_string("(MR_Word) MR_mkword("),
+	mlds_output_tag(Tag),
+	io__write_string(", "),
+	mlds_output_rval(Rval),
+	io__write_string(")").
+
+mlds_output_rval(const(Const)) -->
+	mlds_output_rval_const(Const).
+
+mlds_output_rval(unop(Op, Rval)) -->
+	mlds_output_unop(Op, Rval).
+
+mlds_output_rval(binop(Op, Rval1, Rval2)) -->
+	mlds_output_binop(Op, Rval1, Rval2).
+
+mlds_output_rval(mem_addr(Lval)) -->
+	% XXX the MLDS code generator should probably not generate these
+	% io__write_string("&"),
+	mlds_output_lval(Lval).
+
+:- pred mlds_output_unop(mlds__unary_op, mlds__rval, io__state, io__state).
+:- mode mlds_output_unop(in, in, di, uo) is det.
+	
+mlds_output_unop(cast(Type), Exprn) -->
+	mlds_output_cast_rval(Type, Exprn).
+mlds_output_unop(box(Type), Exprn) -->
+	mlds_output_boxed_rval(Type, Exprn).
+mlds_output_unop(unbox(Type), Exprn) -->
+	mlds_output_unboxed_rval(Type, Exprn).
+mlds_output_unop(std_unop(Unop), Exprn) -->
+	mlds_output_std_unop(Unop, Exprn).
+
+:- pred mlds_output_cast_rval(mlds__type, mlds__rval, io__state, io__state).
+:- mode mlds_output_cast_rval(in, in, di, uo) is det.
+% XXX Putting these casts in seems pointless.	
+mlds_output_cast_rval(_Type, Exprn) -->
+	%io__write_string("("),
+	%mlds_output_type(Type),
+	%io__write_string(") "),
+	mlds_output_rval(Exprn).
+
+:- pred mlds_output_boxed_rval(mlds__type, mlds__rval, io__state, io__state).
+:- mode mlds_output_boxed_rval(in, in, di, uo) is det.
+	
+mlds_output_boxed_rval(Type, Exprn) -->
+	(
+		{ java_builtin_type(Type, _JavaName, JavaBoxedName,
+			_UnboxMethod) }
+	->
+		io__write_string("new "),
+		io__write_string(JavaBoxedName),
+		io__write_string("("),
+		mlds_output_rval(Exprn),
+		io__write_string(")")
+	;
+		io__write_string("((java.lang.Object) ("),
+		mlds_output_rval(Exprn),
+		io__write_string("))")
+	).
+
+:- pred mlds_output_unboxed_rval(mlds__type, mlds__rval, io__state, io__state).
+:- mode mlds_output_unboxed_rval(in, in, di, uo) is det.
+
+mlds_output_unboxed_rval(Type, Exprn) -->
+	(
+		{ java_builtin_type(Type, _JavaName, JavaBoxedName,
+			UnboxMethod) }
+	->
+		io__write_string("(("),
+		io__write_string(JavaBoxedName),
+		io__write_string(") "), 
+		mlds_output_bracketed_rval(Exprn),
+		io__write_string(")."),
+		io__write_string(UnboxMethod),
+		io__write_string("()")
+	;
+		io__write_string("(("),
+		mlds_output_type(Type),
+		io__write_string(") "),
+		mlds_output_rval(Exprn),
+		io__write_string(")")
+	).
+
+	% java_builtin_type(MLDS_Type, JavaUnboxedType, JavaBoxedType,
+	%	UnboxMethod):
+	% For a given Mercury type, check if this corresponds to a
+	% Java type which has both unboxed (builtin) and boxed (class)
+	% versions, and if so, return their names, and the name of
+	% the method to get the unboxed value from the boxed type.
+	%
+:- pred java_builtin_type(mlds__type, string, string, string).
+:- mode java_builtin_type(in, out, out, out) is semidet.
+
+java_builtin_type(Type, "int", "java.lang.Integer", "intValue") :-
+	Type = mlds__native_int_type.
+java_builtin_type(Type, "int", "java.lang.Integer", "intValue") :-
+	Type = mlds__mercury_type(term__functor(term__atom("int"), [], _), _).
+java_builtin_type(Type, "double", "java.lang.Double", "doubleValue") :-
+	Type = mlds__native_float_type.
+java_builtin_type(Type, "double", "java.lang.Double", "doubleValue") :-
+	Type = mlds__mercury_type(term__functor(term__atom("float"),
+		[], _), _).
+java_builtin_type(Type, "char", "java.lang.Character", "charValue") :-
+	Type = mlds__native_char_type.
+java_builtin_type(Type, "char", "java.lang.Character", "charValue") :-
+	Type = mlds__mercury_type(term__functor(term__atom("character"),
+		[], _), _).
+java_builtin_type(Type, "boolean", "java.lang.Boolean", "booleanValue") :-
+	Type = mlds__native_bool_type.
+
+:- pred mlds_output_std_unop(builtin_ops__unary_op, mlds__rval,
+		io__state, io__state).
+:- mode mlds_output_std_unop(in, in, di, uo) is det.
+	
+mlds_output_std_unop(UnaryOp, Exprn) -->
+	{ c_util__unary_prefix_op(UnaryOp, UnaryOpString) },
+	io__write_string(UnaryOpString),
+	io__write_string("("),
+	( { UnaryOp = tag } ->
+		% XXX This is probably not right in the Java backend.
+		% The MR_tag macro requires its argument to be of type 
+		% `MR_Word'.
+		% XXX should we put this cast inside the definition of MR_tag?
+		io__write_string("(MR_Word) ")
+	;
+		[]
+	),
+	mlds_output_rval(Exprn),
+	io__write_string(")").
+
+:- pred mlds_output_binop(binary_op, mlds__rval, mlds__rval,
+			io__state, io__state).
+:- mode mlds_output_binop(in, in, in, di, uo) is det.
+	
+mlds_output_binop(Op, X, Y) -->
+	(
+		{ Op = array_index }
+	->
+		mlds_output_bracketed_rval(X),
+		io__write_string("["),
+		mlds_output_rval(Y),
+		io__write_string("]")
+	;
+		{ c_util__string_compare_op(Op, OpStr) }
+	->
+		mlds_output_rval(X),
+		io__write_string(".equals("),
+		mlds_output_rval(Y),
+		io__write_string(")"),
+		io__write_string(" "),
+		io__write_string(OpStr),
+		io__write_string(" "),
+		io__write_string("true")
+	;
+		( { c_util__float_compare_op(Op, OpStr1) } ->
+			{ OpStr = OpStr1 }
+		; { c_util__float_op(Op, OpStr2) } ->
+			{ OpStr = OpStr2 }
+		;
+			{ fail }
+		)
+	->
+		io__write_string("("),
+		mlds_output_rval_maybe_with_enum(X),
+		io__write_string(" "),
+		io__write_string(OpStr),
+		io__write_string(" "),
+		mlds_output_rval_maybe_with_enum(Y),
+		io__write_string(")")
+	;
+		io__write_string("("),
+		mlds_output_rval_maybe_with_enum(X),
+		io__write_string(" "),
+		mlds_output_binary_op(Op),
+		io__write_string(" "),
+		mlds_output_rval_maybe_with_enum(Y),
+		io__write_string(")")
+	).
+
+	% Output an Rval, if the Rval represents an enumeration object
+	% put in the ".value" so we can access its value.
+	%
+:- pred mlds_output_rval_maybe_with_enum(mlds__rval, io__state, io__state).
+:- mode mlds_output_rval_maybe_with_enum(in, di, uo) is det.
+
+mlds_output_rval_maybe_with_enum(Rval) -->
+	mlds_output_rval(Rval),
+	( { rval_is_enum_var(Rval) } ->
+		io__write_string(".value")
+	;
+		[]
+	).
+
+:- pred mlds_output_binary_op(binary_op, io__state, io__state).
+:- mode mlds_output_binary_op(in, di, uo) is det.
+
+mlds_output_binary_op(Op) -->
+	( { c_util__binary_infix_op(Op, OpStr) } ->
+		io__write_string(OpStr)
+	;
+		{ error("mlds_output_binary_op: invalid binary operator") }
+	).
+
+:- pred mlds_output_rval_const(mlds__rval_const, io__state, io__state).
+:- mode mlds_output_rval_const(in, di, uo) is det.
+
+mlds_output_rval_const(true) -->
+	io__write_string("true").	
+
+mlds_output_rval_const(false) -->
+	io__write_string("false").	
+
+mlds_output_rval_const(int_const(N)) -->
+	io__write_int(N).
+
+mlds_output_rval_const(float_const(FloatVal)) -->
+	io__write_float(FloatVal).
+
+mlds_output_rval_const(string_const(String)) -->
+	io__write_string(""""),
+	c_util__output_quoted_string(String),
+	io__write_string("""").
+
+mlds_output_rval_const(multi_string_const(Length, String)) -->
+	io__write_string(""""),
+	c_util__output_quoted_multi_string(Length, String),
+	io__write_string("""").
+
+mlds_output_rval_const(code_addr_const(CodeAddr)) -->
+	mlds_output_code_addr(CodeAddr).
+
+mlds_output_rval_const(data_addr_const(DataAddr)) -->
+	mlds_output_data_addr(DataAddr).
+
+mlds_output_rval_const(null(_)) -->
+       io__write_string("null").
+
+%-----------------------------------------------------------------------------%
+
+:- pred mlds_output_tag(mlds__tag, io__state, io__state).
+:- mode mlds_output_tag(in, di, uo) is det.
+
+mlds_output_tag(Tag) -->
+	io__write_string("MR_mktag("),
+	io__write_int(Tag),
+	io__write_string(")").
+
+%-----------------------------------------------------------------------------%
+
+:- pred mlds_output_code_addr(mlds__code_addr, io__state, io__state).
+:- mode mlds_output_code_addr(in, di, uo) is det.
+
+mlds_output_code_addr(proc(Label, _Sig)) -->
+	mlds_output_fully_qualified_proc_label(Label).
+mlds_output_code_addr(internal(Label, SeqNum, _Sig)) -->
+	mlds_output_fully_qualified_proc_label(Label),
+	io__write_string("_"),
+	io__write_int(SeqNum).
+
+:- pred mlds_output_proc_label(mlds__proc_label, io__state, io__state).
+:- mode mlds_output_proc_label(in, di, uo) is det.
+
+mlds_output_proc_label(PredLabel - ProcId) -->
+	mlds_output_pred_label(PredLabel),
+	{ proc_id_to_int(ProcId, ModeNum) },
+	io__format("_%d", [i(ModeNum)]).
+
+:- 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)) -->
+	mlds_output_module_name(
+		mlds_module_name_to_sym_name(ModuleName)),
+	io__write_string("."),
+	mlds_output_data_name(DataName).
+
+%-----------------------------------------------------------------------------%
+%
+% Miscellaneous stuff to handle indentation and generation of
+% source context annotations.  (XXX This can probably be simplified
+% since Java doens't have an equivalent of #line directives.)
+%
+
+:- pred mlds_output_context(mlds__context, io__state, io__state).
+:- mode mlds_output_context(in, di, uo) is det.
+
+mlds_output_context(_Context) --> [].
+
+:- pred mlds_indent(mlds__context, indent, io__state, io__state).
+:- mode mlds_indent(in, in, di, uo) is det.
+
+mlds_indent(Context, N) -->
+	mlds_output_context(Context),
+	mlds_indent(N).
+
+% A value of type `indent' records the number of levels
+% of indentation to indent the next piece of code.
+% Currently we output two spaces for each level of indentation.
+% XXX There is a small amount of code duplication with mlds_to_c.m here.
+:- type indent == int.
+
+:- pred mlds_indent(indent, io__state, io__state).
+:- mode mlds_indent(in, di, uo) is det.
+
+mlds_indent(N) -->
+	( { N =< 0 } ->
+		[]
+	;
+		io__write_string("  "),
+		mlds_indent(N - 1)
+	).
+
+:- func this_file = string.
+this_file = "mlds_to_java.m".
+
 :- end_module mlds_to_java.
+
 %-----------------------------------------------------------------------------%



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