[m-dev.] for review: The .NET MSIL backend.

Tyson Dowd trd at cs.mu.OZ.AU
Fri Oct 13 14:09:56 AEDT 2000


> Apart from that, this change looks fine.
> I'd like to see a relative diff for any changes that you make.

Estimated hours taken: 220

The .NET MSIL (Microsoft Intermediate Language) backend. 

While not complete, this backend implements enough of Mercury to run
programs such as eliza (with an appropriate runtime, which is not part
of this change).  The IL backend TODO list is in mlds_to_il.m.

We generate IL "assembler" from MLDS.  The IL assembler (ILASM) then
turns this into bytecode in a .DLL or .EXE file.  

Pragma C code is put into a separate .cpp file and compiled using the managed
C++ compiler.

compiler/il_peephole.m:
	Peephole optimize the IL.

compiler/ilasm.m:
	Generate IL assembler from IL.
	Also a representation of the entities in the IL assembler
	syntax.

compiler/ilds.m:
	The IL instruction set. 

compiler/mercury_compile.m:
	Generate IL if --target il is set.
	Define mercury_compile__mlds_has_main/1.
	Assemble the IL if --target-code-only is not set.
	Use "target_debug" option instead of "c_debug".

compiler/ml_code_gen.m:
	If the target is IL and we are generating MLDS for foreign code
	that calls continuations (that is, model_non pragma C code),
	create a nested function (not implemented in foreign code) to
	call the continuation.  This is because in managed C++ it isn't
	possible to call a continuation, but it's fine to call a method
	written in IL that calls the continuation instead.

compiler/ml_code_util.m:
	Add unexpected/1 as another error message handler.
	Add code for generating indirect calls to success continutation
	(via a nested function).

compiler/ml_elim_nested.m:
	Generate slightly different code for IL environments.  We don't
	use the address of the environment variable (like in the C
	backend) but use the environment variable directly.  We also
	have to initialize the environment as a new object.
	This is because we use a class to represent the environment,
	whereas the C backend uses a struct. 

	Also, if there is no environment required for nested functions
	(that is, the nested functions don't use any of the local
	variables of the parent), don't generate an environment. 
	This is important for the nested functions generated in mangaged
	C++ -- otherwise have to be able to handle defining and
	initializing environments in managed C++ just to do the continuation
	calls for model non pragma C code.

	Add field names to elim_info.

compiler/mlds_to_il.m:
	The IL code generator.	
	Also contains the mapping from MLDS type to IL types (which
	is useful when generating forieng language stubs to interface
	with IL).

compiler/options.m:
	Add a debugging option for IL assember -- it prints out each
	line of assembler before it executes.  This is very much a
	developer only option.
	Make a "target_debug" option -- the old "c_debug" option is just
	an alias for this option.  If the target it IL, "target_debug"
	can also turn on debugging for IL, allowing the IL debugger to
	display IL instructions as it traces execution.


Incremental diff (includes all changes made since original diff was
posted, except for one round of mostly
compiler/notes/compiler_design.html and il_peephole.m changes that has
already been posted in this thread).


diff -u il_peephole.m il_peephole.m
--- il_peephole.m
+++ il_peephole.m
@@ -93,7 +93,7 @@
 	 	Decl0 = Decl 
 	).
 
-:- pred optimize_method_decl(methoddecl::in, methoddecl::out, 
+:- pred optimize_method_decl(method_body_decl::in, method_body_decl::out, 
 	bool::in, bool::out) is det.
 optimize_method_decl(Decl0, Decl, Mod0, Mod) :-
 	( Decl0 = instrs(Instrs0) ->
@@ -162,9 +162,11 @@
 	), Instrs0, PreLabel, NextInstrs0),
 	PreLabel \= [],
 
-	list__filter(equivalent_to_nop, PreLabel, KeepInstrs),
+	list__filter((pred(X::in) is semidet :- equivalent_to_nop(X) = yes), 
+		PreLabel, KeepInstrs),
 	Replacement = list__condense([KeepInstrs,
-			[comment("eliminated instrs after ret"), ret],
+			[comment("peephole -- eliminated instrs after ret"),
+			 ret],
 			NextInstrs0]).
 
 	% A branch to a label that is followed by a return can be reduced
@@ -219,8 +221,8 @@
 		X \= label(_),
 		X \= stloc(Var),
 		X \= stind(_),
-		not can_call(X),
-		not can_branch(X)
+		can_call(X) = no,
+		can_branch(X) = no
 	), Instrs0, PreLdInstrs, [ldloc(Var) | Rest]),
 
 		% Comment and replacement
@@ -295,7 +297,7 @@
 		R0 = Pre0 - Post0,
 		Post0 = InstrIn0,
 		list__takewhile(
-			(pred(X::in) is semidet :- equivalent_to_nop(X)), 
+			(pred(X::in) is semidet :- equivalent_to_nop(X) = yes), 
 			InstrIn0, Pre, MaybePost),
 		MaybePost = [stloc(V) | Post],
 		IsUnusedLocal(V),
@@ -352,9 +354,11 @@
 	Instrs = list__condense([Comments, Replacement, Instrs0]).
 
 	% Any scope without local variables may be eliminated.
-	% XXX we don't do this yet becuase it requires finding the
+	% XXX we don't do this yet because it would requirer finding the
 	% matching end_block and removing it too.  Now that block IDs
-	% are available we can actually do this.
+	% are available we could actually do this, but
+	% currently we don't, because the code below is incomplete.
+	% This procedure is not yet called from anywhere.
 :- pred match4(instr, instrs, instrs).
 :- mode match4(in, in, out) is semidet.
 match4(start_block(scope([]), _), Instrs0, Instrs) :-
@@ -369,51 +373,18 @@
 	% Skip over all the comments.
 :- pred skip_comments(instrs::in, instrs::out, instrs::out) is det.
 
-skip_comments(Instrs0, Instrs1, Comments) :-
-	list__takewhile((pred(X::in) is semidet :- 
-		X = ilds__comment(_)
-	), Instrs0, Comments, Instrs1).
+skip_comments(Instrs0, Instrs, Comments) :-
+        list__takewhile(pred(ilds__comment(_)::in) is semidet,
+	                Instrs0, Comments, Instrs).
 
 	% Skip over all the nop equivalents.
 :- pred skip_nops(instrs::in, instrs::out, instrs::out) is det.
 
-skip_nops(Instrs0, Instrs1, Nops) :-
-	list__takewhile((pred(X::in) is semidet :- 
-		equivalent_to_nop(X)
-	), Instrs0, Nops, Instrs1).
-
-	% These instructions generate no actual code and do not affect
-	% control flow, they are simply part of instr for
-	% convenience.
-:- pred equivalent_to_nop(instr).
-:- mode equivalent_to_nop(in) is semidet.
-equivalent_to_nop(end_block(scope(_), _)).
-equivalent_to_nop(comment(_)).
-equivalent_to_nop(start_block(scope(_), _)).
+skip_nops(Instrs0, Instrs, Nops) :-
+        list__takewhile((pred(X::in) is semidet :- equivalent_to_nop(X) = yes), 
+		Instrs0, Nops, Instrs).
 
-	% These instructions can branch control flow.
-:- pred can_branch(instr).
-:- mode can_branch(in) is semidet.
-can_branch(br(_)).
-can_branch(brtrue(_)).
-can_branch(brfalse(_)).
-can_branch(beq(_)).
-can_branch(bge(_, _)).
-can_branch(bgt(_, _)).
-can_branch(ble(_, _)).
-can_branch(blt(_, _)).
-can_branch(bne(_, _)).
-can_branch(switch(_)).
 
-	% These instructions can make a call
-:- pred can_call(instr).
-:- mode can_call(in) is semidet.
-can_call(call(_)).
-can_call(calli(_)).
-can_call(callvirt(_)).
-can_call(jmp(_)).
-can_call(jmpi).
-can_call(newobj(_)).
 
 	% keep_looking(Producer, Condition, Input, IntermediateResult0, 
 	%	FinalResult, Leftovers) :-
@@ -448,5 +419,328 @@
 
 %-----------------------------------------------------------------------------%
 
+	% These instructions can make a call
+:- func can_call(instr) = bool.
+can_call(call(_)) 				= yes.
+can_call(calli(_)) 				= yes.
+can_call(callvirt(_)) 				= yes.
+can_call(jmp(_)) 				= yes.
+can_call(jmpi) 					= yes.
+can_call(newobj(_))			 	= yes.
+
+can_call(comment(_Comment)) 			= no. 
+can_call(label(_Label)) 			= no. 
+can_call(start_block(_, _Id)) 			= no.
+can_call(end_block(_, _Id)) 			= no.
+can_call(ret) 					= no. 
+can_call((and)) 				= no. 
+can_call(ann_catch) 				= no. 
+can_call(ann_def) 				= no. 
+can_call(ann_lab) 				= no. 
+can_call(arglist) 				= no. 
+can_call(break) 				= no. 
+can_call(ceq) 					= no. 
+can_call(ckfinite) 				= no. 
+can_call(cpblk) 				= no. 
+can_call(dup) 					= no.
+can_call(endcatch) 				= no.
+can_call(endfilter) 				= no. 
+can_call(endfinally) 				= no. 
+can_call(initblk) 				= no. 
+can_call(ldnull) 				= no. 
+can_call(localloc)	 			= no. 
+can_call(neg) 					= no. 
+can_call(nop) 					= no. 
+can_call((not)) 				= no. 
+can_call((or)) 					= no. 
+can_call(pop) 					= no. 
+can_call(shl) 					= no. 
+can_call(tailcall) 				= no. 
+can_call(volatile) 				= no. 
+can_call(xor) 					= no. 
+can_call(entercrit) 				= no. 
+can_call(exitcrit) 				= no.
+can_call(ldlen) 				= no. 
+can_call(throw)	 				= no. 
+can_call(ann_hoisted_call) 			= no.
+can_call(ldarg(_)) 				= no. 
+can_call(ldc(_Type, _Const)) 			= no.
+can_call(ldstr(_String)) 			= no. 
+can_call(add(_Overflow, _Signed)) 		= no. 
+can_call(beq(_Target)) 				= no.
+can_call(bge(_Signed, _Target)) 		= no.
+can_call(bgt(_Signed, _Target)) 		= no. 
+can_call(ble(_Signed, _Target)) 		= no.
+can_call(blt(_Signed, _Target)) 		= no.
+can_call(bne(_Signed, _Target)) 		= no.
+can_call(br(_Target)) 				= no.
+can_call(brfalse(_Target)) 			= no. 
+can_call(brtrue(_Target)) 			= no. 
+can_call(cgt(_Signed)) 				= no.
+can_call(clt(_Signed)) 				= no.
+can_call(conv(_SimpleType)) 			= no. 
+can_call(div(_Signed)) 				= no. 
+can_call(ldarga(_Variable)) 			= no.
+can_call(ldftn(_MethodRef)) 			= no. 
+can_call(ldind(_SimpleType)) 			= no. 
+can_call(ldloc(_Variable)) 			= no. 
+can_call(ldloca(_Variable)) 			= no.
+can_call(leave(_Target)) 			= no. 
+can_call(mul(_Overflow, _Signed)) 		= no. 
+can_call(rem(_Signed)) 				= no. 
+can_call(shr(_Signed)) 				= no. 
+can_call(starg(_Variable)) 			= no.
+can_call(stind(_SimpleType)) 			= no. 
+can_call(stloc(_Variable)) 			= no. 
+can_call(sub(_OverFlow, _Signed)) 		= no. 
+can_call(switch(_)) 				= no.
+can_call(unaligned(_)) 				= no.
+can_call(box(_Type)) 				= no. 
+can_call(castclass(_Type)) 			= no.
+can_call(cpobj(_Type)) 				= no. 
+can_call(initobj(_Type)) 			= no. 
+can_call(isinst(_Type)) 			= no. 
+can_call(ldelem(_SimpleType)) 			= no. 
+can_call(ldelema(_Type)) 			= no. 
+can_call(ldfld(_FieldRef)) 			= no.
+can_call(ldflda(_FieldRef)) 			= no.
+can_call(ldobj(_Type)) 				= no.
+can_call(ldrefany(_Index)) 			= no.
+can_call(ldsfld(_FieldRef)) 			= no. 
+can_call(ldsflda(_FieldRef)) 			= no. 
+can_call(ldtoken(_)) 				= no.
+can_call(ldvirtftn(_MethodRef)) 		= no.
+can_call(mkrefany(_Type)) 			= no.
+can_call(newarr(_Type)) 			= no. 
+can_call(stelem(_SimpleType)) 			= no. 
+can_call(stfld(_FieldRef)) 			= no. 
+can_call(stsfld(_FieldRef)) 			= no. 
+can_call(typerefany(_Index)) 			= no.
+can_call(unbox(_Type)) 				= no.
+can_call(ann_call(_)) 				= no.
+can_call(ann_data(_)) 				= no.
+can_call(ann_dead(_)) 				= no.
+can_call(ann_hoisted(_)) 			= no.
+can_call(ann_live(_)) 				= no.
+can_call(ann_phi(_)) 				= no.
+can_call(ann_ref(_)) 				= no.
 
+	% These instructions generate no actual code and do not affect
+	% control flow, they are simply part of instr for
+	% convenience.
+:- func equivalent_to_nop(instr) = bool.
+equivalent_to_nop(comment(_)) 			= yes.
+equivalent_to_nop(start_block(scope(_), _)) 	= yes.
+equivalent_to_nop(end_block(scope(_), _)) 	= yes.
+equivalent_to_nop(nop) 				= yes. 
+
+equivalent_to_nop(start_block(try, _))			= no.
+equivalent_to_nop(end_block(try, _))			= no.
+equivalent_to_nop(start_block(catch(_), _))		= no.
+equivalent_to_nop(end_block(catch(_), _))		= no.
+equivalent_to_nop(label(_Label)) 			= no. 
+equivalent_to_nop(call(_MethodRef)) 			= no. 
+equivalent_to_nop(calli(_Signature)) 			= no.
+equivalent_to_nop(callvirt(_MethodRef)) 		= no. 
+equivalent_to_nop(ret) 					= no. 
+equivalent_to_nop((and)) 				= no. 
+equivalent_to_nop(ann_catch) 				= no. 
+equivalent_to_nop(ann_def) 				= no. 
+equivalent_to_nop(ann_lab) 				= no. 
+equivalent_to_nop(arglist) 				= no. 
+equivalent_to_nop(break) 				= no. 
+equivalent_to_nop(ceq) 					= no. 
+equivalent_to_nop(ckfinite) 				= no. 
+equivalent_to_nop(cpblk) 				= no. 
+equivalent_to_nop(dup) 					= no.
+equivalent_to_nop(endcatch) 				= no.
+equivalent_to_nop(endfilter) 				= no. 
+equivalent_to_nop(endfinally) 				= no. 
+equivalent_to_nop(initblk) 				= no. 
+equivalent_to_nop(jmpi) 				= no. 
+equivalent_to_nop(ldnull) 				= no. 
+equivalent_to_nop(localloc)	 			= no. 
+equivalent_to_nop(neg) 					= no. 
+equivalent_to_nop((not)) 				= no. 
+equivalent_to_nop((or)) 				= no. 
+equivalent_to_nop(pop) 					= no. 
+equivalent_to_nop(shl) 					= no. 
+equivalent_to_nop(tailcall) 				= no. 
+equivalent_to_nop(volatile) 				= no. 
+equivalent_to_nop(xor) 					= no. 
+equivalent_to_nop(entercrit) 				= no. 
+equivalent_to_nop(exitcrit) 				= no.
+equivalent_to_nop(ldlen) 				= no. 
+equivalent_to_nop(throw) 				= no. 
+equivalent_to_nop(ann_hoisted_call) 			= no.
+equivalent_to_nop(ldarg(_)) 				= no. 
+equivalent_to_nop(ldc(_Type, _Const)) 			= no.
+equivalent_to_nop(ldstr(_String)) 			= no. 
+equivalent_to_nop(add(_Overflow, _Signed)) 		= no. 
+equivalent_to_nop(beq(_Target)) 			= no.
+equivalent_to_nop(bge(_Signed, _Target)) 		= no.
+equivalent_to_nop(bgt(_Signed, _Target)) 		= no. 
+equivalent_to_nop(ble(_Signed, _Target)) 		= no.
+equivalent_to_nop(blt(_Signed, _Target)) 		= no.
+equivalent_to_nop(bne(_Signed, _Target)) 		= no.
+equivalent_to_nop(br(_Target)) 				= no.
+equivalent_to_nop(brfalse(_Target)) 			= no. 
+equivalent_to_nop(brtrue(_Target)) 			= no. 
+equivalent_to_nop(cgt(_Signed)) 			= no.
+equivalent_to_nop(clt(_Signed)) 			= no.
+equivalent_to_nop(conv(_SimpleType)) 			= no. 
+equivalent_to_nop(div(_Signed)) 			= no. 
+equivalent_to_nop(jmp(_MethodRef)) 			= no. 
+equivalent_to_nop(ldarga(_Variable)) 			= no.
+equivalent_to_nop(ldftn(_MethodRef)) 			= no. 
+equivalent_to_nop(ldind(_SimpleType)) 			= no. 
+equivalent_to_nop(ldloc(_Variable)) 			= no. 
+equivalent_to_nop(ldloca(_Variable)) 			= no.
+equivalent_to_nop(leave(_Target)) 			= no. 
+equivalent_to_nop(mul(_Overflow, _Signed)) 		= no. 
+equivalent_to_nop(rem(_Signed)) 			= no. 
+equivalent_to_nop(shr(_Signed)) 			= no. 
+equivalent_to_nop(starg(_Variable)) 			= no.
+equivalent_to_nop(stind(_SimpleType)) 			= no. 
+equivalent_to_nop(stloc(_Variable)) 			= no. 
+equivalent_to_nop(sub(_OverFlow, _Signed)) 		= no. 
+equivalent_to_nop(switch(_)) 				= no.
+equivalent_to_nop(unaligned(_)) 			= no.
+equivalent_to_nop(box(_Type)) 				= no. 
+equivalent_to_nop(castclass(_Type)) 			= no.
+equivalent_to_nop(cpobj(_Type)) 			= no. 
+equivalent_to_nop(initobj(_Type)) 			= no. 
+equivalent_to_nop(isinst(_Type)) 			= no. 
+equivalent_to_nop(ldelem(_SimpleType)) 			= no. 
+equivalent_to_nop(ldelema(_Type)) 			= no. 
+equivalent_to_nop(ldfld(_FieldRef)) 			= no.
+equivalent_to_nop(ldflda(_FieldRef)) 			= no.
+equivalent_to_nop(ldobj(_Type)) 			= no.
+equivalent_to_nop(ldrefany(_Index)) 			= no.
+equivalent_to_nop(ldsfld(_FieldRef)) 			= no. 
+equivalent_to_nop(ldsflda(_FieldRef)) 			= no. 
+equivalent_to_nop(ldtoken(_)) 				= no.
+equivalent_to_nop(ldvirtftn(_MethodRef)) 		= no.
+equivalent_to_nop(mkrefany(_Type)) 			= no.
+equivalent_to_nop(newarr(_Type)) 			= no. 
+equivalent_to_nop(newobj(_MethodRef)) 			= no. 
+equivalent_to_nop(stelem(_SimpleType)) 			= no. 
+equivalent_to_nop(stfld(_FieldRef)) 			= no. 
+equivalent_to_nop(stsfld(_FieldRef)) 			= no. 
+equivalent_to_nop(typerefany(_Index)) 			= no.
+equivalent_to_nop(unbox(_Type)) 			= no.
+equivalent_to_nop(ann_call(_)) 				= no.
+equivalent_to_nop(ann_data(_)) 				= no.
+equivalent_to_nop(ann_dead(_)) 				= no.
+equivalent_to_nop(ann_hoisted(_)) 			= no.
+equivalent_to_nop(ann_live(_)) 				= no.
+equivalent_to_nop(ann_phi(_)) 				= no.
+equivalent_to_nop(ann_ref(_)) 				= no.
+
+
+	% These instructions can branch control flow.
+:- func can_branch(instr) = bool.
+can_branch(br(_)) 					= yes.
+can_branch(brtrue(_))					= yes.
+can_branch(brfalse(_))					= yes.
+can_branch(beq(_))					= yes.
+can_branch(bge(_, _))					= yes.
+can_branch(bgt(_, _))					= yes.
+can_branch(ble(_, _))					= yes.
+can_branch(blt(_, _))					= yes.
+can_branch(bne(_, _))					= yes.
+can_branch(switch(_))					= yes.
+
+can_branch(end_block(_, _)) 				= no.
+can_branch(comment(_)) 					= no.
+can_branch(start_block(_, _)) 				= no.
+can_branch(nop) 					= no. 
+can_branch(label(_Label)) 				= no. 
+can_branch(call(_MethodRef)) 				= no. 
+can_branch(calli(_Signature)) 				= no.
+can_branch(callvirt(_MethodRef)) 			= no. 
+can_branch(ret) 					= no. 
+can_branch((and)) 					= no. 
+can_branch(ann_catch) 					= no. 
+can_branch(ann_def) 					= no. 
+can_branch(ann_lab) 					= no. 
+can_branch(arglist) 					= no. 
+can_branch(break) 					= no. 
+can_branch(ceq) 					= no. 
+can_branch(ckfinite) 					= no. 
+can_branch(cpblk) 					= no. 
+can_branch(dup) 					= no.
+can_branch(endcatch) 					= no.
+can_branch(endfilter) 					= no. 
+can_branch(endfinally) 					= no. 
+can_branch(initblk) 					= no. 
+can_branch(jmpi) 					= no. 
+can_branch(ldnull) 					= no. 
+can_branch(localloc)		 			= no. 
+can_branch(neg) 					= no. 
+can_branch((not)) 					= no. 
+can_branch((or)) 					= no. 
+can_branch(pop) 					= no. 
+can_branch(shl) 					= no. 
+can_branch(tailcall) 					= no. 
+can_branch(volatile) 					= no. 
+can_branch(xor) 					= no. 
+can_branch(entercrit) 					= no. 
+can_branch(exitcrit) 					= no.
+can_branch(ldlen) 					= no. 
+can_branch(throw) 					= no. 
+can_branch(ann_hoisted_call) 				= no.
+can_branch(ldarg(_)) 					= no. 
+can_branch(ldc(_Type, _Const)) 				= no.
+can_branch(ldstr(_String)) 				= no. 
+can_branch(add(_Overflow, _Signed))	 		= no. 
+can_branch(cgt(_Signed)) 				= no.
+can_branch(clt(_Signed)) 				= no.
+can_branch(conv(_SimpleType)) 				= no. 
+can_branch(div(_Signed)) 				= no. 
+can_branch(jmp(_MethodRef)) 				= no. 
+can_branch(ldarga(_Variable)) 				= no.
+can_branch(ldftn(_MethodRef)) 				= no. 
+can_branch(ldind(_SimpleType)) 				= no. 
+can_branch(ldloc(_Variable)) 				= no. 
+can_branch(ldloca(_Variable)) 				= no.
+can_branch(leave(_Target)) 				= no. 
+can_branch(mul(_Overflow, _Signed)) 			= no. 
+can_branch(rem(_Signed)) 				= no. 
+can_branch(shr(_Signed)) 				= no. 
+can_branch(starg(_Variable)) 				= no.
+can_branch(stind(_SimpleType)) 				= no. 
+can_branch(stloc(_Variable)) 				= no. 
+can_branch(sub(_OverFlow, _Signed)) 			= no. 
+can_branch(unaligned(_)) 				= no.
+can_branch(box(_Type)) 					= no. 
+can_branch(castclass(_Type)) 				= no.
+can_branch(cpobj(_Type)) 				= no. 
+can_branch(initobj(_Type)) 				= no. 
+can_branch(isinst(_Type)) 				= no. 
+can_branch(ldelem(_SimpleType)) 			= no. 
+can_branch(ldelema(_Type)) 				= no. 
+can_branch(ldfld(_FieldRef)) 				= no.
+can_branch(ldflda(_FieldRef)) 				= no.
+can_branch(ldobj(_Type)) 				= no.
+can_branch(ldrefany(_Index)) 				= no.
+can_branch(ldsfld(_FieldRef)) 				= no. 
+can_branch(ldsflda(_FieldRef)) 				= no. 
+can_branch(ldtoken(_)) 					= no.
+can_branch(ldvirtftn(_MethodRef)) 			= no.
+can_branch(mkrefany(_Type)) 				= no.
+can_branch(newarr(_Type)) 				= no. 
+can_branch(newobj(_MethodRef)) 				= no. 
+can_branch(stelem(_SimpleType)) 			= no. 
+can_branch(stfld(_FieldRef)) 				= no. 
+can_branch(stsfld(_FieldRef)) 				= no. 
+can_branch(typerefany(_Index)) 				= no.
+can_branch(unbox(_Type)) 				= no.
+can_branch(ann_call(_)) 				= no.
+can_branch(ann_data(_)) 				= no.
+can_branch(ann_dead(_)) 				= no.
+can_branch(ann_hoisted(_)) 				= no.
+can_branch(ann_live(_)) 				= no.
+can_branch(ann_phi(_)) 					= no.
+can_branch(ann_ref(_)) 					= no.
 
diff -u ilasm.m ilasm.m
--- ilasm.m
+++ ilasm.m
@@ -8,6 +8,9 @@
 % Main author: trd.
 %
 %
+% IL assembler syntax is documented in the Microsoft .NET Framework SDK.
+% See ilds.m for links to the documentation.
+%
 % This code is a little messy.  Some of the code here is a hangover from
 % earlier versions of the assembler grammar.
 %
@@ -21,24 +24,19 @@
 
 :- interface.
 
-:- import_module io, list, term, std_util, bool.
+:- import_module io, list, term, std_util, bool, integer.
 :- import_module ilds.
 
 :- pred ilasm__output(
 	list(decl)::in, io__state::di, io__state::uo) is det.
 
-% XXX When representing these types, we just use a convenient Mercury type.
-% If we *really* wanted to support these types we would need to make sure
-% all values of the type can really fit.
-% XXX not all code uses these types yet.  It should.
-
-:- type int64 == int.
-:- type int32 == int.
-:- type int16 == int.
-:- type int8 == int.
-:- type float64 == float.
-:- type float32 == float.
-:- type byte == int.
+:- type int64 ---> int64(integer).
+:- type int32 ---> int32(int).
+:- type int16 ---> int16(int).
+:- type int8  ---> int8(int).
+:- type byte  == int8.
+:- type float64 ---> float64(float).
+:- type float32 ---> float32(float).
 
 % A top level declaration in IL assembler.
 :- type decl
@@ -58,12 +56,12 @@
 		)
 		% .method  (a global function)
 		% there are lots of restriction on global functions so
-		% don't get to excited about using them for anything.
+		% don't get too excited about using them for anything.
 		% In particular, you can't reference a namespace
 		% qualified global function from outside the module.
 	;	method(
 			methodhead,
-			list(methoddecl)
+			method_defn
 		)
 		% .data  (module local data)
 	;	data(
@@ -76,7 +74,6 @@
 		% .assembly extern
 		% declares an assembly name
 	;	extern_assembly(ilds__id)
-			% an assembly declaration
 
 		% .assembly
 		% defines an assembly
@@ -84,14 +81,18 @@
 
 		% comments
 	;	comment_term(term)
+			% print almost anything using pprint__to_doc
+			% (see library/pprint.m for limitations).
 	;	some [T] comment_thing(T)
 	;	comment(string).
 
+	% a method definition is just a list of body decls.
+:- type method_defn == list(method_body_decl).
 
 :- type methodhead 
 	---> methodhead(
 			list(methattr),		% method attributes
-			method_name,		% method name
+			member_name,		% method name
 			signature,		% method signature
 			list(implattr)		% implementation attributes
 	).
@@ -100,7 +101,7 @@
 		% .method (a class method)
 	--->	method(
 			methodhead,		% name, signature, attributes
-			list(methoddecl)	% definition of method
+			method_defn		% definition of method
 		)	
 		% .field (a class field)
 	;	field(
@@ -113,6 +114,8 @@
 		% comments
 	;	comment_term(term)
 	;	comment(string)
+			% print almost anything using pprint__to_doc
+			% (see library/pprint.m for limitations).
 	;	some [T] comment_thing(T).
 
 :- type field_initializer
@@ -124,6 +127,8 @@
 	% but not quite the same as data items. 
 :- type field_init
 	--->	data_item(data_item)		% most data_items are valid
+			% XXX unicode is not yet implemented, don't use
+			% wchar_ptr unless you intend to implement it
 	;	wchar_ptr(string)		% a string to convert to unicode
 	;	binary_float32(int32)		% binary rep. of float
 	;	binary_float64(int64).		% binary rep. of double
@@ -131,19 +136,25 @@
 	% a parent class to extend
 :- type extends 
 	--->	extends(classname)
-	;	noextend.
+	;	extends_nothing.
 
 	% a list of interfaces that we implement
-	% XXX should probably just use an empty list to represent
-	% noimplement
 :- type implements
-	--->	implements(list(classname))
-	;	noimplement. 
+	--->	implements(list(classname)).
 
 	% declarations that can form the body of a method.
-:- type methoddecl 
-	--->	emitbyte(byte)		% raw byte output (danger! danger!)
-	;	maxstack(int)		% maximum stack size (still needed?)
+:- type method_body_decl
+	--->	emitbyte(int32)		% raw byte output (danger! danger!)
+		        % "emits an int32 to the code section of the method"
+			% according to the IL Assembly Language
+			% Programmers' Reference.
+			% This probably means it can output IL
+			% bytecodes.
+	;	maxstack(int32)		% maximum stack size 
+		        % "Defines the maximum size of the stack,
+			% specified by the int32"
+			% But does it measure in bits, nibbles, bytes,
+			% words or something else?
 	;	entrypoint		% is this "main"?
 	;	zeroinit		% initialize locals to zero.
 	;	instrs(list(instr))	% instructions
@@ -189,15 +200,16 @@
 
 	% various constants that can be used in .data declarations
 :- type data_item 
-	---> 	float32(float)
-	;	float64(float)
-	;	int64(int)
-	;	int32(int)
-	;	int16(int)
-	;	int8(int)
+	---> 	float32(float32)
+	;	float64(float64)
+	;	int64(int64)
+	;	int32(int32)
+	;	int16(int16)
+	;	int8(int8)
 	;	char_ptr(string)
 	;	'&'(ilds__id)
-	;	bytearray(list(byte)).	% two digit hex, e.g. 01 F7 0A
+	;	bytearray(list(byte)).	% output as two digit hex, e.g.
+					% 01 F7 0A
 
 
 	% classnames are just structured names.
@@ -205,8 +217,9 @@
 
 :- implementation.
 
-:- import_module require, int, term_io, varset, globals, options, bool.
-:- import_module string, pprint, getopt.
+:- import_module char, string, pprint, getopt.
+:- import_module require, int, term_io, varset, bool.
+:- import_module globals, options.
 
 ilasm__output(Blocks) --> 
 	io__write_list(Blocks, "\n\n", output_decl),
@@ -226,15 +239,15 @@
 	),
 	output_id(Id),
 	(
-		{ Extends = extends(ExtendsModule) }
-	->
+		{ Extends = extends(ExtendsModule) },
 		io__write_string(" extends "),
 		output_classname(ExtendsModule)
 	;
-		[]
+		{ Extends = extends_nothing }
 	),
+	{ Implements = implements(ImplementsList) },
 	(
-		{ Implements = implements(ImplementsList) }
+		{ ImplementsList = [_|_] }
 	->
 		io__write_string(" implements "),
 		io__write_list(ImplementsList, ", ", output_classname)
@@ -254,7 +267,7 @@
 	io__write_string(".method "),
 	output_methodhead(MethodHead),
 	io__write_string(" {\n"),
-	io__write_list(MethodDecls, "\n", output_methoddecl),
+	io__write_list(MethodDecls, "\n", output_method_body_decl),
 	io__write_string("}\n").
 ilasm__output_decl(data(TLS, MaybeId, Body)) --> 
 	io__write_string(".data "),
@@ -283,9 +296,7 @@
 	io__write_string("\n").
 
 ilasm__output_decl(comment(CommentStr)) --> 
-	io__write_string("// "),
-	io__write_string(CommentStr),
-	io__write_string("\n").
+	output_comment_string(CommentStr).
 
 ilasm__output_decl(extern_assembly(AsmName)) --> 
 	io__write_string(".assembly extern "),
@@ -301,33 +312,23 @@
 	io__state::uo) is det.
 
 ilasm__output_classdecl(method(MethodHead, MethodDecls)) -->
-	io__write_string(".method "),
-	output_methodhead(MethodHead),
-
 		% Don't do debug output on class constructors, since
 		% they are automatically generated and take forever to
 		% run.
 	globals__io_lookup_option(debug_il_asm, DebugIlAsm),
 	( { MethodHead = methodhead(_, cctor, _, _) } ->
-		globals__io_set_option(debug_il_asm, bool(no))
-	;
-		[]
-	),
-	io__write_string(" {\n"),
-	io__write_list(MethodDecls, "\n", output_methoddecl),
-	io__write_string("}\n"),
-	( { MethodHead = methodhead(_, cctor, _, _) } ->
+		globals__io_set_option(debug_il_asm, bool(no)),
+		ilasm__output_decl(method(MethodHead, MethodDecls)),
 		globals__io_set_option(debug_il_asm, DebugIlAsm)
 	;
-		[]
+		ilasm__output_decl(method(MethodHead, MethodDecls))
 	).
 
-
 ilasm__output_classdecl(
 		field(FieldAttrs, Type, IlId, MaybeOffset, Initializer)) -->
 	io__write_string(".field "),
 	( { MaybeOffset = yes(Offset) } ->
-		io__write_int(Offset),
+		output_int32(Offset),
 		io__write_string(" ")
 	;
 		[]
@@ -344,9 +345,7 @@
 	output_field_initializer(Initializer).
 
 ilasm__output_classdecl(comment(CommentStr)) --> 
-	io__write_string("// "),
-	io__write_string(CommentStr),
-	io__write_string("\n").
+	output_comment_string(CommentStr).
 
 ilasm__output_classdecl(comment_term(CommentTerm)) --> 
 	io__write_string("// "),
@@ -372,27 +371,27 @@
 	output_name_signature_and_call_conv(Signature, yes(MethodName)),
 	io__write_list(ImplAttrs, " ", io__write).
 
-:- pred ilasm__output_methoddecl(methoddecl::in, io__state::di,
+:- pred ilasm__output_method_body_decl(method_body_decl::in, io__state::di,
 	io__state::uo) is det.
-ilasm__output_methoddecl(emitbyte(Byte)) -->
+ilasm__output_method_body_decl(emitbyte(Int32)) -->
 	io__write_string(".emitbyte "),
-	io__write_int(Byte).
+	output_int32(Int32).
 
-ilasm__output_methoddecl(maxstack(Int)) -->
+ilasm__output_method_body_decl(maxstack(Int32)) -->
 	io__write_string(".maxstack "),
-	io__write_int(Int).
+	output_int32(Int32).
 
-ilasm__output_methoddecl(entrypoint) -->
+ilasm__output_method_body_decl(entrypoint) -->
 	io__write_string(".entrypoint ").
 
-ilasm__output_methoddecl(zeroinit) -->
+ilasm__output_method_body_decl(zeroinit) -->
 	io__write_string(".zeroinit ").
 
-ilasm__output_methoddecl(instrs(Instrs)) -->
+ilasm__output_method_body_decl(instrs(Instrs)) -->
 	output_instructions(Instrs).
 
-ilasm__output_methoddecl(label(Label)) -->
-	io__write_string(Label),
+ilasm__output_method_body_decl(label(Label)) -->
+	output_label(Label),
 	io__write_string(":").
 
 :- pred output_label(label::in, io__state::di, io__state::uo) is det.
@@ -415,7 +414,7 @@
 	).
 
 :- pred output_name_signature_and_call_conv(signature::in,
-	maybe(method_name)::in, io__state::di, io__state::uo) is det.
+	maybe(member_name)::in, io__state::di, io__state::uo) is det.
 output_name_signature_and_call_conv(signature(CallConv, ReturnType,
 		 ArgTypes), MaybeMethodName) -->
 	output_call_conv(CallConv),
@@ -423,7 +422,7 @@
 	output_ret_type(ReturnType),
 	io__write_string(" "),
 	( { MaybeMethodName = yes(MethodName) } ->
-		output_method_name(MethodName)
+		output_member_name(MethodName)
 	;
 		[]
 	),
@@ -431,9 +430,9 @@
 	io__write_list(ArgTypes, ", ", output_param),
 	io__write_string(")").
 
-:- pred output_method_name(method_name::in, io__state::di,
+:- pred output_member_name(member_name::in, io__state::di,
 	 io__state::uo) is det.
-output_method_name(MethodName) -->
+output_member_name(MethodName) -->
 	( { MethodName = ctor },
 		io__write_string(".ctor")
 	; { MethodName = cctor },
@@ -495,9 +494,9 @@
 output_simple_type(interface(Name)) --> 
 	io__write_string("interface "),
 	output_structured_name(Name).
-output_simple_type('[]'(Type, _Bounds)) --> 
+output_simple_type('[]'(Type, Bounds)) --> 
 	output_type(Type),
-	io__write_string("[]").  % XXX we don't output bounds!
+	output_bounds(Bounds).
 output_simple_type('*'(Type)) --> 
 	output_type(Type),
 	io__write_string("*").
@@ -523,9 +522,12 @@
 output_simple_type_opcode(float32) --> io__write_string("r4").
 output_simple_type_opcode(float64) --> io__write_string("r8").
 output_simple_type_opcode(native_float) --> 
-	{ error("unable to create opcode for this simple type") }.
+	{ error("unable to create opcode for native_float") }.
+		% XXX should i4 be used for bool and char? 
 output_simple_type_opcode(bool) --> io__write_string("i4").
 output_simple_type_opcode(char) --> io__write_string("i4").
+
+	% all reference types use "ref" as their opcode.
 output_simple_type_opcode(refany) --> io__write_string("ref").
 output_simple_type_opcode(class(_Name)) --> io__write_string("ref").
 output_simple_type_opcode(value_class(_Name)) --> io__write_string("ref").
@@ -534,6 +536,24 @@
 output_simple_type_opcode('*'(_Type)) --> io__write_string("ref").
 output_simple_type_opcode('&'(_Type)) --> io__write_string("ref").
 
+:- pred output_bounds(bounds::in, io__state::di, io__state::uo) is det.
+output_bounds(Bounds) -->
+	io__write_string("["),
+	io__write_list(Bounds, ", ", output_bound),
+	io__write_string("]").
+
+:- pred output_bound(bound::in, io__state::di, io__state::uo) is det.
+output_bound(upper(X)) --> 
+	io__write_int(X).
+output_bound(lower(X)) --> 
+	io__write_int(X),
+	io__write_string("...").
+output_bound(between(X, Y)) --> 
+	io__write_int(X),
+	io__write_string("..."),
+	io__write_int(Y).
+
+
 
 :- pred output_modifier(ilds__type_modifier::in, io__state::di,
 		io__state::uo) is det.
@@ -598,8 +618,10 @@
 			% We have to quote loadstrings.
 		( { Instr = ldstr(LoadString) } ->
 			io__write_string("ldstr \\"""),
-			term_io__write_escaped_string(LoadString),
+			output_escaped_string(LoadString, """"),
 			io__write_string("\\""")
+				% XXX there could be issues with
+				% comments containing embedded newlines
 		; { Instr = comment(Comment) } ->
 			io__write_string("comment: "),
 			io__write_string(Comment)
@@ -635,8 +657,8 @@
 	io__state::uo) is det.
 
 output_instr(comment(Comment)) --> 
-	io__write_string("// "),
-	io__write_string(Comment).
+	output_comment_string(Comment).
+
 
 output_instr(label(Label)) --> 
 	output_label(Label),
@@ -936,9 +958,6 @@
 	; { Variable = name(Name) }, output_id(Name)
 	).
 
-	% XXX should implement this (although we don't use it).
-output_instr(ldptr(_)) --> { error("output not implemented") }.
-
 output_instr(leave(Target)) --> 
 	io__write_string("leave\t"),
 	output_target(Target).
@@ -1090,10 +1109,10 @@
 
 :- pred output_fieldref(fieldref::in,
 	io__state::di, io__state::uo) is det.
-output_fieldref(fieldref(Type, MemberName)) -->
+output_fieldref(fieldref(Type, ClassMemberName)) -->
 	output_type(Type),
 	io__write_string(" "),
-	output_member_name(MemberName).
+	output_class_member_name(ClassMemberName).
 
 :- pred output_methodref(methodref::in,
 	io__state::di, io__state::uo) is det.
@@ -1111,7 +1130,7 @@
 	io__write_list(ArgTypes, ", ", output_type),
 	io__write_string(")").
 output_methodref(methoddef(call_conv(IsInstance, _), ReturnType, 
-		MemberName, ArgTypes)) -->
+		ClassMemberName, ArgTypes)) -->
 	( { IsInstance = yes } ->
 		io__write_string("instance ")
 	;
@@ -1119,7 +1138,7 @@
 	),
 	output_ret_type(ReturnType),
 	io__write_string(" "),
-	output_member_name(MemberName),
+	output_class_member_name(ClassMemberName),
 	io__write_string("("),
 	io__write_list(ArgTypes, ", ", output_type),
 	io__write_string(")").
@@ -1132,7 +1151,7 @@
 	),
 	output_ret_type(ReturnType),
 	io__write_string(" "),
-	output_method_name(MethodName),
+	output_member_name(MethodName),
 	io__write_string("("),
 	io__write_list(ArgTypes, ", ", output_type),
 	io__write_string(")").
@@ -1141,25 +1160,23 @@
 output_index(Index) -->
 	io__write_int(Index).
 
-	% XXX Should we do our own escaping?
 :- pred output_string_constant(string::in, io__state::di, io__state::uo)
 	is det.
 output_string_constant(String) -->
 	io__write_string(""""),
-	term_io__write_escaped_string(String),  
+	output_escaped_string(String, """"),  
 	io__write_string("""").
 
-
-:- pred output_member_name(member_name::in,
+:- pred output_class_member_name(class_member_name::in,
 	io__state::di, io__state::uo) is det.
-output_member_name(member_name(StructuredName, MethodName)) -->
+output_class_member_name(class_member_name(StructuredName, MemberName)) -->
 	( { StructuredName = [_ | _] } ->
 		output_structured_name(StructuredName),
 		io__write_string("::")
 	;
 		[]
 	),
-	output_method_name(MethodName).
+	output_member_name(MemberName).
 
 
 	% For any "other" modules, we we reference the
@@ -1182,8 +1199,8 @@
 		; { ModuleName = "mercury_base_typeclass_info" } ->
 			{ DottedName = [ModuleName | Rest] }
 		;
-			{ escape_id(ModuleName, EscapedModuleName) },
-			io__format("[%s]", [s(EscapedModuleName)]),
+			{ quote_id(ModuleName, QuotedModuleName) },
+			io__format("[%s]", [s(QuotedModuleName)]),
 			{ DottedName = [ModuleName | Rest] }
 		),
 		output_dotted_name(DottedName)
@@ -1198,8 +1215,8 @@
 
 :- pred output_id(ilds__id::in, io__state::di, io__state::uo) is det.
 output_id(Id) -->
-	{ escape_id(Id, EscapedId) },
-	io__write_string(EscapedId).
+	{ quote_id(Id, QuotedId) },
+	io__write_string(QuotedId).
 
 :- pred output_field_initializer(field_initializer::in, io__state::di,
 	io__state::uo) is det.
@@ -1212,13 +1229,13 @@
 	output_field_init(FieldInit).
 
 :- pred output_field_init(field_init::in, io__state::di, io__state::uo) is det.
-output_field_init(binary_float64(Int)) -->
+output_field_init(binary_float64(Int64)) -->
 	io__write_string("float64("),
-	io__write_int(Int),
+	output_int64(Int64),
 	io__write_string(")").
-output_field_init(binary_float32(Int)) -->
+output_field_init(binary_float32(Int32)) -->
 	io__write_string("float32("),
-	io__write_int(Int),
+	output_int32(Int32),
 	io__write_string(")").
 output_field_init(wchar_ptr(String)) -->
 	io__write_string("wchar *("),
@@ -1244,27 +1261,27 @@
 :- pred output_data_item(data_item::in, io__state::di, io__state::uo) is det.
 output_data_item(float64(Float)) -->
 	io__write_string("float64("),
-	io__write_float(Float),
+	output_float64(Float),
 	io__write_string(")").
-output_data_item(float32(Float)) -->
+output_data_item(float32(Float32)) -->
 	io__write_string("float32("),
-	io__write_float(Float),
+	output_float32(Float32),
 	io__write_string(")").
-output_data_item(int64(Int)) -->
+output_data_item(int64(Int64)) -->
 	io__write_string("int64("),
-	io__write_int(Int),
+	output_int64(Int64),
 	io__write_string(")").
-output_data_item(int32(Int)) -->
+output_data_item(int32(Int32)) -->
 	io__write_string("int32("),
-	io__write_int(Int),
+	output_int32(Int32),
 	io__write_string(")").
-output_data_item(int16(Int)) -->
+output_data_item(int16(Int16)) -->
 	io__write_string("int16("),
-	io__write_int(Int),
+	output_int16(Int16),
 	io__write_string(")").
-output_data_item(int8(Int)) -->
+output_data_item(int8(Int8)) -->
 	io__write_string("int8("),
-	io__write_int(Int),
+	output_int8(Int8),
 	io__write_string(")").
 output_data_item(char_ptr(String)) -->
 	io__write_string("char *("),
@@ -1279,17 +1296,89 @@
 	io__write_list(Bytes, " ", output_hexbyte),
 	io__write_string(")").
 
+:- pred output_float64(float64::in, io__state::di, io__state::uo) is det.
+output_float64(float64(Float)) -->
+	io__write_float(Float).
+
+:- pred output_float32(float32::in, io__state::di, io__state::uo) is det.
+output_float32(float32(Float)) -->
+	io__write_float(Float).
+
+:- pred output_int64(int64::in, io__state::di, io__state::uo) is det.
+output_int64(int64(Integer)) -->
+	io__write_string(integer__to_string(Integer)).
+
+:- pred output_int32(int32::in, io__state::di, io__state::uo) is det.
+output_int32(int32(Int)) -->
+	io__write_int(Int).
+
+:- pred output_int16(int16::in, io__state::di, io__state::uo) is det.
+output_int16(int16(Int)) -->
+	io__write_int(Int).
+
+:- pred output_int8(int8::in, io__state::di, io__state::uo) is det.
+output_int8(int8(Int)) -->
+	io__write_int(Int).
+
+:- pred output_byte(byte::in, io__state::di, io__state::uo) is det.
+output_byte(Byte) --> output_int8(Byte).
 
 :- pred output_hexbyte(byte::in, io__state::di, io__state::uo) is det.
-output_hexbyte(Byte) -->
-	{ string__int_to_base_string(Byte, 16, Tmp) },
+output_hexbyte(int8(Int)) -->
+	{ string__int_to_base_string(Int, 16, Tmp) },
 	io__write_string(Tmp).
 
-	% We need to escape all the IDs we output to avoid bumping into
+:- pred output_comment_string(string::in, io__state::di, io__state::uo) is det.
+output_comment_string(Comment) -->
+	io__write_string("// "),
+	{ CommentDoc = separated(text, line, 
+		string__words((pred('\n'::in) is semidet :- true), Comment)) },
+	{ Doc = label("\t// ", CommentDoc) },
+	write(70, Doc).
+
+	% We need to quote all the IDs we output to avoid bumping into
 	% keywords that assembler uses (there are a lot of them, and
 	% there is no list available).
-:- pred escape_id(ilds__id::in, string::out) is det.
-escape_id(Id, EscapedId) :-
-	string__append_list(["'", Id, "'"], EscapedId).
+:- pred quote_id(ilds__id::in, string::out) is det.
+quote_id(Id, QuotedId) :-
+	escape_string(Id, "'", EscapedId),
+	string__append_list(["'", EscapedId, "'"], QuotedId).
+
+:- pred output_escaped_string(string::in, string::in,
+		io__state::di, io__state::uo) is det.
+output_escaped_string(String, Escape) -->
+	{ escape_string(String, Escape, EscapedString) },
+	io__write_string(EscapedString).
+
+	% Replace all Rep0 with backslash quoted Rep0 in Str0,
+	% giving the escaped string Str.
+	% We also escape embedded newlines and other characters.
+	% We already do some name mangling during code generation that
+	% means we avoid most weird characters here.
+:- pred escape_string(string::in, string::in, string::out) is det.
+escape_string(Str0, Replace, Str) :-
+	string__append("\\", Replace, ReplaceWith),
+	string__replace_all(Str0, Replace, ReplaceWith, Str1),
+	string__to_char_list(Str1, CharList0),
+	list__foldl(
+		(pred(Char::in, E0::in, E::out) is det :-
+			( escape_special_char(Char, QuoteChar) ->
+				E = [QuoteChar, '\\' | E0]
+			;
+				E = [Char | E0]
+			)
+		), CharList0, [], CharList),
+	string__from_rev_char_list(CharList, Str).
+
+
+	% Characters that should be escaped in strings, and the
+	% character to escape with.
+:- pred escape_special_char(char::in, char::out) is semidet.
+escape_special_char('\\', '\\').
+escape_special_char('\n', 'n').
+escape_special_char('\t', 't').
+escape_special_char('\b', 'b').
+
+
 
 :- end_module ilasm.
diff -u ilds.m ilds.m
--- ilds.m
+++ ilds.m
@@ -7,13 +7,15 @@
 % ilds - The IL instruction set.
 % Main author: trd.
 %
-% This code is a little messy.  Much of it was lifted straight from the
-% assembler grammar and could be generalized some more.  Some of the
-% naming conventions are a bit screwy.
+% The IL instruction set is documented in the Microsoft .NET Framework SDK.
 %
-% To do:
-%	[ ] Use uniform naming.
-% 	[ ] Generalize and eliminate unnecessary types.
+% See 
+% 	http://msdn.microsoft.com/net/
+% for more info, including a downloadable (Windows only) version of the
+% SDK available here:
+% 	http://msdn.microsoft.com/downloads/default.asp?URL=/code/sample.asp?url=/msdn-files/027/000/976/msdncompositedoc.xml
+%
+%-----------------------------------------------------------------------------%
 
 :- module ilds.
 
@@ -37,33 +39,44 @@
 
 	% A method reference.
 :- type methodref
-	---> methoddef(call_conv, ret_type, member_name,
+	---> methoddef(call_conv, ret_type, class_member_name,
 		list(ilds__type))
-			% XXX not sure whether this is used.
-	;    methodref(call_conv, ret_type, structured_name,
+			% XXX not sure whether methodref is used.
+	;    methodref(call_conv, ret_type, class_name,
 		list(ilds__type))
-	;    local_method(call_conv, ret_type, method_name,
+	;    local_method(call_conv, ret_type, member_name,
 		list(ilds__type)).
 
 	% A field reference
 :- type fieldref
-	---> fieldref(ilds__type, member_name).
+	---> fieldref(ilds__type, class_member_name).
 
 % -------------------------------------------------------------------------
 
 :- type structured_name == list(ilds__id).
 
-:- type member_name 
-	---> member_name(structured_name, method_name).
+	% A namespace qualified class name is a structured name.
+	% Foo::Bar::Baz is ["Foo", "Bar", "Baz"]
+:- type class_name == structured_name.
+
+	% A member of a class 
+:- type class_member_name
+	---> class_member_name(
+			class_name, 
+			member_name
+	).
 
-:- type method_name 
-	--->	ctor
-	; 	cctor
-	;	id(ilds__id).
+	% The name of a member (method, field, event or property)
+:- type member_name 
+	--->	ctor		% constructor (initializes instances
+				% of this class)
+	; 	cctor		% class constructor (initializes
+				% non-instance fields).
+	;	id(ilds__id).	% ordinary method or field name
 
 	% calling conventions.
 :- type call_conv   
-	---> call_conv(
+	--->	call_conv(
 			bool,		% is this an instance method call?
 			call_kind	% what kind of call is it
 	).
@@ -76,6 +89,11 @@
 	;	unmanaged_thiscall
 	;	unmanaged_fastcall.
 
+
+	% XXX types have changed significantly in the spec since this
+	% was written, we should update this section (indeed, we should
+	% update all of ilds.m and ilasm.m).
+
 	% return types
 :- type ret_type
 	--->	void
@@ -98,36 +116,36 @@
 	;	uint16
 	;	uint32
 	;	uint64
-	;	native_int
-	;	native_uint
+	;	native_int	
+	;	native_uint		% Also used for unmanaged pointers.
 	;	float32
 	;	float64
 	;	native_float
 	;	bool
-	;	char
-	;	refany
-	; 	class(structured_name)
-	;	value_class(structured_name)
-	;	interface(structured_name)
-	;	'[]'(ilds__type, bounds)
-	;	'&'(ilds__type)
-	;	'*'(ilds__type).
+	;	char			% A unicode character.
+	;	refany			% a reference to value with an attached
+					% type
+	; 	class(class_name)
+	;	value_class(class_name)
+	;	interface(class_name)
+	;	'[]'(ilds__type, bounds) % An array
+	;	'&'(ilds__type)		 % A managed pointer
+	;	'*'(ilds__type).	 % A transient pointer (could become 
+					 % managed or unmanaged depending on
+					 % usage).
 
 :- type bounds == list(bound).
 
 :- type bound 
-	---> 	is(int)
-	;    	between(int, int).
+	---> 	upper(int)		% 0 <= index <= int
+	;    	lower(int)		% int <= index <= maxint
+	;    	between(int, int).	% int <= index <= int2
 
 	% an ID must start with "<", "_" or an alphabetic character.
 	% This initial character can be followed by any number of alphabetic
 	% characters, decimal digits, ">", "<", or "_".
 :- type ilds__id == string.
 
-	% The relative virtual address of something (e.g. a static data
-	% structure)
-:- type addressrva == int.
-
 	% XXX should really limit this, but we don't really support
 	% the alignment instruction just yet.
 :- type alignment == int.
@@ -151,8 +169,6 @@
 
 :- type index == int.
 
-:- type number == int.
-
 :- type target 
 	---> 	offset_target(int)
 	;	label_target(label).
@@ -166,10 +182,11 @@
 :- type blocktype 
 	--->	scope(locals)
 	;	try
-	;	catch(structured_name).
+	;	catch(class_name).
 
-	% each block has an identifier (mainly so you can tell which
+	% each block has a unique identifier (mainly so you can tell which
 	% ones match up without counting them).
+	% XXX should probably use counter type instead.
 :- type blockid == int. 
 
 :- type instr 
@@ -224,7 +241,6 @@
 	;	ldloc(variable)	% load a local variable onto the stack
 	;	ldloca(variable) 	% load a local variable address
 	;	ldnull			% push a null GC reference onto stack
-	;	ldptr(addressrva)	% load a constant pointer address
 	;	leave(target)	% exit a protected region of code
 	;	localloc		% allocate space from local pool
 	;	mul(overflow, signed)	% multiply values
@@ -268,7 +284,7 @@
 %	;	ldrefanya(index, ilds__type) % push refany addr into arg num
 	;	ldsfld(fieldref)	% load static field of a class
 	;	ldsflda(fieldref)	% load static field address
-	;	ldstr(string)	% load a literal string
+	;	ldstr(string)		% load a literal string
 	;	ldtoken(signature)	% load runtime rep of metadata token
 	;	ldvirtftn(methodref)	% push a pointer to a virtual method
 	;	mkrefany(ilds__type)	% push a refany pointer of type class
@@ -285,15 +301,25 @@
 
 	;	ann_call(signature)	% start of simple calling sequence
 	;	ann_catch		% start an exception filter or handler
-	;	ann_data(number)	% multi-byte no operation
-	;	ann_dead(number)	% stack location is no longer live
-	;	ann_def			% SSA definition node
+	;	ann_data(int)		% int32 bytes of uninterp. data follows 
+	;	ann_dead(location)	% stack location is no longer live
+	;	ann_def			% start SSA node
 	;	ann_hoisted(signature)  % start of complex argument evaluation
 	;	ann_hoisted_call	% start of simple part of hoisted call
 	;	ann_lab			% label (mark a branch target location)
-	;	ann_live(number)	% mark a stack location as live
-	;	ann_phi(list(number))	% SSA definition node
-	;	ann_ref(number).	% SSA reference node
+	;	ann_live(location)	% mark a stack location as live
+	;	ann_phi(list(node_number)) % merge SSA definition nodes
+	;	ann_ref(node_number).	% SSA reference node -- value at 
+					% node_number is same as next 
+					% instruction
+
+	% locations marked as dead by ann_dead -- positive numbers are
+	% stack slots, negative numbers are locals.
+:- type location == int.
+
+	% static single assignment nodes are generated, numbered from 0,
+	% by ann_def and ann_phi.
+:- type node_number == int.
 
 :- type label == string.
 
diff -u compiler/mercury_compile.m compiler/mercury_compile.m
--- compiler/mercury_compile.m
+++ compiler/mercury_compile.m
@@ -61,12 +61,13 @@
 :- import_module ml_elim_nested, ml_tailcall.	% MLDS -> MLDS
 :- import_module ml_optimize.			% MLDS -> MLDS
 :- import_module mlds_to_c.			% MLDS -> C
+:- import_module mlds_to_ilasm.			% MLDS -> IL assembler
+
 
 	% miscellaneous compiler modules
 :- import_module prog_data, hlds_module, hlds_pred, hlds_out, llds, rl.
 :- import_module mercury_to_mercury, mercury_to_goedel.
 :- import_module mlds_to_c.			% MLDS -> C
-:- import_module mlds_to_ilasm.			% MLDS -> IL assembler
 
 
 	% miscellaneous compiler modules
diff -u compiler/ml_code_gen.m compiler/ml_code_gen.m
--- compiler/ml_code_gen.m
+++ compiler/ml_code_gen.m
@@ -1876,6 +1876,14 @@
 	{ module_info_globals(ModuleInfo, Globals) },
 	{ globals__lookup_string_option(Globals, target, Target) },
 	( { CodeModel = model_non } ->
+
+		% For IL code, we can't call continutations because
+		% there is no syntax for calling managed function
+		% pointers in managed C++.  Instead we
+		% have to call back into IL and make the continuation
+		% call in IL.  This is called an "indirect" success
+		% continuation call.
+		
 		(
 			{ Target = "il" }
 		->
diff -u mlds_to_il.m mlds_to_il.m
--- mlds_to_il.m
+++ mlds_to_il.m
@@ -49,6 +49,13 @@
 %     pointers as MR_Box rather than MR_Word.
 % [ ] When generating target_code, sometimes we output more calls than
 %     we should (this can occur in nondet C code). 
+% [ ] ml_gen_call_current_success_cont_indirectly should be merged with
+% 	similar code for doing copy-in/copy-out.
+% [ ] figure out whether we need maxstack and fix it
+% [ ] Try to use the IL bool type for the true/false rvals.
+% [ ] Add an option to do overflow checking.
+% [ ] Should replace hard-coded of int32 with a more abstract name such
+%     as `mercury_int_il_type'.
 %
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -95,21 +102,19 @@
 :- mode mangle_mlds_var(in, out) is det.
 
 	% Get the corresponding ILDS type for a MLDS 
-:- pred mlds_type_to_ilds_type(mlds__type, ilds__type).
-:- mode mlds_type_to_ilds_type(in, out) is det.
+:- func mlds_type_to_ilds_type(mlds__type) = ilds__type.
 
-	% Turn a proc name into an IL structured name (class name) and a 
-	% method name.
+	% Turn a proc name into an IL class_name and a method name.
 :- pred mangle_mlds_proc_label(mlds__qualified_proc_label, 
-	maybe(mlds__func_sequence_num), structured_name, ilds__id).
+	maybe(mlds__func_sequence_num), ilds__class_name, ilds__id).
 :- mode mangle_mlds_proc_label(in, in, out, out) is det.
 
-	% Turn an MLDS module name into a structured IL name.	
-:- func mlds_module_name_to_structured_name(mlds_module_name) =
-		structured_name.
+	% Turn an MLDS module name into a class_name name.	
+:- func mlds_module_name_to_class_name(mlds_module_name) =
+		ilds__class_name.
 
-	% Return the structured name for the generic class.
-:- func il_generic_class_name = structured_name.
+	% Return the class_name for the generic class.
+:- func il_generic_class_name = ilds__class_name.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -153,7 +158,7 @@
 	method_c_code	:: bool,		% method contains c_code
 		% method-wide attributes (static)
 	arguments 	:: arguments_map, 	% The arguments 
-	method_name	:: method_name,	% current method name
+	method_name	:: member_name,		% current method name
 	signature	:: signature		% current return type 
 	).
 
@@ -170,11 +175,11 @@
 
 		% Generate code for all the methods in this module.
 	list__foldl(generate_method_defn, Defns, Info0, Info1),
-	or(Info1 ^ file_c_code, Info1 ^ method_c_code, ContainsCCode),
+	bool__or(Info1 ^ file_c_code, Info1 ^ method_c_code, ContainsCCode),
 	Info = Info1 ^ file_c_code := ContainsCCode,
 	ClassDecls = Info ^ classdecls,
-	InitInstrs = condense(flatten(Info ^ init_instrs)),
-	AllocInstrs = condense(flatten(Info ^ alloc_instrs)),
+	InitInstrs = list__condense(tree__flatten(Info ^ init_instrs)),
+	AllocInstrs = list__condense(tree__flatten(Info ^ alloc_instrs)),
 
 		% Generate definitions for all the other things
 		% declared within this module.
@@ -183,7 +188,7 @@
 	list__condense(OtherDeclsList, OtherDecls),
 
 	SymName = mlds_module_name_to_sym_name(ModuleName),
-	ClassStructuredName = mlds_module_name_to_structured_name(ModuleName),
+	ClassName = mlds_module_name_to_class_name(ModuleName),
 	mlds_to_il__sym_name_to_string(SymName, MStr),
 
 		% Make this module an assembly unless it is in the standard
@@ -217,7 +222,7 @@
 
 		% Generate a field that records whether we have finished
 		% RTTI initialization.
-	generate_rtti_initialization_field(ClassStructuredName, 
+	generate_rtti_initialization_field(ClassName, 
 		AllocDoneFieldRef, AllocDoneField),
 
 		% Generate a class constructor.
@@ -228,7 +233,7 @@
 	MethodDecls = [AllocDoneField, CCtor | ClassDecls],
 
 		% The class that corresponds to this MLDS module.
-	MainClass = [class([public], MStr, noextend, noimplement,
+	MainClass = [class([public], MStr, extends_nothing, implements([]),
 		MethodDecls)],
 
 		% A namespace to contain all the other declarations that
@@ -249,27 +254,45 @@
 generate_method_defn(defn(type(_, _), _, _, _)) --> [].
 	% XXX we don't handle export
 generate_method_defn(defn(export(_), _, _, _)) --> [].
-generate_method_defn(defn(function(PredLabel, ProcId, MaybeSeqNum, PredId), 
-		Context, DeclsFlags, Entity)) --> 
+generate_method_defn(FunctionDefn) -->
+	{ FunctionDefn = defn(function(PredLabel, ProcId, MaybeSeqNum, PredId), 
+		Context, DeclsFlags, Entity) },
 	( { Entity = mlds__function(_PredProcId, Params, MaybeStatement) } ->
+
 		il_info_get_module_name(ModuleName),
+			% Generate a term (we use it to emit the complete
+			% method definition as a comment, which is nice
+			% for debugging).
 		{ term__type_to_term(defn(function(PredLabel, ProcId, 
 			MaybeSeqNum, PredId), Context, DeclsFlags, Entity),
 			MLDSDefnTerm) },
+
+			% Generate the signature
 		{ Params = mlds__func_params(Args, Returns) },
 		{ list__map(mlds_arg_to_il_arg, Args, ILArgs) },
 		{ params_to_il_signature(ModuleName, Params,
 			ILSignature) },
+			
+			% Generate the name of the method.
 		{ predlabel_to_id(PredLabel, ProcId, MaybeSeqNum,
 			Id) },
 
+			% Initialize the IL info with this method info.
 		il_info_new_method(ILArgs, ILSignature, id(Id)),
+
+			% Start a new block, which we will use to wrap
+			% up the entire method.
 		il_info_get_next_block_id(BlockId),
+
+			% Generate the code of the statement.
 		( { MaybeStatement = yes(Statement) } -> 
 			statement_to_il(Statement, InstrsTree0)
 		;
 			{ InstrsTree0 = empty }
 		),
+
+			% If this is main, add the entrypoint and set a
+			% flag.
 		( { PredLabel = pred(predicate, no, "main", 2) },
 		  { MaybeSeqNum = no }
 		->
@@ -279,14 +302,18 @@
 		;
 			{ EntryPoint = [] }
 		),
-		il_info_get_locals_list(Locals),
+
 			% Need to insert a ret for functions returning
-			% void.
+			% void (MLDS doesn't).
 		{ Returns = [] ->
 			MaybeRet = instr_node(ret)
 		;
 			MaybeRet = empty
 		},
+
+			% Retrieve the locals, put them in the enclosing
+			% scope.
+		il_info_get_locals_list(Locals),
 		{ InstrsTree = tree__list([
 			instr_node(start_block(scope(Locals), BlockId)),
 			InstrsTree0, 
@@ -294,20 +321,13 @@
 			instr_node(end_block(scope(Locals), BlockId))
 			])
 		},
-		{ Instrs = condense(flatten(InstrsTree)) },
 
-		{ list__append(EntryPoint, 
-			% XXX should avoid hard-coding "100" for
-			% the maximum static size -- not sure if we even
-			% need this anymore.
-			[maxstack(100), 
-			% note that we only need .zeroinit to ensure
-			% verifiability; for nonverifiable code,
-			% we could omit that (it ensures that all
-			% variables are initialized to zero).
-			zeroinit,
-			instrs(Instrs)], 
-				MethodContents) },
+			% Generate the entire method contents.
+		{ MethodBody = make_method_defn(InstrsTree) },
+		{ list__append(EntryPoint, MethodBody, MethodContents) },
+
+			% Add this method and a comment to the class
+			% declarations.
 		{ ClassDecls = [
 			comment_term(MLDSDefnTerm),
 			ilasm__method(methodhead([static], id(Id), 
@@ -319,24 +339,70 @@
 	).
 
 
-generate_method_defn(defn(data(DataName), Context, DeclsFlags, Entity)) --> 
+generate_method_defn(DataDefn) --> 
+	{ DataDefn = defn(data(DataName), _Context, _DeclsFlags, Entity) },
 	il_info_get_module_name(ModuleName),
-	{ term__type_to_term(defn(data(DataName), Context, DeclsFlags, Entity),
-		MLDSDefnTerm) },
+	{ ClassName = mlds_module_name_to_class_name(ModuleName) },
+
+		% Generate a term (we use it to emit the complete
+		% method definition as a comment, which is nice
+		% for debugging).
+	{ term__type_to_term(DataDefn, MLDSDefnTerm) },
+
+		% Generate the field name for this data.
 	{ mangle_dataname(DataName, FieldName) },
-	{ ModuleStructuredName = mlds_module_name_to_structured_name(
-		ModuleName) },
+		
 	( 
 		{ Entity = mlds__data(_DataType, DataInitializer) }
 	->
+			% Generate instructions to initialize this data.
+			% There are two sorts of instructions,
+			% instructions to allocate the data structure,
+			% and instructions to initialize it.
+			% See the comments about class constructors to
+			% find out why we do this.
 		data_initializer_to_instrs(DataInitializer, AllocInstrsTree,
 			InitInstrTree),
+
+			% Make a field reference for the field
 		{ FieldRef = make_fieldref(il_array_type,
-			ModuleStructuredName, FieldName) },
+			ClassName, FieldName) },
+
 		{ AllocComment = comment_node(
 			string__append("allocation for ", FieldName)) },
 		{ InitComment = comment_node(
 			string__append("initializer for ", FieldName)) },
+
+			% If we had to allocate memory, the code
+			% we generate looks like this:
+			%
+			%	// allocation for foo
+			%	... allocation instructions ...
+			%	stsfld thisclass::foo
+			%
+			%
+			%	// initializer for foo
+			%	ldsfld thisclass::foo
+			%	... initialization code ...
+			%	pop
+			%
+			% The final pop is necessary because the init
+			% code will leave the field on the stack, but we
+			% don't need it anymore (and we already set the
+			% field when we allocated it).
+			%
+			% If no memory had to be allocated, the code is
+			% a bit simpler.
+			%
+			%	// allocation for foo
+			%	nothing here! 
+			%	
+			%	// initializer for foo
+			%	... initialization code ...
+			%	stsfld thisclass::foo
+			%
+			% Note that here we have to set the field.
+
 		{ AllocInstrsTree = node([]) ->
 			StoreAllocTree = node([]),
 			StoreInitTree = node([stsfld(FieldRef)]),
@@ -346,6 +412,7 @@
 			StoreInitTree = node([pop]),
 			LoadTree = node([ldsfld(FieldRef)])
 		},
+
 			% Add a store after the alloc instrs (if necessary)
 		{ AllocInstrs = list__condense(tree__flatten(
 			tree(AllocComment,
@@ -354,58 +421,77 @@
 		{ InitInstrs = list__condense(tree__flatten(
 			tree(InitComment,
 			tree(LoadTree, tree(InitInstrTree, StoreInitTree))))) },
+		
+			% Add these instructions to the lists of
+			% allocation/initialization instructions.
+			% They will be put into the class constructor
+			% later.
 		il_info_add_alloc_instructions(AllocInstrs),
 		il_info_add_init_instructions(InitInstrs),
+
+			% Make a public static field and add the field
+			% and a comment term to the class decls.
 		{ Field = field([public, static], il_array_type,
 			FieldName, no, none) },
 		{ ClassDecls = [comment_term(MLDSDefnTerm), Field] }
 	;
-		{ ClassDecls = [comment_term(MLDSDefnTerm),
-			comment("This type unimplemented.")] }
+		{ error("entity not data") }
 	),
 	il_info_add_classdecls(ClassDecls).
 	
 	% Generate top level declarations for "other" things (e.g.
-	% anything that is not a methods in the main class).
+	% anything that is not a method in the main class).
 	% XXX Really, this should be integrated with the other pass
 	% (generate_method_defn), and we can generate them all at once.
 	% This would involve adding the top-level decls list to il_info too.
 :- pred generate_other_decls(mlds_module_name, mlds__defn, list(ilasm__decl)).
 :- mode generate_other_decls(in, in, out) is det.
 generate_other_decls(ModuleName, MLDSDefn, Decls) :-
-	ModuleStructuredName = mlds_module_name_to_structured_name(ModuleName),
+	ClassName = mlds_module_name_to_class_name(ModuleName),
 	MLDSDefn = mlds__defn(EntityName, _Context, _DeclFlags, Entity), 
 	term__type_to_term(MLDSDefn, MLDSDefnTerm),
 	( EntityName = type(TypeName, _Arity),
-		list__append(ModuleStructuredName, [TypeName],
+		list__append(ClassName, [TypeName],
 			FullClassName),
-		( Entity = mlds__class(ClassDefn),
-			ClassDefn = mlds__class_defn(mlds__class, _Imports, 
-				_Inherits, _Implements, Defns) ->
-			list__map(defn_to_class_decl, Defns, ILDefns),
-			make_constructor(FullClassName, ClassDefn, 
-				ConstructorILDefn),
-			Decls = [comment_term(MLDSDefnTerm),
-				class([public], TypeName, noextend,
-				noimplement, [ConstructorILDefn | ILDefns])]
-		; Entity = mlds__class(ClassDefn),
-			ClassDefn = mlds__class_defn(mlds__struct, _Imports, 
-				_Inherits, _Implements, Defns) ->
-			list__map(defn_to_class_decl, Defns, ILDefns),
-			make_constructor(FullClassName, ClassDefn, 
-				ConstructorILDefn),
-			Decls = [comment_term(MLDSDefnTerm),
-				class([public], TypeName, 
-				extends(il_envptr_class_name), 
-				noimplement, [ConstructorILDefn | ILDefns])]
+		( 
+			Entity = mlds__class(ClassDefn) 
+		->
+			ClassDefn = mlds__class_defn(ClassType, _Imports, 
+				_Inherits, _Implements, Defns),
+			( 
+				ClassType = mlds__class
+			->
+				list__map(defn_to_class_decl, Defns, ILDefns),
+				make_constructor(FullClassName, ClassDefn, 
+					ConstructorILDefn),
+				Decls = [comment_term(MLDSDefnTerm),
+					class([public], TypeName,
+					extends_nothing, implements([]),
+					[ConstructorILDefn | ILDefns])]
+			; 
+				Entity = mlds__class(ClassDefn),
+				ClassType = mlds__struct
+			->
+				list__map(defn_to_class_decl, Defns, ILDefns),
+				make_constructor(FullClassName, ClassDefn, 
+					ConstructorILDefn),
+				Decls = [comment_term(MLDSDefnTerm),
+					class([public], TypeName, 
+					extends(il_envptr_class_name), 
+					implements([]), 
+					[ConstructorILDefn | ILDefns])]
+			;
+				Decls = [comment_term(MLDSDefnTerm),
+					comment("This type unimplemented.")]
+			)
 		;
 			Decls = [comment_term(MLDSDefnTerm),
 				comment("This type unimplemented.")]
 		)
 	; EntityName = function(_PredLabel, _ProcId, _MaybeFn, _PredId),
 		Decls = []
-			% XXX we don't handle export
 	; EntityName = export(_),
+			% XXX we don't handle export
 		Decls = []
 	; EntityName = data(_),
 		Decls = []
@@ -468,6 +554,7 @@
 data_initializer_to_instrs(init_obj(Rval), node([]), InitInstrs) --> 
 	load(Rval, InitInstrs).
 
+	% Currently, structs are the same as arrays.
 data_initializer_to_instrs(init_struct(InitList), AllocInstrs, InitInstrs) --> 
 	data_initializer_to_instrs(init_array(InitList), AllocInstrs, 
 		InitInstrs).
@@ -477,6 +564,22 @@
 	% and InitInstrs apart, since we are only interested in top level
 	% allocations.
 data_initializer_to_instrs(init_array(InitList), AllocInstrs, InitInstrs) -->
+
+		% To initialize an array, we generate the following
+		% code:
+		% 	ldc <length of array>
+		% 	newarr System::Object
+		%	
+		% Then, for each element in the array:
+		%	dup
+		%	ldc <index of this element in the array>
+		%	... allocation instructions ...
+		%	... initialization instructions ...
+		%	box the value (if necessary)
+		%	stelem System::Object
+		%
+		% The initialization will leave the array on the stack.
+		%	
 	{ AllocInstrs = node([ldc(int32, i(list__length(InitList))), 
 		newarr(il_generic_type)]) },
 	{ AddInitializer = 
@@ -521,8 +624,8 @@
 
 	% XXX shouldn't we re-use the code for creating fieldrefs here?
 defn_to_class_decl(mlds__defn(Name, _Context, _DeclFlags, 
-	mlds__data(Type, _Initializer)), ILClassDecl) :-
-	mlds_type_to_ilds_type(Type, ILType0),
+		mlds__data(Type, _Initializer)), ILClassDecl) :-
+	ILType0 = mlds_type_to_ilds_type(Type),
 		% IL doesn't allow byrefs in classes, so we don't use
 		% them.
 		% XXX really this should be a transformation done in
@@ -547,8 +650,8 @@
 	% XXX this might not need to be implemented (nested classes)
 	% since it will probably be flattened earlier.
 defn_to_class_decl(mlds__defn(_Name, _Context, _DeclFlags,
-	mlds__class(_)), _ILClassDecl) :-
-		error("nested data definition not expected here").
+		mlds__class(_)), _ILClassDecl) :-
+	error("nested data definition not expected here").
 
 
 %-----------------------------------------------------------------------------%
@@ -558,7 +661,7 @@
 
 :- pred statements_to_il(list(mlds__statement), instr_tree, il_info, il_info).
 :- mode statements_to_il(in, out, in, out) is det.
-statements_to_il([], empty, Info, Info).
+statements_to_il([], empty) --> [].
 statements_to_il([ S | Statements], tree(Instrs0, Instrs1)) -->
 	statement_to_il(S, Instrs0),
 	statements_to_il(Statements, Instrs1).
@@ -576,7 +679,7 @@
 		InitInstrsTree),
 	statements_to_il(Statements, BlockInstrs),
 	{ list__map((pred((K - V)::in, (K - W)::out) is det :- 
-		mlds_type_to_ilds_type(V, W)), Locals, ILLocals) },
+		W = mlds_type_to_ilds_type(V)), Locals, ILLocals) },
 	{ Instrs = tree__list([
 			node([start_block(scope(ILLocals), BlockId)]),
 			InitInstrsTree,
@@ -670,9 +773,9 @@
 			instr_node(br(label_target(StartLabel))),
 			instr_node(label(EndLabel))
 		])
+	; AtLeastOnce = yes, 
 			% XXX this generates a branch over branch which
 			% is suboptimal.
-	; AtLeastOnce = yes, 
 		Instrs = tree__list([
 			comment_node("while (actually do ... while)"),
 			instr_node(label(StartLabel)),
@@ -692,6 +795,7 @@
 			LoadInstrs,
 			instr_node(ret)]) }
 	;
+		% MS IL doesn't support multiple return values
 		{ sorry("multiple return values") }
 	).
 
@@ -704,6 +808,16 @@
 	{ Instrs = node([comment(Comment), br(label_target(Label))]) }.
 
 statement_to_il(statement(do_commit(Ref), _Context), Instrs) -->
+
+	% For commits, we use exception handling.
+	%
+	% We generate code of the following form:
+	% 
+	% 	<load exception rval -- should be of a special commit type>
+	% 	throw
+	%
+	% 
+
 	load(Ref, RefLoadInstrs),
 	{ Instrs = tree__list([
 		comment_node("do_commit/1"),
@@ -716,15 +830,17 @@
 
 	% For commits, we use exception handling.
 	%
-	% .try {	
-	%	GoalToTry
-	%	leave label1
-	% } catch commit_type {
-	%	pop
-	% 	CommitHandlerGoal
-	%	leave label1
-	% }
-	% label1:
+	% We generate code of the following form:
+	%
+	% 	.try {	
+	%		GoalToTry
+	%		leave label1
+	% 	} catch commit_type {
+	%		pop	// discard the exception object
+	% 		CommitHandlerGoal
+	%		leave label1
+	% 	}
+	% 	label1:
 	% 
 
 	il_info_get_next_block_id(TryBlockId),
@@ -734,7 +850,7 @@
 	il_info_make_next_label(DoneLabel),
 
 	rval_to_type(lval(Ref), MLDSRefType),
-	{ mlds_type_to_ilds_type(MLDSRefType, RefType) },
+	{ RefType = mlds_type_to_ilds_type(MLDSRefType) },
 	{ RefType = ilds__type(_, class(ClassName0)) ->
 			ClassName = ClassName0
 		;
@@ -791,8 +907,7 @@
 	( { Info ^ method_c_code = no } ->
 		dcg_set(Info ^ method_c_code := yes),
 		{ mangle_dataname_module(no, ModuleName, NewModuleName) },
-		{ StructuredName = mlds_module_name_to_structured_name(
-			NewModuleName) },
+		{ ClassName = mlds_module_name_to_class_name(NewModuleName) },
 		{ Info ^ signature = signature(_, RetType, Params) }, 
 			% If there is a return value, put it in succeeded.
 		{ RetType = void ->
@@ -809,7 +924,7 @@
 		{ list__condense(
 			[[comment("target code -- call handwritten version")],
 			LoadInstrs,
-			[call(get_static_methodref(StructuredName, MethodName, 
+			[call(get_static_methodref(ClassName, MethodName, 
 				RetType, TypeParams))],
 			StoreReturnInstr	
 			], Instrs) }
@@ -836,82 +951,134 @@
 atomic_statement_to_il(comment(Comment), Instrs) -->
 	{ Instrs = node([comment(Comment)]) }.
 
+atomic_statement_to_il(delete_object(Target), Instrs) -->
+		% XXX we assume the code generator knows what it is
+		% doing and is only going to delete real objects (e.g.
+		% reference types).  It would perhaps be prudent to
+		% check the type of delete_object (if it had one) to
+		% make sure.
+	
+		% We implement delete_object by storing null in the
+		% lval, which hopefully gives the garbage collector a good
+		% solid hint that this storage is no longer required.
+	get_load_store_lval_instrs(Target, LoadInstrs, StoreInstrs),
+	{ Instrs = tree__list([LoadInstrs, instr_node(ldnull), StoreInstrs]) }.
+
 atomic_statement_to_il(new_object(Target, _MaybeTag, Type, Size, _CtorName,
 		Args, ArgTypes), Instrs) -->
-	% If this is an env_ptr we should call the constructor...
-	% This is how we will handle high-level data
-    ( { Type = mlds__generic_env_ptr_type 
-      ; Type = mlds__class_type(_, _, _) } ->
-	{ mlds_type_to_ilds_type(Type, ILType) },
-	{ ILType = ilds__type(_, class(ClassName0)) ->
-		ClassName = ClassName0
-	;
-		unexpected("non-class for new_object")
-	},	
-	list__map_foldl(load, Args, ArgsLoadInstrsTrees),
-	{ ArgsLoadInstrs = tree__list(ArgsLoadInstrsTrees) },
-	get_load_store_lval_instrs(Target, LoadMemRefInstrs,
-		StoreLvalInstrs),
-	{ CallCtor = newobj_constructor(ClassName) },
-	{ Instrs = tree__list([
-		LoadMemRefInstrs, 
-		comment_node("new object (call constructor)"),
-		ArgsLoadInstrs,
-		instr_node(CallCtor),
-		StoreLvalInstrs
-		]) }
-    ;
-		% this is a generic object, but we need to do the boxing
-		% ourselves because MLDS hasn't done it.
-	{ Box = (pred(A - T::in, B::out) is det :- 
-		B = unop(box(T), A)   
-	) },
-	{ assoc_list__from_corresponding_lists(Args, ArgTypes,
-		ArgsAndTypes) },
-	{ list__map(Box, ArgsAndTypes, BoxedArgs) },
-
-	{ GenericSimpleType = class(["mscorlib", "System", "Object"]) },
-	{ GenericType = ilds__type([], GenericSimpleType) },
-	{ LoadInArray = (pred(Rval::in, I::out, Arg0::in, 
-			Arg::out) is det :- 
-		Arg0 = Index - S0,
-		I0 = instr_node(dup),
-		load(const(int_const(Index)), I1, S0, S1),
-		load(Rval, I2, S1, S), 
-		I3 = instr_node(stelem(GenericSimpleType)),
-		I = tree__list([I0, I1, I2, I3]),
-		Arg = (Index + 1) - S
-	) },
-	=(State0),
-	{ list__map_foldl(LoadInArray, BoxedArgs, ArgsLoadInstrsTrees,
-		0 - State0, _ - State) },
-	{ ArgsLoadInstrs = tree__list(ArgsLoadInstrsTrees) },
-	dcg_set(State),
-
-	get_load_store_lval_instrs(Target, LoadMemRefInstrs,
-		StoreLvalInstrs),
-
-		% XXX some hackery here to get around the MLDS memory
-		% allocation that tries to allocate in bytes.
-	{ Size = yes(binop((*), SizeInWordsRval0, _)) ->
-		SizeInWordsRval = SizeInWordsRval0
-	; Size = yes(SizeInWordsRval0) ->
-		SizeInWordsRval = SizeInWordsRval0
-	;
-		% XXX something else
-		error("unknown size in MLDS new_object")
-	},
-	load(SizeInWordsRval, LoadSizeInstrs),
+	( 
+		{ Type = mlds__generic_env_ptr_type 
+		; Type = mlds__class_type(_, _, _) }
+	->
+			% If this is an env_ptr we should call the
+			% constructor.  
+			% (This is also how we will handle high-level data).
+			% We generate code of the form:
+			%
+			% 	... load memory reference ...
+			%	// new object (call constructor)
+			%	... load each argument ...
+			%	call ClassName::.ctor
+			%	... store to memory reference ...
+			%
+		{ ILType = mlds_type_to_ilds_type(Type) },
+		{ 
+			ILType = ilds__type(_, class(ClassName0))
+		->
+			ClassName = ClassName0
+		;
+			unexpected("non-class for new_object")
+		},	
+		list__map_foldl(load, Args, ArgsLoadInstrsTrees),
+		{ ArgsLoadInstrs = tree__list(ArgsLoadInstrsTrees) },
+		get_load_store_lval_instrs(Target, LoadMemRefInstrs,
+			StoreLvalInstrs),
+		{ CallCtor = newobj_constructor(ClassName) },
+		{ Instrs = tree__list([
+			LoadMemRefInstrs, 
+			comment_node("new object (call constructor)"),
+			ArgsLoadInstrs,
+			instr_node(CallCtor),
+			StoreLvalInstrs
+			]) }
+	    ;
+			% Otherwise this is a generic mercury object -- we 
+			% use an array of System::Object to represent
+			% it.
+			%
+			% 	... load memory reference ...
+			%	// new object 
+			%	ldc <size of array>
+			%	newarr
+			%
+			% And then for each array element:
+			%
+			%	dup
+			%	ldc <array index>
+			%	... load and box rval ...
+			%	stelem System::Object
+			%
+			% Finally, after all the array elements have
+			% been set:
+			%
+			%	... store to memory reference ...
+			
+			% We need to do the boxing ourselves because
+			% MLDS hasn't done it.  We add boxing unops to
+			% the rvals.
+		{ Box = (pred(A - T::in, B::out) is det :- 
+			B = unop(box(T), A)   
+		) },
+		{ assoc_list__from_corresponding_lists(Args, ArgTypes,
+			ArgsAndTypes) },
+		{ list__map(Box, ArgsAndTypes, BoxedArgs) },
+	
+			% Load each rval 
+			% (XXX we do almost exactly the same code when
+			% initializing array data structures -- we
+			% should reuse that code.
+		{ LoadInArray = (pred(Rval::in, I::out, Arg0::in, 
+				Arg::out) is det :- 
+			Arg0 = Index - S0,
+			I0 = instr_node(dup),
+			load(const(int_const(Index)), I1, S0, S1),
+			load(Rval, I2, S1, S), 
+			I3 = instr_node(stelem(il_generic_simple_type)),
+			I = tree__list([I0, I1, I2, I3]),
+			Arg = (Index + 1) - S
+		) },
+		=(State0),
+		{ list__map_foldl(LoadInArray, BoxedArgs, ArgsLoadInstrsTrees,
+			0 - State0, _ - State) },
+		{ ArgsLoadInstrs = tree__list(ArgsLoadInstrsTrees) },
+		dcg_set(State),
+
+			% Get the instructions to load and store the
+			% target.
+		get_load_store_lval_instrs(Target, LoadMemRefInstrs,
+			StoreLvalInstrs),
+
+			% XXX some hackery here to get around the MLDS memory
+			% allocation that tries to allocate in bytes.
+		{ Size = yes(binop((*), SizeInWordsRval0, _)) ->
+			SizeInWordsRval = SizeInWordsRval0
+		; Size = yes(SizeInWordsRval0) ->
+			SizeInWordsRval = SizeInWordsRval0
+		;
+			% XXX something else
+			error("unknown size in MLDS new_object")
+		},
+		load(SizeInWordsRval, LoadSizeInstrs),
 
-	{ Instrs = tree__list([
-		LoadMemRefInstrs,
-		comment_node("new object"),
-		LoadSizeInstrs,
-		instr_node(newarr(GenericType)),
-		ArgsLoadInstrs,
-		StoreLvalInstrs
-		]) }
-	).
+		{ Instrs = tree__list([
+			LoadMemRefInstrs,
+			comment_node("new object"),
+			LoadSizeInstrs,
+			instr_node(newarr(il_generic_type)),
+			ArgsLoadInstrs,
+			StoreLvalInstrs
+			]) }
+		).
 
 :- pred get_all_load_store_lval_instrs(list(lval), instr_tree, instr_tree,
 		il_info, il_info).
@@ -937,7 +1104,7 @@
 		StoreLvalInstrs) -->
 	( { Lval = mem_ref(Rval0, MLDS_Type) } ->
 		load(Rval0, LoadMemRefInstrs),
-		{ mlds_type_to_ilds_type(MLDS_Type, ILType) },
+		{ ILType = mlds_type_to_ilds_type(MLDS_Type) },
 		{ ILType = ilds__type(_, SimpleType) },
 		{ StoreLvalInstrs = instr_node(stind(SimpleType)) } 
 	; { Lval = field(_MaybeTag, FieldRval, FieldNum, FieldType, 
@@ -975,23 +1142,22 @@
 		;
 			% XXX RTTI generates vars which are references
 			% to other modules!
-			% XXX we have no type information about this
-			% thing, so we have to assume it is a constant
-			% int32 in private_builtin__c_code.
 			Var = qual(ModuleName, _),
 			mangle_dataname_module(no, ModuleName,
 				NewModuleName),
-			StructuredName = mlds_module_name_to_structured_name(
+			ClassName = mlds_module_name_to_class_name(
 				NewModuleName),
-			FieldRef = make_fieldref(ilds__type([], int32),
-				StructuredName, MangledVarStr),
+			GlobalType = mlds_type_to_ilds_type(
+				mlds_type_for_rtti_global),
+			FieldRef = make_fieldref(GlobalType, ClassName, 
+				MangledVarStr),
 			Instrs = instr_node(ldsfld(FieldRef))
 		),
 		Info0 = Info
 	; Lval = field(_MaybeTag, Rval, FieldNum, FieldType, ClassType),
 		load(Rval, RvalLoadInstrs, Info0, Info1),
 		( FieldNum = offset(OffSet) ->
-			mlds_type_to_ilds_type(FieldType, ILFieldType),
+			ILFieldType = mlds_type_to_ilds_type(FieldType),
 			ILFieldType = ilds__type(_, SimpleFieldType),
 			load(OffSet, OffSetLoadInstrs, Info1, Info),
 			LoadInstruction = ldelem(SimpleFieldType)
@@ -1007,7 +1173,7 @@
 				instr_node(LoadInstruction)
 				])
 	; Lval = mem_ref(Rval, MLDS_Type),
-		mlds_type_to_ilds_type(MLDS_Type, ILType),
+		ILType = mlds_type_to_ilds_type(MLDS_Type),
 		ILType = ilds__type(_, SimpleType),
 		load(Rval, RvalLoadInstrs, Info0, Info),
 		Instrs = tree__list([
@@ -1017,11 +1183,13 @@
 	).
 
 load(mkword(_Tag, _Rval), Instrs, Info, Info) :- 
-		Instrs = comment_node("unimplemented load rval mkword").
+	Instrs = comment_node("unimplemented load rval mkword").
 
 	% XXX check these, what should we do about multi strings, 
 	% characters, etc.
 load(const(Const), Instrs, Info, Info) :- 
+		% XXX is there a better way to handle true and false
+		% using IL's bool type?
 	( Const = true,
 		Instrs = instr_node(ldc(int32, i(1)))
 	; Const = false,
@@ -1040,9 +1208,9 @@
 	; Const = data_addr_const(DataAddr),
 		data_addr_constant_to_fieldref(DataAddr, FieldRef),
 		Instrs = instr_node(ldsfld(FieldRef))
+	; Const = null(_MLDSType),
 			% We might consider loading an integer for 
 			% null function types.
-	; Const = null(_MLDSType),
 		Instrs = instr_node(ldnull)
 	).
 
@@ -1075,6 +1243,7 @@
 			])
 	; Lval = mem_ref(_, _),
 		Info0 = Info,
+			% XXX implement this
 		Instrs = throw_unimplemented("load mem_addr lval mem_ref")
 	).
 
@@ -1088,9 +1257,9 @@
 	Instrs = tree__list([RvalLoadInstrs, instr_node(stfld(FieldRef))]).
 
 store(mem_ref(_Rval, _Type), _Instrs, Info, Info) :- 
-			% you always need load the reference first, then
-			% the value, then stind it.  There's no swap
-			% instruction.  Annoying, eh?
+		% you always need load the reference first, then
+		% the value, then stind it.  There's no swap
+		% instruction.  Annoying, eh?
 	unexpected("store into mem_ref").
 
 store(var(Var), Instrs, Info, Info) :- 
@@ -1123,11 +1292,11 @@
 	load(const(int_const(0)), Instrs).
 unaryop_to_il(std_unop(unmktag), _, comment_node("unmktag (a no-op)")) --> [].
 unaryop_to_il(std_unop(mkbody),	_, comment_node("mkbody (a no-op)")) --> [].
-unaryop_to_il(std_unop(body), _, comment_node("body (a no-op)")) --> [].
 unaryop_to_il(std_unop(unmkbody), _, comment_node("unmkbody (a no-op)")) --> [].
 
 unaryop_to_il(std_unop(cast_to_unsigned), _,
 	throw_unimplemented("unimplemented cast_to_unsigned unop")) --> [].
+		% XXX implement this using string__hash
 unaryop_to_il(std_unop(hash_string), _,
 	throw_unimplemented("unimplemented hash_string unop")) --> [].
 unaryop_to_il(std_unop(bitwise_complement), _, node([not])) --> [].
@@ -1143,11 +1312,11 @@
 		% XXX should also test the cast-to type, to handle the
 		% cases where it is unboxed.
 unaryop_to_il(cast(Type), Rval, Instrs) -->
-	{ mlds_type_to_ilds_type(Type, ILType) },
+	{ ILType = mlds_type_to_ilds_type(Type) },
 	{ 
 		Rval = const(Const),
 		RvalType = rval_const_to_type(Const),
-		mlds_type_to_ilds_type(RvalType, RvalILType),
+		RvalILType = mlds_type_to_ilds_type(RvalType),
 		not already_boxed(RvalILType)
 	->
 		Instrs = node([call(convert_to_object(RvalILType)),
@@ -1165,10 +1334,10 @@
 	% then unboxing should just be castclass(System.Int32 or whatever),
 	% then unbox.
 unaryop_to_il(box(Type), _, Instrs) -->
-	{ mlds_type_to_ilds_type(Type, ILType) },
+	{ ILType = mlds_type_to_ilds_type(Type) },
 	{ already_boxed(ILType) ->
 		Instrs = node([isinst(ilds__type([], 
-			class(["mscorlib", "System", "Object"])))])
+			class([mscorlib_name, "System", "Object"])))])
 	;
 		Instrs = node([call(convert_to_object(ILType))])
 		% XXX can't just use box, because it requires a pointer to
@@ -1178,7 +1347,7 @@
 	}.
 
 unaryop_to_il(unbox(Type), _, Instrs) -->
-	{ mlds_type_to_ilds_type(Type, ILType) },
+	{ ILType = mlds_type_to_ilds_type(Type) },
 	{ ILType = ilds__type(_, class(_)) ->
 		Instrs = node([castclass(ILType)])
 	;
@@ -1241,6 +1410,10 @@
 		ceq
 	] }.
 
+binaryop_to_il(body, _) -->
+	{ error("unexpected binop: body") }.
+
+
 	% XXX we need to know what kind of thing is being indexed
 	% from the array in general. 
 binaryop_to_il(array_index, throw_unimplemented("array index unimplemented")) 
@@ -1359,20 +1532,20 @@
 
 
 	% Convert an rval into a function we can call.
-:- pred rval_to_function(rval, member_name).
+:- pred rval_to_function(rval, class_member_name).
 :- mode rval_to_function(in, out) is det.
 rval_to_function(Rval, MemberName) :-
 	( Rval = const(Const),
 		( Const = code_addr_const(CodeConst) ->
 			( CodeConst = proc(ProcLabel, _Sig),
 				mangle_mlds_proc_label(ProcLabel, no, 
-					StructuredName, ProcLabelStr),
-				MemberName = member_name(StructuredName, 
+					ClassName, ProcLabelStr),
+				MemberName = class_member_name(ClassName, 
 					id(ProcLabelStr))
 			; CodeConst = internal(ProcLabel, SeqNum, _Sig),
 				mangle_mlds_proc_label(ProcLabel, yes(SeqNum),
-					StructuredName, ProcLabelStr),
-				MemberName = member_name(StructuredName, 
+					ClassName, ProcLabelStr),
+				MemberName = class_member_name(ClassName, 
 					id(ProcLabelStr))
 			)
 		;
@@ -1421,11 +1594,29 @@
 	% in all .cctors is a check to see if the flag is set.  If it is, we
 	% return immediately (we have already been called and our
 	% initialization is either complete or at pass 2).
-
-
-	% Generate a classdecl for a .cctor, including a test to see if
-	% we have already initialized.
 	%
+	% 	// if (rtti_initialized) return;
+	% 	ldsfld rtti_initialized
+	%       brfalse done_label
+	% 	ret
+	% 	done_label:
+	% 
+	% 	// rtti_initialized = true
+	% 	ldc.i4.1
+	% 	stsfld rtti_initialized
+	% 
+	% 	// allocate RTTI data structures.
+	% 	<allocation instructions generated by field initializers>
+	% 
+	% 	// call .cctors
+	% 	call	someclass::.cctor
+	% 	call	someotherclass::.cctor
+	% 	... etc ...
+	% 
+	% 	// fill in fields of RTTI data structures
+	% 	<initialization instructions generated by field initializers>
+	%
+
 :- pred make_class_constructor_classdecl(fieldref, mlds__imports,
 	list(instr), list(instr), classdecl, il_info, il_info).
 :- mode make_class_constructor_classdecl(in, in, in, in, out, in, out) is det.
@@ -1437,7 +1628,7 @@
 	test_rtti_initialization_field(DoneFieldRef, TestInstrs),
 	set_rtti_initialization_field(DoneFieldRef, SetInstrs),
 	{ CCtorCalls = list__map((func(X) = call_class_constructor(
-		mlds_module_name_to_structured_name(X))), Imports) },
+		mlds_module_name_to_class_name(X))), Imports) },
 	{ AllInstrs = list__condense([TestInstrs, AllocInstrs, SetInstrs,
 		CCtorCalls, InitInstrs, [ret]]) },
 	{ MethodDecls = [instrs(AllInstrs)] }.
@@ -1457,16 +1648,16 @@
 	{ Instrs = [ldc(int32, i(1)), stsfld(FieldRef)] }.
 
 
-:- pred generate_rtti_initialization_field(structured_name, 
+:- pred generate_rtti_initialization_field(ilds__class_name, 
 		fieldref, classdecl).
 :- mode generate_rtti_initialization_field(in, out, out) is det.
-generate_rtti_initialization_field(StructuredName, AllocDoneFieldRef,
+generate_rtti_initialization_field(ClassName, AllocDoneFieldRef,
 		AllocDoneField) :-
 	AllocDoneFieldName = "rtti_initialized",
 	AllocDoneField = field([public, static], ilds__type([], bool),
 				AllocDoneFieldName, no, none),
 	AllocDoneFieldRef = make_fieldref(ilds__type([], bool),
-		StructuredName, AllocDoneFieldName).
+		ClassName, AllocDoneFieldName).
 
 
 
@@ -1477,7 +1668,7 @@
 :- pred mlds_signature_to_ilds_type_params(mlds__func_signature, list(ilds__type)).
 :- mode mlds_signature_to_ilds_type_params(in, out) is det.
 mlds_signature_to_ilds_type_params(func_signature(Args, _Returns), Params) :-
-	list__map(mlds_type_to_ilds_type, Args, Params).
+	Params = list__map(mlds_type_to_ilds_type, Args).
 
 :- pred mlds_arg_to_il_arg(pair(mlds__entity_name, mlds__type), 
 		pair(ilds__id, mlds__type)).
@@ -1491,107 +1682,93 @@
 	( Returns = [] ->
 		Param = void
 	; Returns = [ReturnType] ->
-		mlds_type_to_ilds_type(ReturnType, ReturnParam),
+		ReturnParam = mlds_type_to_ilds_type(ReturnType),
 		ReturnParam = ilds__type(_, SimpleType),
 		Param = simple_type(SimpleType)
 	;
-		error("cannot handle multiple return values")
+		% IL doesn't support multiple return values
+		sorry("multiple return values")
 	).
 
 params_to_il_signature(ModuleName, mlds__func_params(Inputs, Outputs),
 		 ILSignature) :-
-	list__map(input_param_to_ilds_type(ModuleName), Inputs, ILInputTypes),
+	ILInputTypes = list__map(input_param_to_ilds_type(ModuleName), Inputs),
 	( Outputs = [] ->
 		Param = void
 	; Outputs = [ReturnType] ->
-		mlds_type_to_ilds_type(ReturnType, ReturnParam),
+		ReturnParam = mlds_type_to_ilds_type(ReturnType),
 		ReturnParam = ilds__type(_, SimpleType),
 		Param = simple_type(SimpleType)
 	;
+		% IL doesn't support multiple return values
 		sorry("multiple return values")
 	),
 	ILSignature = signature(call_conv(no, default), Param, ILInputTypes).
 
-:- pred input_param_to_ilds_type(mlds_module_name, 
-		pair(entity_name, mlds__type), ilds__param).
-:- mode input_param_to_ilds_type(in, in, out) is det.
-input_param_to_ilds_type(ModuleName, EntityName - MldsType, 
-		ILType - yes(Id)) :-
+:- func input_param_to_ilds_type(mlds_module_name, 
+		pair(entity_name, mlds__type)) = ilds__param.
+input_param_to_ilds_type(ModuleName, EntityName - MldsType) 
+		= ILType - yes(Id) :-
 	mangle_entity_name(EntityName, VarName),
 	mangle_mlds_var(qual(ModuleName, VarName), Id),
-	mlds_type_to_ilds_type(MldsType, ILType).
+	ILType = mlds_type_to_ilds_type(MldsType).
 	
 
-:- pred output_param_to_ilds_type(mlds__type, ilds__param).
-:- mode output_param_to_ilds_type(in, out) is det.
-output_param_to_ilds_type(MldsType, ILType - no) :-
-	mlds_type_to_ilds_type(MldsType, ILType0),
-	make_reference(ILType0, ILType).
-
-:- pred make_reference(ilds__type, ilds__type).
-:- mode make_reference(in, out) is det.
-make_reference(ILType0, ILType) :-
-	ILType = ilds__type([], '&'(ILType0)).
-
 	% XXX make sure all the types are converted correctly
 
-mlds_type_to_ilds_type(mlds__rtti_type(_RttiName), ILType) :-
-	ILType = il_array_type.
+mlds_type_to_ilds_type(mlds__rtti_type(_RttiName)) = il_array_type.
 
-mlds_type_to_ilds_type(mlds__array_type(ElementType), ILType) :-
-	mlds_type_to_ilds_type(ElementType, ElementILType),
-	ILType = ilds__type([], '[]'(ElementILType, [])).
+mlds_type_to_ilds_type(mlds__array_type(ElementType)) = 
+	ilds__type([], '[]'(mlds_type_to_ilds_type(ElementType), [])).
 
 	% This is tricky.  It could be an integer, or it could be
 	% a System.Array.
-mlds_type_to_ilds_type(mlds__pseudo_type_info_type, ILType) :-
-	ILType = il_generic_type.
+mlds_type_to_ilds_type(mlds__pseudo_type_info_type) = il_generic_type.
 
 	% IL has a pretty fuzzy idea about function types.
 	% We treat them as integers for now
 	% XXX This means the code is not verifiable.
-mlds_type_to_ilds_type(mlds__func_type(_), ILType) :-
-	ILType = ilds__type([], int32).
+mlds_type_to_ilds_type(mlds__func_type(_)) = ilds__type([], int32).
 
-mlds_type_to_ilds_type(mlds__generic_type, ILType) :-
-	ILType = il_generic_type.
+mlds_type_to_ilds_type(mlds__generic_type) = il_generic_type.
 
-mlds_type_to_ilds_type(mlds__cont_type(_ArgTypes), ILType) :-
 	% XXX Using int32 here means the code is not verifiable
 	% see comments about function types above.
-	ILType = ilds__type([], int32).
+mlds_type_to_ilds_type(mlds__cont_type(_ArgTypes)) = ilds__type([], int32).
 
-mlds_type_to_ilds_type(mlds__class_type(Class, _Arity, _Kind), ILType) :-
-	Class = qual(MldsModuleName, ClassName),
-	StructuredName = mlds_module_name_to_structured_name(MldsModuleName),
-	list__append(StructuredName, [ClassName], FullClassName),
+mlds_type_to_ilds_type(mlds__class_type(Class, _Arity, _Kind)) = ILType :-
+	Class = qual(MldsModuleName, MldsClassName),
+	ClassName = mlds_module_name_to_class_name(MldsModuleName),
+	list__append(ClassName, [MldsClassName], FullClassName),
 	ILType = ilds__type([], class(FullClassName)).
 
-mlds_type_to_ilds_type(mlds__commit_type, ILType) :-
-	ILType = ilds__type([], class(["mercury", "commit"])).
+mlds_type_to_ilds_type(mlds__commit_type) =
+	ilds__type([], class(["mercury", "commit"])).
 
-mlds_type_to_ilds_type(mlds__generic_env_ptr_type, ILType) :-
-	ILType = il_envptr_type.
+mlds_type_to_ilds_type(mlds__generic_env_ptr_type) = il_envptr_type.
 
-mlds_type_to_ilds_type(mlds__native_bool_type, ILType) :-
 	% XXX we ought to use the IL bool type
-	ILType = ilds__type([], int32).
+mlds_type_to_ilds_type(mlds__native_bool_type) = ilds__type([], int32).
+
 
-mlds_type_to_ilds_type(mlds__native_float_type, ILType) :-
-	ILType = ilds__type([], float64).
+mlds_type_to_ilds_type(mlds__native_char_type) = ilds__type([], char).
 
-mlds_type_to_ilds_type(mlds__native_char_type, ILType) :-
-	ILType = ilds__type([], char).
+	% These two following choices are arbitrary -- IL has native
+	% integer and float types too.  It's not clear whether there is
+	% any benefit in mapping to them instead -- it all depends what
+	% the indended use of mlds__native_int_type and
+	% mlds__native_float_type is.
+	% Any mapping other than int32 would have to be examined to see
+	% whether it is going to be compatible with int32.
+mlds_type_to_ilds_type(mlds__native_int_type) = ilds__type([], int32).
 
-mlds_type_to_ilds_type(mlds__native_int_type, ILType) :-
-	ILType = ilds__type([], int32).
+mlds_type_to_ilds_type(mlds__native_float_type) = ilds__type([], float64).
 
-mlds_type_to_ilds_type(mlds__ptr_type(MLDSType), ILType) :-
-	mlds_type_to_ilds_type(MLDSType, ILType0),
-	ILType = ilds__type([], '&'(ILType0)).
+mlds_type_to_ilds_type(mlds__ptr_type(MLDSType)) =
+	ilds__type([], '&'(mlds_type_to_ilds_type(MLDSType))).
 
 	% XXX should use the classification now that it is available.
-mlds_type_to_ilds_type(mercury_type(Type, _Classification), ILType) :-
+mlds_type_to_ilds_type(mercury_type(Type, _Classification)) = ILType :-
 	( 
 		Type = term__functor(term__atom(Atom), [], _),
 		( Atom = "string", 	SimpleType = il_string_simple_type
@@ -1757,8 +1934,8 @@
 
 	% We turn procedures into methods of classes.
 mangle_mlds_proc_label(qual(ModuleName, PredLabel - ProcId), MaybeSeqNum,
-		StructuredName, PredStr) :-
-	StructuredName = mlds_module_name_to_structured_name(ModuleName),
+		ClassName, PredStr) :-
+	ClassName = mlds_module_name_to_class_name(ModuleName),
 	predlabel_to_id(PredLabel, ProcId, MaybeSeqNum, PredStr).
 
 :- pred mangle_entity_name(mlds__entity_name, string).
@@ -1772,8 +1949,11 @@
 mangle_entity_name(export(_), _MangledName) :-
 	error("can't mangle export names").
 
+	% Any valid Mercury identifier will be fine here too.
+	% We quote all identifiers before we output them, so
+	% even funny characters should be fine.
 mangle_mlds_var(qual(_ModuleName, VarName), Str) :-
-	string__format("%s", [s(VarName)], Str).
+	Str = VarName.
 
 :- pred mlds_to_il__sym_name_to_string(sym_name, string).
 :- mode mlds_to_il__sym_name_to_string(in, out) is det.
@@ -1796,21 +1976,21 @@
 mlds_to_il__sym_name_to_string_2(unqualified(Name), _) -->
         [Name].
 
-mlds_module_name_to_structured_name(MldsModuleName) = StructuredName :-
+mlds_module_name_to_class_name(MldsModuleName) = ClassName :-
 	SymName = mlds_module_name_to_sym_name(MldsModuleName),
-	sym_name_to_structured_name(SymName, StructuredName).
+	sym_name_to_class_name(SymName, ClassName).
 
-:- pred sym_name_to_structured_name(sym_name, list(ilds__id)).
-:- mode sym_name_to_structured_name(in, out) is det.
-sym_name_to_structured_name(SymName, Ids) :-
-	sym_name_to_structured_name_2(SymName, Ids0),
+:- pred sym_name_to_class_name(sym_name, list(ilds__id)).
+:- mode sym_name_to_class_name(in, out) is det.
+sym_name_to_class_name(SymName, Ids) :-
+	sym_name_to_class_name_2(SymName, Ids0),
 	list__reverse(Ids0, Ids).
 
-:- pred sym_name_to_structured_name_2(sym_name, list(ilds__id)).
-:- mode sym_name_to_structured_name_2(in, out) is det.
-sym_name_to_structured_name_2(qualified(ModuleSpec, Name), [Name | Modules]) :-
-	sym_name_to_structured_name_2(ModuleSpec, Modules).
-sym_name_to_structured_name_2(unqualified(Name), [Name]).
+:- pred sym_name_to_class_name_2(sym_name, list(ilds__id)).
+:- mode sym_name_to_class_name_2(in, out) is det.
+sym_name_to_class_name_2(qualified(ModuleSpec, Name), [Name | Modules]) :-
+	sym_name_to_class_name_2(ModuleSpec, Modules).
+sym_name_to_class_name_2(unqualified(Name), [Name]).
 
 
 
@@ -1836,10 +2016,11 @@
 %
 
 	% This gives us the type of an rval. 
-	% This type is with respect to IL (for example we map code
-	% address and data address constants to the MLDS version of our
-	% representation).  This is so you can generate appropriate
-	% box rvals for rval_consts.
+	% This type is an MLDS type, but is with respect to the IL
+	% representation (that is, we map code address and data address
+	% constants to the MLDS version of their IL representation).
+	% This is so you can generate appropriate box rvals for
+	% rval_consts.
 
 :- pred rval_to_type(mlds__rval::in, mlds__type::out,
 		il_info::in, il_info::out) is det.
@@ -1854,18 +2035,27 @@
 		Info = Info0
 	).
 
+	% The following four conversions should never occur or be boxed
+	% anyway, but just in case they are we make them reference
+	% mercury.invalid which is a non-exisitant class.   If we try to
+	% run this code, we'll get a runtime error.
+	% XXX can we just call error?
 rval_to_type(mkword(_Tag, _Rval), Type, I, I) :- 
 	ModuleName = mercury_module_name_to_mlds(unqualified("mercury")),
-	Type = mlds__class_type(qual(ModuleName, "incorrect"), 0, mlds__class).
+	Type = mlds__class_type(qual(ModuleName, "invalid"),
+		0, mlds__class).
 rval_to_type(unop(_, _), Type, I, I) :- 
 	ModuleName = mercury_module_name_to_mlds(unqualified("mercury")),
-	Type = mlds__class_type(qual(ModuleName, "incorrect"), 0, mlds__class).
+	Type = mlds__class_type(qual(ModuleName, "invalid"),
+		0, mlds__class).
 rval_to_type(binop(_, _, _), Type, I, I) :- 
 	ModuleName = mercury_module_name_to_mlds(unqualified("mercury")),
-	Type = mlds__class_type(qual(ModuleName, "incorrect"), 0, mlds__class).
+	Type = mlds__class_type(qual(ModuleName, "invalid"),
+		0, mlds__class).
 rval_to_type(mem_addr(_), Type, I, I) :-
 	ModuleName = mercury_module_name_to_mlds(unqualified("mercury")),
-	Type = mlds__class_type(qual(ModuleName, "incorrect"), 0, mlds__class).
+	Type = mlds__class_type(qual(ModuleName, "invalid"),
+		0, mlds__class).
 rval_to_type(const(Const), Type, I, I) :- 
 	Type = rval_const_to_type(Const).
 
@@ -1892,19 +2082,19 @@
 :- mode code_addr_constant_to_methodref(in, out) is det.
 
 code_addr_constant_to_methodref(proc(ProcLabel, Sig), MethodRef) :-
-	mangle_mlds_proc_label(ProcLabel, no, StructuredName, ProcLabelStr),
+	mangle_mlds_proc_label(ProcLabel, no, ClassName, ProcLabelStr),
 	mlds_signature_to_ilds_type_params(Sig, TypeParams),
 	mlds_signature_to_il_return_param(Sig, ReturnParam),
-	MemberName = member_name(StructuredName, id(ProcLabelStr)),
+	MemberName = class_member_name(ClassName, id(ProcLabelStr)),
 	MethodRef = methoddef(call_conv(no, default), ReturnParam, 
 		MemberName, TypeParams).
 
 code_addr_constant_to_methodref(internal(ProcLabel, SeqNum, Sig), MethodRef) :-
-	mangle_mlds_proc_label(ProcLabel, yes(SeqNum), StructuredName, 
+	mangle_mlds_proc_label(ProcLabel, yes(SeqNum), ClassName, 
 		ProcLabelStr),
 	mlds_signature_to_ilds_type_params(Sig, TypeParams),
 	mlds_signature_to_il_return_param(Sig, ReturnParam),
-	MemberName = member_name(StructuredName, id(ProcLabelStr)),
+	MemberName = class_member_name(ClassName, id(ProcLabelStr)),
 	MethodRef = methoddef(call_conv(no, default), ReturnParam, 
 		MemberName, TypeParams).
 
@@ -1916,8 +2106,8 @@
 data_addr_constant_to_fieldref(data_addr(ModuleName, DataName), FieldRef) :-
 	mangle_dataname(DataName, FieldName),
 	mangle_dataname_module(yes(DataName), ModuleName, NewModuleName),
-	StructuredName = mlds_module_name_to_structured_name(NewModuleName),
-	FieldRef = make_fieldref(il_array_type, StructuredName, FieldName).
+	ClassName = mlds_module_name_to_class_name(NewModuleName),
+	FieldRef = make_fieldref(il_array_type, ClassName, FieldName).
 
 
 %-----------------------------------------------------------------------------%
@@ -1934,17 +2124,17 @@
 :- pred get_fieldref(field_id, mlds__type, mlds__type, fieldref).
 :- mode get_fieldref(in, in, in, out) is det.
 get_fieldref(FieldNum, FieldType, ClassType, FieldRef) :-
-		mlds_type_to_ilds_type(FieldType, FieldILType0),
-		mlds_type_to_ilds_type(ClassType, ClassILType),
+		FieldILType0 = mlds_type_to_ilds_type(FieldType),
+		ClassILType = mlds_type_to_ilds_type(ClassType),
 		( FieldILType0 = ilds__type(_, '&'(FieldILType1)) ->
 			FieldILType = FieldILType1
 		;
 			FieldILType = FieldILType0
 		),
 		( ClassILType = ilds__type(_, 
-			class(ClassTypeStructuredName0))
+			class(ClassTypeName0))
 		->
-			StructuredName = ClassTypeStructuredName0
+			ClassName = ClassTypeName0
 		;
 			unexpected("not a class for field access")
 		),
@@ -1959,7 +2149,7 @@
 			FieldNum = named_field(qual(_ModuleName, FieldId),
 				_Type)
 		),
-		FieldRef = make_fieldref(FieldILType, StructuredName, FieldId).
+		FieldRef = make_fieldref(FieldILType, ClassName, FieldId).
 
 
 %-----------------------------------------------------------------------------%
@@ -1988,21 +2178,23 @@
 
 convert_to_object(Type) = methoddef(call_conv(no, default), 
 		simple_type(il_generic_simple_type),
-		member_name(ConvertClass, id("ToObject")), [Type]) :-
+		class_member_name(ConvertClass, id("ToObject")), [Type]) :-
 	ConvertClass = ["mercury", "mr_convert"].
 
 :- func convert_from_object(ilds__type) = methodref.
 
 convert_from_object(Type) = 
 	methoddef(call_conv(no, default), simple_type(SimpleType),
-		member_name(ConvertClass, id(Id)), [il_generic_type]) :-
+		class_member_name(ConvertClass, id(Id)), [il_generic_type]) :-
 	ConvertClass = ["mercury", "mr_convert"],
 	Type = ilds__type(_, SimpleType),
 	ValueClassName = simple_type_to_value_class_name(SimpleType),
 	string__append("To", ValueClassName, Id).
 
 
-
+	% XXX String and Array should be converted to/from Object using a
+	% cast, not a call to mr_convert.  When that is done they can be
+	% removed from this list
 :- func simple_type_to_value_class_name(simple_type) = string.
 simple_type_to_value_class_name(int8) = "Int8".
 simple_type_to_value_class_name(int16) = "Int16".
@@ -2019,7 +2211,7 @@
 simple_type_to_value_class_name(refany) = _ :-
 	error("no value class name for refany").
 simple_type_to_value_class_name(class(Name)) = VCName :-
-	( Name = ["mscorlib", "System", "String"] ->
+	( Name = [mscorlib_name, "System", "String"] ->
 		VCName = "String"
 	;
 		error("unknown class name")
@@ -2053,14 +2245,14 @@
 il_string_compare = get_static_methodref(il_string_class_name, id("Compare"), 
 	simple_type(int32), [il_string_type, il_string_type]).
 
-:- func il_string_class_name = structured_name.
-il_string_class_name = ["mscorlib", "System", "String"].
+:- func il_string_class_name = ilds__class_name.
+il_string_class_name = [mscorlib_name, "System", "String"].
 
 :- func il_string_simple_type = simple_type.
 il_string_simple_type = class(il_string_class_name).
 
 :- func il_string_type = ilds__type.
-il_string_type = ilds__type([], class(["mscorlib", "System", "String"])).
+il_string_type = ilds__type([], class([mscorlib_name, "System", "String"])).
 
 
 %-----------------------------------------------------------------------------%
@@ -2074,7 +2266,7 @@
 :- func il_generic_simple_type = simple_type.
 il_generic_simple_type = class(il_generic_class_name).
 
-il_generic_class_name = ["mscorlib", "System", "Object"].
+il_generic_class_name = [mscorlib_name, "System", "Object"].
 
 %-----------------------------------------------------------------------------%
 %
@@ -2096,7 +2288,7 @@
 :- func il_envptr_simple_type = simple_type.
 il_envptr_simple_type = class(il_envptr_class_name).
 
-:- func il_envptr_class_name = structured_name.
+:- func il_envptr_class_name = ilds__class_name.
 il_envptr_class_name = ["mercury", "envptr"].
 
 
@@ -2111,19 +2303,24 @@
 :- func il_commit_simple_type = simple_type.
 il_commit_simple_type = class(il_commit_class_name).
 
-:- func il_commit_class_name = structured_name.
+:- func il_commit_class_name = ilds__class_name.
 il_commit_class_name = ["mercury", "commit"].
 
 %-----------------------------------------------------------------------------
 
+:- func mscorlib_name = string. 
+mscorlib_name = "mscorlib".
+
+%-----------------------------------------------------------------------------
+
 	% Generate extern decls for any assembly we reference.
 :- pred mlds_to_il__generate_extern_assembly(mlds__imports, list(decl)).
 :- mode mlds_to_il__generate_extern_assembly(in, out) is det.
 
 mlds_to_il__generate_extern_assembly(Imports, Decls) :-
 	Gen = (pred(Import::in, Decl::out) is semidet :-
-		Structured = mlds_module_name_to_structured_name(Import),
-		Structured = [TopLevel | _],
+		ClassName = mlds_module_name_to_class_name(Import),
+		ClassName = [TopLevel | _],
 		Decl = extern_assembly(TopLevel)
 	),
 	list__filter_map(Gen, Imports, Decls0),
@@ -2131,11 +2328,19 @@
 
 %-----------------------------------------------------------------------------
 
-:- func make_methoddecls(instr_tree) = list(methoddecl).
-make_methoddecls(InstrTree) = MethodDecls :-
-	Instrs = list__condense(flatten(tree(InstrTree, instr_node(ret)))),
+:- func make_method_defn(instr_tree) = method_defn.
+make_method_defn(InstrTree) = MethodDecls :-
+	Instrs = list__condense(tree__flatten(InstrTree)),
 	MethodDecls = [
-		maxstack(100),
+			% XXX should avoid hard-coding "100" for
+			% the maximum static size -- not sure if we even
+			% need this anymore.
+		maxstack(int32(100)),
+			% note that we only need .zeroinit to ensure
+			% verifiability; for nonverifiable code,
+			% we could omit that (it ensures that all
+			% variables are initialized to zero).
+		zeroinit,
 		instrs(Instrs)
 		].
 
@@ -2159,24 +2364,28 @@
 		FieldConstrInstrsLists),
 	list__condense(FieldConstrInstrsLists, FieldConstrInstrs),
 	Instrs = [load_this, call_constructor(CtorMemberName)],
-	MethodDecls = make_methoddecls(tree(node(Instrs),
-		node(FieldConstrInstrs))),
+	MethodDecls = make_method_defn(tree__list(
+		[node(Instrs),
+		 node(FieldConstrInstrs),
+		 instr_node(ret)
+		 ])),
 	ILDecl = make_constructor_classdecl(MethodDecls).
 
 
 	% XXX This should really be generated at a higher level	
-	% XXX For now we only call the constructor if it is an env_ptr.
+	% XXX For now we only call the constructor if it is an env_ptr
+	%     or commit type.
 :- pred call_field_constructor(list(ilds__id), mlds__defn, list(instr)).
 :- mode call_field_constructor(in, in, out) is det.
-call_field_constructor(ObjStructuredName, MLDSDefn, Instrs) :-
+call_field_constructor(ObjClassName, MLDSDefn, Instrs) :-
 	MLDSDefn = mlds__defn(EntityName, _Context, _DeclFlags, Entity), 
 	( 
 		Entity = mlds__data(Type, _Initializer),
 		EntityName = data(DataName)
 	->
-		mlds_type_to_ilds_type(Type, ILType),
+		ILType = mlds_type_to_ilds_type(Type),
 		mangle_dataname(DataName, MangledName),
-		FieldRef = make_fieldref(ILType, ObjStructuredName,
+		FieldRef = make_fieldref(ILType, ObjClassName,
 			MangledName),
 		( 
 			ILType = il_envptr_type, 
@@ -2205,11 +2414,11 @@
 :- func load_this = instr.
 load_this = ldarg(index(0)).
 
-:- func call_class_constructor(structured_name) = instr.
+:- func call_class_constructor(ilds__class_name) = instr.
 call_class_constructor(CtorMemberName) = 
 	call(get_static_methodref(CtorMemberName, cctor, void, [])).
 
-:- func call_constructor(structured_name) = instr.
+:- func call_constructor(ilds__class_name) = instr.
 call_constructor(CtorMemberName) = 
 	call(get_constructor_methoddef(CtorMemberName)).
 
@@ -2222,34 +2431,34 @@
 		throw]
 	).
 
-:- func newobj_constructor(structured_name) = instr.
+:- func newobj_constructor(ilds__class_name) = instr.
 newobj_constructor(CtorMemberName) = 
 	newobj(get_constructor_methoddef(CtorMemberName)).
 
-:- func get_constructor_methoddef(structured_name) = methodref.
+:- func get_constructor_methoddef(ilds__class_name) = methodref.
 get_constructor_methoddef(CtorMemberName) = 
 	get_instance_methodref(CtorMemberName, ctor, void, []).
 
-:- func get_instance_methodref(structured_name, method_name, ret_type,
+:- func get_instance_methodref(ilds__class_name, member_name, ret_type,
 		list(ilds__type)) = methodref.
-get_instance_methodref(MemberName, MethodName, RetType, TypeParams) = 
+get_instance_methodref(ClassName, MethodName, RetType, TypeParams) = 
 	methoddef(call_conv(yes, default), RetType,
-		member_name(MemberName, MethodName), TypeParams).
+		class_member_name(ClassName, MethodName), TypeParams).
 
-:- func get_static_methodref(structured_name, method_name, ret_type,
+:- func get_static_methodref(ilds__class_name, member_name, ret_type,
 		list(ilds__type)) = methodref.
-get_static_methodref(MemberName, MethodName, RetType, TypeParams) = 
+get_static_methodref(ClassName, MethodName, RetType, TypeParams) = 
 	methoddef(call_conv(no, default), RetType,
-		member_name(MemberName, MethodName), TypeParams).
+		class_member_name(ClassName, MethodName), TypeParams).
 
-:- func make_constructor_classdecl(list(methoddecl)) = classdecl.
+:- func make_constructor_classdecl(method_defn) = classdecl.
 make_constructor_classdecl(MethodDecls) = method(
 	methodhead([], ctor, signature(call_conv(no, default), 
 		void, []), []), MethodDecls).
 
-:- func make_fieldref(ilds__type, structured_name, ilds__id) = fieldref.
-make_fieldref(ILType, StructuredName, Id) = 
-	fieldref(ILType, member_name(StructuredName, id(Id))).
+:- func make_fieldref(ilds__type, ilds__class_name, ilds__id) = fieldref.
+make_fieldref(ILType, ClassName, Id) = 
+	fieldref(ILType, class_member_name(ClassName, id(Id))).
 
 %-----------------------------------------------------------------------------%
 %
@@ -2269,7 +2478,7 @@
 	MethodName = id("").
 
 	% reset the il_info for processing a new method
-:- pred il_info_new_method(arguments_map, signature, method_name, 
+:- pred il_info_new_method(arguments_map, signature, member_name, 
 	il_info, il_info).
 :- mode il_info_new_method(in, in, in, in, out) is det.
 
@@ -2282,8 +2491,8 @@
 		AllocInstrs, InitInstrs, ClassDecls, HasMain, NewClassCCode,
 		map__init, empty, counter__init(1), counter__init(1), no,
 		ILArgs, MethodName, ILSignature)) :-
-	or(ClassCCode, MethodCCode, NewClassCCode),
-	or(FileCCode, MethodCCode, NewFileCCode).
+	bool__or(ClassCCode, MethodCCode, NewClassCCode),
+	bool__or(FileCCode, MethodCCode, NewFileCCode).
 
 :- pred il_info_set_arguments(assoc_list(ilds__id, mlds__type), 
 	il_info, il_info).
@@ -2308,13 +2517,16 @@
 	->
 		Type = Type0
 	;
-		% If it isn't a local or an argument, it can only be a
-		% "global variable" -- used by RTTI.  We will assume this
-		% is an integer for now.
-		Type = native_int_type
+		% XXX If it isn't a local or an argument, it can only be a
+		% "global variable" -- used by RTTI.  
+		Type = mlds_type_for_rtti_global
 	).
-		
 
+	% RTTI creates global variables -- these all happen to be of
+	% type mlds__native_int_type.
+:- func mlds_type_for_rtti_global = mlds__type.
+mlds_type_for_rtti_global = native_int_type.
+		
 :- pred il_info_set_modulename(mlds_module_name, il_info, il_info).
 :- mode il_info_set_modulename(in, in, out) is det.
 il_info_set_modulename(ModuleName, Info0, Info) :- 
@@ -2367,7 +2579,7 @@
 :- mode il_info_get_locals_list(out, in, out) is det.
 il_info_get_locals_list(Locals, Info, Info) :- 
 	map__map_values((pred(_K::in, V::in, W::out) is det :- 
-		mlds_type_to_ilds_type(V, W)), Info ^ locals, LocalsMap),
+		W = mlds_type_to_ilds_type(V)), Info ^ locals, LocalsMap),
 	map__to_assoc_list(LocalsMap, Locals).
 
 :- pred il_info_get_module_name(mlds_module_name, il_info, il_info).
diff -u compiler/options.m compiler/options.m
--- compiler/options.m
+++ compiler/options.m
@@ -833,6 +833,10 @@
 long_option("debug-pd",			debug_pd).
 long_option("debug-rl-gen",		debug_rl_gen).
 long_option("debug-rl-opt",		debug_rl_opt).
+	% debug-il-asm does very low-level printf style debugging of
+	% IL assember.  Each instruction is written on stdout before it
+	% is executed.  It is a temporary measure until the IL debugging
+	% system built into .NET improves.
 long_option("debug-il-asm",		debug_il_asm).
 
 % output options (mutually exclusive)
@@ -988,7 +992,12 @@
 long_option("cflags-for-regs",		cflags_for_regs).
 long_option("cflags-for-gotos",		cflags_for_gotos).
 long_option("cflags-for-threads",	cflags_for_threads).
-long_option("c-debug",			c_debug).
+	% XXX we should consider the relationship between c_debug and
+	% target_debug more carefully.  Perhaps target_debug could imply
+	% C debug if the target is C.  However for the moment they are
+	% just synonyms.
+long_option("c-debug",			target_debug).
+long_option("target-debug",		target_debug).
 long_option("c-include-directory",	c_include_directory).
 long_option("c-flag-to-name-object-file", c_flag_to_name_object_file).
 long_option("object-file-extension",	object_file_extension).
@@ -997,8 +1006,7 @@
 long_option("cflags-for-regs",		cflags_for_regs).
 long_option("cflags-for-gotos",		cflags_for_gotos).
 long_option("cflags-for-threads",	cflags_for_threads).
-long_option("c-debug",			target_debug).
-long_option("target-debug",		target_debug).
+long_option("c-debug",			c_debug).
 long_option("c-include-directory",	c_include_directory).
 long_option("c-flag-to-name-object-file", c_flag_to_name_object_file).
 long_option("object-file-extension",	object_file_extension).
@@ -2025,6 +2033,18 @@
 		"\tCauses the generated code to become VERY big and VERY",
 		"\tinefficient.  Slows down compilation a LOT.",
 
+		"--target-debug",
+		"\tEnable debugging of the generated target code.",
+		"\tIf the target language is C, this has the same effect as",
+		"`--c-debug' (see below).",
+                "\tIf the target language is IL, this causes the compiler to",
+		"\tpass `/debug' to the IL assembler.)",
+
+		"--c-debug",
+		"\tEnable debugging of the generated C code.",
+		"\t(This has the same effect as",
+		"\t`--cflags ""-g"" --link-flags ""--no-strip""'.)",
+
 		"--no-trad-passes",
 		"\tThe default `--trad-passes' completely processes each predicate",
 		"\tbefore going on to the next predicate.",
@@ -2058,10 +2078,6 @@
 		% are reserved for use by the `mmc' script;
 		% they are deliberately not documented.
 
-		"--c-debug",
-		"\tEnable debugging of the generated C code.",
-		"\t(This has the same effect as",
-		"\t`--cflags ""-g"" --link-flags ""--no-strip""'.)",
 
 		"--c-flag-to-name-object-file <flag>",
 		"\tThe flag the C compiler uses to name object files.",
@@ -2100,10 +2116,7 @@
 		"--fact-table-hash-percent-full <percentage>",
 		"\tSpecify how full the `:- pragma fact_table' hash tables",
 		"\tshould be allowed to get.  Given as an integer percentage",
-		"\t(valid range: 1 to 100, default: 90).",
-
-		"--target-debug",
-		"\tEnable debugging of the generated target code."
+		"\t(valid range: 1 to 100, default: 90)."
 
 % This option is not yet documented because the `--gcc-nested-functions' option
 % is not documented.
diff -u compiler/notes/compiler_design.html compiler/notes/compiler_design.html
--- compiler/notes/compiler_design.html
+++ compiler/notes/compiler_design.html
@@ -947,9 +947,9 @@
 The MLDS->IL backend is broken into several submodules.
 <ul>
 <li> mlds_to_ilasm.m converts MLDS to IL assembler and writes it to a .il file.
-<li> mlds_to_il.m converts MLDS to MSIL 
-<li> ilds.m and ilasm.m contain representations of MSIL, and output
-	routines for writing MSIL to assembler.
+<li> mlds_to_il.m converts MLDS to IL 
+<li> ilds.m contains representations of IL  
+<li> ilasm.m contains output routines for writing IL to assembler.
 <li> il_peephole.m performs peephole optimization on IL instructions.
 </ul>
 After IL assembler has been emitted, ILASM in invoked to turn the .il
only in patch2:
--- doc/user_guide.texi	2000/10/03 00:34:52	1.221
+++ doc/user_guide.texi	2000/10/13 02:13:07
@@ -3563,6 +3563,14 @@
 inefficient, and slows down compilation a lot.
 
 @sp 1
+ at item @code{--target-debug}
+Enable debugging of the generated target code.
+If the target language is C, this has the same effect as
+ at samp{--c-debug} (see below).
+If the target language is IL, this causes the compiler to
+pass @samp{/debug} to the IL assembler.
+
+ at sp 1
 @item --no-trad-passes
 The default @samp{--trad-passes} completely processes each predicate
 before going on to the next predicate.

-- 
       Tyson Dowd           # 
                            #  Surreal humour isn't everyone's cup of fur.
     trd at cs.mu.oz.au        # 
http://www.cs.mu.oz.au/~trd #
--------------------------------------------------------------------------
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