[m-rev.] diff: convert a bunch of modules to four-space indentation

Zoltan Somogyi zs at cs.mu.OZ.AU
Thu Oct 13 09:50:31 AEST 2005


compiler/*.m:
	Convert a bunch of modules to four-space indentation.
	In the process, fix departures from our coding standards.

	In some cases, do minor other cleanups such as changing argument orders
	to be friendly to state variables.

	There are no algorithmic changes.

Zoltan.

cvs diff: Diffing .
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/accumulator.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/accumulator.m,v
retrieving revision 1.42
diff -u -b -r1.42 accumulator.m
--- compiler/accumulator.m	14 Sep 2005 05:26:35 -0000	1.42
+++ compiler/accumulator.m	12 Oct 2005 07:29:41 -0000
@@ -558,7 +558,7 @@
     goal_info_get_instmap_delta(GoalInfo, InstMapDelta),
     instmap__apply_instmap_delta(IM0, InstMapDelta, IM),
 
-    goal_store__det_insert(GS0, Identifier - N, Goal - IM0, GS).
+    goal_store__det_insert(Identifier - N, Goal - IM0, GS0, GS).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -1226,7 +1226,7 @@
 
     process_assoc_set(Ids, GS, OutPrime, ModuleInfo, !Substs,
         !VarSet, !VarTypes, CS0, Warnings0),
-    goal_store__det_insert(CS0, Id, CSGoal, CS),
+    goal_store__det_insert(Id, CSGoal, CS0, CS),
     list__append(Warnings0, Warning, Warnings).
 
 :- pred has_heuristic(module_name::in, string::in, arity::in) is semidet.
@@ -1793,7 +1793,7 @@
         (pred(Id::in, GS0::in, GS::out) is det :-
             goal_store__lookup(From, Id, Goal0 - InstMap),
             goal_util__rename_vars_in_goal(Subst, Goal0, Goal),
-            goal_store__det_insert(GS0, Id, Goal - InstMap, GS)
+            goal_store__det_insert(Id, Goal - InstMap, GS0, GS)
         ), Ids, Initial, Final).
 
     % Return all the goal_ids which belong in the base case.
Index: compiler/backend_libs.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/backend_libs.m,v
retrieving revision 1.9
diff -u -b -r1.9 backend_libs.m
--- compiler/backend_libs.m	6 Mar 2005 05:17:27 -0000	1.9
+++ compiler/backend_libs.m	12 Oct 2005 05:52:01 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
Index: compiler/c_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/c_util.m,v
retrieving revision 1.26
diff -u -b -r1.26 c_util.m
--- compiler/c_util.m	31 Aug 2005 03:08:10 -0000	1.26
+++ compiler/c_util.m	12 Oct 2005 05:59:18 -0000
@@ -1,18 +1,20 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1999-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % File: c_util.m
 % Main author: fjh.
-
-% This module defines utility routines that are useful when
-% generating and/or emitting C code.  Some of these routines are
-% also useful with other languages whose syntax is similar to C.
-
+%
+% This module defines utility routines that are useful when generating and/or
+% emitting C code.  Some of these routines are also useful with other languages
+% whose syntax is similar to C.
+%
 % NOTE: changes to this module may require changes to be made to java_util.m.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module backend_libs__c_util.
@@ -32,119 +34,129 @@
 %-----------------------------------------------------------------------------%
 %
 % Line numbering.
-%
 
 	% set_line_num(FileName, LineNum):
-	%	emit a #line directive to set the specified filename & linenum
-	%	so that C compiler error messages etc. will refer to the
-	%	correct location in the original source file location.
-:- pred c_util__set_line_num(string::in, int::in, io::di, io::uo) is det.
-
-	%	emit a #line directive to cancel the effect of any previous
-	%	#line directives, so that C compiler error messages etc. will
-	%	refer to the appropriate location in the generated .c file.
-:- pred c_util__reset_line_num(io::di, io::uo) is det.
+    %
+    % Emit a #line directive to set the specified filename and linenumber
+    % so that C compiler error messages etc. will refer to the correct location
+    % in the original source file location.
+    %
+:- pred set_line_num(string::in, int::in, io::di, io::uo) is det.
+
+    % Emit a #line directive to cancel the effect of any previous #line
+    % directives, so that C compiler error messages etc. will refer to the
+    % appropriate location in the generated .c file.
+    %
+:- pred reset_line_num(io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 %
 % String and character handling.
-%
 
 	% Print out a string suitably escaped for use as a C string literal.
 	% This doesn't actually print out the enclosing double quotes --
 	% that is the caller's responsibility.
-:- pred c_util__output_quoted_string(string::in, io::di, io::uo) is det.
+    %
+:- pred output_quoted_string(string::in, io::di, io::uo) is det.
 
-	% output_quoted_multi_string is like output_quoted_string
-	% except that the string may contain embedded NUL characters
-	% (i.e. '\0').  The int specifies the length of the string.
+    % Output_quoted_multi_string is like output_quoted_string except that
+    % the string may contain embedded NUL characters (i.e. '\0').
+    % The int specifies the length of the string.
+    %
 :- type multi_string == string.
-:- pred c_util__output_quoted_multi_string(int::in, multi_string::in,
+:- pred output_quoted_multi_string(int::in, multi_string::in,
 	io::di, io::uo) is det.
 
 	% Print out a char suitably escaped for use as a C char literal.
 	% This doesn't actually print out the enclosing single quotes --
 	% that is the caller's responsibility.
-:- pred c_util__output_quoted_char(char::in, io::di, io::uo) is det.
+    %
+:- pred output_quoted_char(char::in, io::di, io::uo) is det.
 
 	% Convert a string to a form that is suitably escaped for use as a
-	% C string literal.  This doesn't actually add the enclosing double
-	% quotes -- that is the caller's responsibility.
-:- pred c_util__quote_string(string::in, string::out) is det.
+    % C string literal. This doesn't actually add the enclosing double quotes
+    % -- that is the caller's responsibility.
+    %
+:- pred quote_string(string::in, string::out) is det.
 
 	% Convert a character to a form that is suitably escaped for use as a
 	% C character literal.  This doesn't actually add the enclosing single
 	% quotes -- that is the caller's responsibility.
-:- pred c_util__quote_char(char::in, string::out) is det.
+    %
+:- pred quote_char(char::in, string::out) is det.
 
 %-----------------------------------------------------------------------------%
 %
 % Float literals.
-%
 
 	% Convert a float to a string suitable for use as a C (or Java, or IL)
 	% floating point literal.
-:- func c_util__make_float_literal(float) = string.
+    %
+:- func make_float_literal(float) = string.
 
 	% As above, but write the string to the current output stream
 	% rather than returning it.
-:- pred c_util__output_float_literal(float::in, io::di, io::uo) is det.
+    %
+:- pred output_float_literal(float::in, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 %
 % Operators.
 %
-% The following predicates all take as input an operator,
-% check if it is an operator of the specified kind,
-% and if so, return the name of the corresponding C operator
-% that can be used to implement it.
-%
+% The following predicates all take as input an operator, check if it is
+% an operator of the specified kind, and if so, return the name of the
+% corresponding C operator that can be used to implement it.
 
 	% The operator returned will be <, >, etc.;
 	% it can be used in the form `strcmp(<Arg1>, <Arg2>) <Op> 0'.
 	%
-:- pred c_util__string_compare_op(binary_op::in, string::out) is semidet.
+:- pred string_compare_op(binary_op::in, string::out) is semidet.
 
 	% The operator returned will be +, *, etc.;
 	% the arguments should be floats and the result will be a float.
-:- pred c_util__float_op(binary_op::in, string::out) is semidet.
+    %
+:- pred float_op(binary_op::in, string::out) is semidet.
 
 	% The operator returned will be <, >, etc.;
 	% the arguments should be floats and the result will be a boolean.
-:- pred c_util__float_compare_op(binary_op::in, string::out) is semidet.
+    %
+:- pred float_compare_op(binary_op::in, string::out) is semidet.
 
-	% The operator returned will be an infix operator.
-	% The arguments should be cast to MR_Unsigned,
-	% and the result will be a boolean.
-:- pred c_util__unsigned_compare_op(binary_op::in, string::out) is semidet.
+    % The operator returned will be an infix operator. The arguments should be
+    % cast to MR_Unsigned, and the result will be a boolean.
+    %
+:- pred unsigned_compare_op(binary_op::in, string::out) is semidet.
 
-	% The operator returned will be either a prefix operator
-	% or a macro or function name.  The operand needs
-	% to be placed in parentheses after the operator name.
-:- pred c_util__unary_prefix_op(unary_op::in, string::out) is det.
+    % The operator returned will be either a prefix operator or a macro
+    % or function name. The operand needs to be placed in parentheses
+    % after the operator name.
+    %
+:- pred unary_prefix_op(unary_op::in, string::out) is det.
 
-	% The operator returned will be an infix operator.
-	% The arguments should be integer or booleans
-	% and the result will be an integer or a boolean.
-:- pred c_util__binary_infix_op(binary_op::in, string::out) is semidet.
+    % The operator returned will be an infix operator. The arguments should be
+    % integer or booleans and the result will be an integer or a boolean.
+    %
+:- pred binary_infix_op(binary_op::in, string::out) is semidet.
 
 %-----------------------------------------------------------------------------%
 
-	% Currently the `.rlo' files are stored as static data in the
-	% executable. It may be better to store them in separate files
-	% in a known location and load them at runtime.
-:- pred c_util__output_rl_file(module_name::in, maybe(rl_file)::in,
-	io::di, io::uo) is det.
+    % Currently the `.rlo' files are stored as static data in the executable.
+    % It may be better to store them in separate files in a known location
+    % and load them at runtime.
+    %
+:- pred output_rl_file(module_name::in, maybe(rl_file)::in, io::di, io::uo)
+    is det.
 
 %-----------------------------------------------------------------------------%
 
-	% output_c_file_intro_and_grade(SourceFileName, Version)
-	% outputs a comment which includes the settings used to generate
-	% the C file.  This is used by configure to check the any
-	% existing C files are consistent with the current
-	% configuration.  SourceFileName is the name of the file from
-	% which the C is generated, while Version is the version name
-	% of the mercury compiler.
+    % output_c_file_intro_and_grade(SourceFileName, Version):
+    %
+    % Outputs a comment which includes the settings used to generate
+    % the C file. This is used by configure to check the any existing C files
+    % are consistent with the current configuration. SourceFileName is the
+    % name of the file from which the C is generated, while Version is the
+    % version name of the mercury compiler.
+    %
 :- pred output_c_file_intro_and_grade(string::in, string::in,
 	io::di, io::uo) is det.
 
@@ -164,11 +176,11 @@
 %-----------------------------------------------------------------------------%
 %
 % Line numbering.
-%
 
-c_util__set_line_num(File, Line, !IO) :-
+set_line_num(File, Line, !IO) :-
 	globals__io_lookup_bool_option(line_numbers, LineNumbers, !IO),
-	( LineNumbers = yes ->
+    (
+        LineNumbers = yes,
 		(
 			Line > 0,
 			File \= ""
@@ -176,16 +188,16 @@
 			io__write_string("#line ", !IO),
 			io__write_int(Line, !IO),
 			io__write_string(" """, !IO),
-			c_util__output_quoted_string(File, !IO),
+            output_quoted_string(File, !IO),
 			io__write_string("""\n", !IO)
 		;
-			c_util__reset_line_num(!IO)
+            reset_line_num(!IO)
 		)
 	;
-		true
+        LineNumbers = no
 	).
 
-c_util__reset_line_num(!IO) :-
+reset_line_num(!IO) :-
 	% We want to generate another #line directive to reset the C compiler's
 	% idea of what it is processing back to the file we are generating.
 	io__get_output_line_number(Line, !IO),
@@ -199,7 +211,7 @@
 		io__write_string("#line ", !IO),
 		io__write_int(Line + 1, !IO),
 		io__write_string(" """, !IO),
-		c_util__output_quoted_string(FileName, !IO),
+        output_quoted_string(FileName, !IO),
 		io__write_string("""\n", !IO)
 	;
 		true
@@ -208,41 +220,39 @@
 %-----------------------------------------------------------------------------%
 %
 % String and character handling.
-%
 
-c_util__output_quoted_string(S0, !IO) :-
-	c_util__output_quoted_multi_string(string__length(S0), S0, !IO).
+output_quoted_string(S0, !IO) :-
+    output_quoted_multi_string(string__length(S0), S0, !IO).
 
-c_util__output_quoted_multi_string(Len, S, !IO) :-
-	c_util__output_quoted_multi_string_2(0, Len, S, !IO).
+output_quoted_multi_string(Len, S, !IO) :-
+    output_quoted_multi_string_2(0, Len, S, !IO).
 
-:- pred c_util__output_quoted_multi_string_2(int::in, int::in, string::in,
+:- pred output_quoted_multi_string_2(int::in, int::in, string::in,
 	io::di, io::uo) is det.
 
-c_util__output_quoted_multi_string_2(Cur, Len, S, !IO) :-
+output_quoted_multi_string_2(Cur, Len, S, !IO) :-
 	( Cur < Len ->
-			% Avoid a limitation in the MSVC compiler where
-			% string literals can be no longer then 2048
-			% chars.  However if you output the string in
-			% chunks, eg "part a" "part b" it will accept a
-			% string longer then 2048 chars, go figure!
-		( Cur \= 0, Cur mod 512 = 0 ->
+        % Avoid a limitation in the MSVC compiler where string literals
+        % can be no longer then 2048 chars. However if you output the string
+        % in chunks, eg "part a" "part b" it will accept a string longer than
+        % 2048 chars, go figure!
+        (
+            Cur \= 0,
+            Cur mod 512 = 0
+        ->
 			io__write_string("\" \"", !IO)
 		;
 			true
 		),
 
-			% we must use unsafe index, because we want to be able
-			% to access chars beyond the first NUL
+        % We must use unsafe index, because we want to be able to access chars
+        % beyond the first NUL.
 		string__unsafe_index(S, Cur, Char),
-		c_util__output_quoted_char(Char, !IO),
+        output_quoted_char(Char, !IO),
 		
-		%
-		% Check for trigraph sequences in string literals.
-		% We break the trigraph by breaking the string into 
-		% multiple chunks.  For example "??-" gets converted to
-		% "?" "?-".
-		%
+        % Check for trigraph sequences in string literals. We break the
+        % trigraph by breaking the string into multiple chunks. For example,
+        % "??-" gets converted to "?" "?-".
 		(
 			Char = '?',
 			Cur < Len + 2
@@ -265,45 +275,44 @@
 		true
 	).
 
-c_util__output_quoted_char(Char, !IO) :-
-	c_util__quote_char(Char, EscapedChars),
+output_quoted_char(Char, !IO) :-
+    quote_char(Char, EscapedChars),
 	io__write_string(EscapedChars, !IO).
 
-c_util__quote_char(Char, QuotedChar) :-
-	c_util__quote_one_char(Char, [], RevQuotedChar),
+quote_char(Char, QuotedChar) :-
+    quote_one_char(Char, [], RevQuotedChar),
 	string__from_rev_char_list(RevQuotedChar, QuotedChar).
 
-c_util__quote_string(String, QuotedString) :-
-	string__foldl(c_util__quote_one_char, String, [], RevQuotedChars),
+quote_string(String, QuotedString) :-
+    string__foldl(quote_one_char, String, [], RevQuotedChars),
 	string__from_rev_char_list(RevQuotedChars, QuotedString).
 
-:- pred c_util__quote_one_char(char::in, list(char)::in, list(char)::out)
-	is det.
+:- pred quote_one_char(char::in, list(char)::in, list(char)::out) is det.
 
-c_util__quote_one_char(Char, RevChars0, RevChars) :-
-	( c_util__escape_special_char(Char, EscapeChar) ->
+quote_one_char(Char, RevChars0, RevChars) :-
+    ( escape_special_char(Char, EscapeChar) ->
 		RevChars = [EscapeChar, '\\' | RevChars0]
-	; c_util__is_c_source_char(Char) ->
+    ; is_c_source_char(Char) ->
 		RevChars = [Char | RevChars0]
 	; char__to_int(Char, 0) ->
 		RevChars = ['0', '\\' | RevChars0]
 	;
-		c_util__escape_any_char(Char, EscapeChars),
+        escape_any_char(Char, EscapeChars),
 		reverse_append(EscapeChars, RevChars0, RevChars)
 	).
 
-:- pred c_util__escape_special_char(char::in, char::out) is semidet.
+:- pred escape_special_char(char::in, char::out) is semidet.
 
-c_util__escape_special_char('"', '"').
-c_util__escape_special_char('''', '''').
-c_util__escape_special_char('\\', '\\').
-c_util__escape_special_char('\n', 'n').
-c_util__escape_special_char('\t', 't').
-c_util__escape_special_char('\b', 'b').
-c_util__escape_special_char('\a', 'a').
-c_util__escape_special_char('\v', 'v').
-c_util__escape_special_char('\r', 'r').
-c_util__escape_special_char('\f', 'f').
+escape_special_char('"', '"').
+escape_special_char('''', '''').
+escape_special_char('\\', '\\').
+escape_special_char('\n', 'n').
+escape_special_char('\t', 't').
+escape_special_char('\b', 'b').
+escape_special_char('\a', 'a').
+escape_special_char('\v', 'v').
+escape_special_char('\r', 'r').
+escape_special_char('\f', 'f').
 
 	% Succeed if the given character, prefixed with "??", is a trigraph.
 	%
@@ -321,23 +330,24 @@
 
 	% This succeeds iff the specified character is allowed as an (unescaped)
 	% character in standard-conforming C source code.
+    %
+:- pred is_c_source_char(char::in) is semidet.
 
-:- pred c_util__is_c_source_char(char::in) is semidet.
-
-c_util__is_c_source_char(Char) :-
+is_c_source_char(Char) :-
 	( char__is_alnum(Char)
 	; string__contains_char(c_graphic_chars, Char)
 	).
 
-	% This returns a string containing all the characters that the C
-	% standard specifies as being included in the "basic execution
-	% character set", except for the letters (a-z A-Z) and digits (0-9).
-
+    % This returns a string containing all the characters that the C standard
+    % specifies as being included in the "basic execution character set",
+    % except for the letters (a-z A-Z) and digits (0-9).
+    %
 :- func c_graphic_chars = string.
 
 c_graphic_chars = " !\"#%&'()*+,-./:;<=>?[\\]^_{|}~".
 
 	% reverse_append(Xs, Ys, Zs) <=> Zs = list__reverse(Xs) ++ Ys.
+    %
 :- pred reverse_append(list(T)::in, list(T)::in, list(T)::out) is det.
 
 reverse_append([], L, L).
@@ -349,6 +359,7 @@
         % Convert a character to the corresponding C octal escape code.
 	% XXX This assumes that the target language compiler's representation
 	%     of characters is the same as the Mercury compiler's.
+    %
 escape_any_char(Char, EscapeCodeChars) :-
         char__to_int(Char, Int),
         string__int_to_base_string(Int, 8, OctalString0),
@@ -361,15 +372,13 @@
 %
 % XXX These routines do not yet handle infinities and NaNs properly.
 
+make_float_literal(Float) = string__format("%#.17g", [f(Float)]).
 	% This is used by the C, Java, and IL back-ends,
 	% so the output must be valid syntax in all three languages.
 	%
-	% We output literals using 17 digits of precision.
-	% This is the minimum needed to be able to convert IEEE
-	% double-precision floating point values to strings and
-	% back again without losing precision.
-	%
-make_float_literal(Float) = string__format("%#.17g", [f(Float)]).
+    % We output literals using 17 digits of precision. This is the minimum
+    % needed to be able to convert IEEE double-precision floating point values
+    % to strings and back again without losing precision.
 
 output_float_literal(Float, !IO) :-
 	io__write_string(make_float_literal(Float), !IO).
@@ -377,76 +386,73 @@
 %-----------------------------------------------------------------------------%
 %
 % Operators.
-%
 
-c_util__unary_prefix_op(mktag,			"MR_mktag").
-c_util__unary_prefix_op(tag,			"MR_tag").
-c_util__unary_prefix_op(unmktag,		"MR_unmktag").
-c_util__unary_prefix_op(mkbody,			"MR_mkbody").
-c_util__unary_prefix_op(unmkbody,		"MR_unmkbody").
-c_util__unary_prefix_op(strip_tag,		"MR_strip_tag").
-c_util__unary_prefix_op(hash_string,		"MR_hash_string").
-c_util__unary_prefix_op(bitwise_complement,	"~").
-c_util__unary_prefix_op(not,			"!").
-
-c_util__string_compare_op(str_eq, "==").
-c_util__string_compare_op(str_ne, "!=").
-c_util__string_compare_op(str_le, "<=").
-c_util__string_compare_op(str_ge, ">=").
-c_util__string_compare_op(str_lt, "<").
-c_util__string_compare_op(str_gt, ">").
-
-c_util__unsigned_compare_op(unsigned_le, "<=").
-
-c_util__float_op(float_plus, "+").
-c_util__float_op(float_minus, "-").
-c_util__float_op(float_times, "*").
-c_util__float_op(float_divide, "/").
-
-c_util__float_compare_op(float_eq, "==").
-c_util__float_compare_op(float_ne, "!=").
-c_util__float_compare_op(float_le, "<=").
-c_util__float_compare_op(float_ge, ">=").
-c_util__float_compare_op(float_lt, "<").
-c_util__float_compare_op(float_gt, ">").
-
-c_util__binary_infix_op(+, "+").
-c_util__binary_infix_op(-, "-").
-c_util__binary_infix_op(*, "*").
-c_util__binary_infix_op(/, "/").
-c_util__binary_infix_op(<<, "<<").
-c_util__binary_infix_op(>>, ">>").
-c_util__binary_infix_op(&, "&").
-c_util__binary_infix_op('|', "|").
-c_util__binary_infix_op(^, "^").
-c_util__binary_infix_op(mod, "%").
-c_util__binary_infix_op(eq, "==").
-c_util__binary_infix_op(ne, "!=").
-c_util__binary_infix_op(and, "&&").
-c_util__binary_infix_op(or, "||").
-c_util__binary_infix_op(<, "<").
-c_util__binary_infix_op(>, ">").
-c_util__binary_infix_op(<=, "<=").
-c_util__binary_infix_op(>=, ">=").
+unary_prefix_op(mktag,              "MR_mktag").
+unary_prefix_op(tag,                "MR_tag").
+unary_prefix_op(unmktag,            "MR_unmktag").
+unary_prefix_op(mkbody,             "MR_mkbody").
+unary_prefix_op(unmkbody,           "MR_unmkbody").
+unary_prefix_op(strip_tag,          "MR_strip_tag").
+unary_prefix_op(hash_string,        "MR_hash_string").
+unary_prefix_op(bitwise_complement, "~").
+unary_prefix_op(not,                "!").
+
+string_compare_op(str_eq, "==").
+string_compare_op(str_ne, "!=").
+string_compare_op(str_le, "<=").
+string_compare_op(str_ge, ">=").
+string_compare_op(str_lt, "<").
+string_compare_op(str_gt, ">").
+
+unsigned_compare_op(unsigned_le, "<=").
+
+float_op(float_plus, "+").
+float_op(float_minus, "-").
+float_op(float_times, "*").
+float_op(float_divide, "/").
+
+float_compare_op(float_eq, "==").
+float_compare_op(float_ne, "!=").
+float_compare_op(float_le, "<=").
+float_compare_op(float_ge, ">=").
+float_compare_op(float_lt, "<").
+float_compare_op(float_gt, ">").
+
+binary_infix_op(+, "+").
+binary_infix_op(-, "-").
+binary_infix_op(*, "*").
+binary_infix_op(/, "/").
+binary_infix_op(<<, "<<").
+binary_infix_op(>>, ">>").
+binary_infix_op(&, "&").
+binary_infix_op('|', "|").
+binary_infix_op(^, "^").
+binary_infix_op(mod, "%").
+binary_infix_op(eq, "==").
+binary_infix_op(ne, "!=").
+binary_infix_op(and, "&&").
+binary_infix_op(or, "||").
+binary_infix_op(<, "<").
+binary_infix_op(>, ">").
+binary_infix_op(<=, "<=").
+binary_infix_op(>=, ">=").
 
 %-----------------------------------------------------------------------------%
 
-c_util__output_rl_file(ModuleName, MaybeRLFile, !IO) :-
+output_rl_file(ModuleName, MaybeRLFile, !IO) :-
 	globals__io_lookup_bool_option(aditi, Aditi, !IO),
 	(
 		Aditi = no
 	;
 		Aditi = yes,
-		io__write_string("\n\n/* Aditi-RL code for this module. */\n",
-			!IO),
+        io__write_string("\n\n/* Aditi-RL code for this module. */\n", !IO),
 		RLDataConstName = make_rl_data_name(ModuleName),
 		io__write_string("const char ", !IO),
 		io__write_string(RLDataConstName, !IO),
 		io__write_string("[] = {", !IO),
 		(
 			MaybeRLFile = yes(RLFile),
-			rl_file__write_binary(c_util__output_rl_byte,
-				RLFile, Length, !IO),
+            rl_file__write_binary(output_rl_byte, RLFile, Length, !IO),
 			io__write_string("0};\n", !IO)
 		;
 			MaybeRLFile = no,
@@ -465,9 +471,9 @@
 		io__write_string(";\n\n", !IO)
 	).
 
-:- pred c_util__output_rl_byte(int::in, io::di, io::uo) is det.
+:- pred output_rl_byte(int::in, io::di, io::uo) is det.
 
-c_util__output_rl_byte(Byte, !IO) :-
+output_rl_byte(Byte, !IO) :-
 	io__write_int(Byte, !IO),
 	io__write_string(", ", !IO).
 
Index: compiler/check_hlds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/check_hlds.m,v
retrieving revision 1.9
diff -u -b -r1.9 check_hlds.m
--- compiler/check_hlds.m	23 Apr 2005 06:29:46 -0000	1.9
+++ compiler/check_hlds.m	12 Oct 2005 06:00:00 -0000
@@ -1,12 +1,12 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
 %
-% check_hlds: semantic analysis and error checking
-%	(the "front end" HLDS pass).
-%
+% check_hlds: semantic analysis and error checking (the "front end" HLDS pass).
 
 :- module check_hlds.
 :- interface.
Index: compiler/code_model.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_model.m,v
retrieving revision 1.7
diff -u -b -r1.7 code_model.m
--- compiler/code_model.m	31 Mar 2005 04:44:21 -0000	1.7
+++ compiler/code_model.m	12 Oct 2005 06:01:10 -0000
@@ -1,24 +1,26 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2000, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
-:- module hlds__code_model.
-
+%
 % This module defines the `code_model' data type, and associated procedures.
 % The `code_model' type is a simplified version of the `determinism' type
 % that is defined in prog_data.m.  It ignores most of the distinctions in
 % the determinism type and keeps only the distinctions that are important
 % for code generation.
-
+%
 % We define this in a different module than the `determinism' type because
 % it is only used by some of the different back-ends, not all of them.
 % It is used by the MLDS, LLDS, and bytecode back-ends, but not by the
 % Aditi-RL back-end.
-
+%
 %-----------------------------------------------------------------------------%
 
+:- module hlds__code_model.
+
 :- interface.
 
 :- import_module hlds__hlds_goal.
@@ -38,16 +40,16 @@
 
 :- pred goal_info_get_code_model(hlds_goal_info::in, code_model::out) is det.
 
-	% Construct a representation of the interface determinism of a
-	% procedure. The code we have chosen is not sequential; instead
-	% it encodes the various properties of each determinism.
-	% This must match the encoding of MR_Determinism in
-	% mercury_stack_layout.h.
+    % Construct a representation of the interface determinism of a procedure.
+    % The code we have chosen is not sequential; instead it encodes the various
+    % properties of each determinism. This must match the encoding of
+    % MR_Determinism in mercury_stack_layout.h.
 	%
 	% The 8 bit is set iff the context is first_solution.
 	% The 4 bit is set iff the min number of solutions is more than zero.
 	% The 2 bit is set iff the max number of solutions is more than zero.
 	% The 1 bit is set iff the max number of solutions is more than one.
+    %
 :- func represent_determinism(determinism) = int.
 
 %-----------------------------------------------------------------------------%
Index: compiler/code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_util.m,v
retrieving revision 1.156
diff -u -b -r1.156 code_util.m
--- compiler/code_util.m	24 Mar 2005 05:33:59 -0000	1.156
+++ compiler/code_util.m	12 Oct 2005 06:55:04 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1994-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -29,70 +31,65 @@
 :- import_module list.
 :- import_module std_util.
 
-	% Create a code address which holds the address of the specified
-	% procedure.
-	% The `immed' argument should be `no' if the the caller wants the
-	% returned address to be valid from everywhere in the program.
-	% If being valid from within the current procedure is enough,
-	% this argument should be `yes' wrapped around the value of the
-	% --procs-per-c-function option and the current procedure id.
-	% Using an address that is only valid from within the current
-	% procedure may make jumps more efficient.
-
+    % Create a code address which holds the address of the specified procedure.
+    % The `immed' argument should be `no' if the the caller wants the returned
+    % address to be valid from everywhere in the program. If being valid from
+    % within the current procedure is enough, this argument should be `yes'
+    % wrapped around the value of the --procs-per-c-function option and the
+    % current procedure id. Using an address that is only valid from within
+    % the current procedure may make jumps more efficient.
+    %
 :- type immed == maybe(pair(int, pred_proc_id)).
+:- pred make_entry_label(module_info::in, pred_id::in, proc_id::in, immed::in,
+    code_addr::out) is det.
 
-:- pred code_util__make_entry_label(module_info::in, pred_id::in, proc_id::in,
-	immed::in, code_addr::out) is det.
-
-:- pred code_util__make_entry_label_from_rtti(rtti_proc_label::in, immed::in,
+:- pred make_entry_label_from_rtti(rtti_proc_label::in, immed::in,
 	code_addr::out) is det.
 
 	% Create a label which holds the address of the specified procedure,
 	% which must be defined in the current module (procedures that are
 	% imported from other modules have representations only as code_addrs,
-	% not as labels, since their address is not known at C compilation
-	% time).
-	% The fourth argument has the same meaning as for
-	% code_util__make_entry_label.
-
-:- pred code_util__make_local_entry_label(module_info::in,
-	pred_id::in, proc_id::in, immed::in, label::out) is det.
+    % not as labels, since their address is not known at C compilation time).
+    % The fourth argument has the same meaning as for make_entry_label.
+    %
+:- pred make_local_entry_label(module_info::in, pred_id::in, proc_id::in,
+    immed::in, label::out) is det.
 
 	% Create a label internal to a Mercury procedure.
-:- pred code_util__make_internal_label(module_info::in,
-	pred_id::in, proc_id::in, int::in, label::out) is det.
+    %
+:- pred make_internal_label(module_info::in, pred_id::in, proc_id::in, int::in,
+    label::out) is det.
 
-:- pred code_util__extract_proc_label_from_code_addr(code_addr::in,
-	proc_label::out) is det.
+:- pred extract_proc_label_from_code_addr(code_addr::in, proc_label::out)
+    is det.
 
-:- pred code_util__arg_loc_to_register(arg_loc::in, lval::out) is det.
+:- pred arg_loc_to_register(arg_loc::in, lval::out) is det.
 
-:- pred code_util__max_mentioned_reg(list(lval)::in, int::out) is det.
-:- pred code_util__max_mentioned_abs_reg(list(abs_locn)::in, int::out) is det.
+:- pred max_mentioned_reg(list(lval)::in, int::out) is det.
+:- pred max_mentioned_abs_reg(list(abs_locn)::in, int::out) is det.
 
-:- pred code_util__goal_may_alloc_temp_frame(hlds_goal::in) is semidet.
+:- pred goal_may_alloc_temp_frame(hlds_goal::in) is semidet.
 
 	% Negate a condition.
 	% This is used mostly just to make the generated code more readable.
+    %
+:- pred neg_rval(rval::in, rval::out) is det.
 
-:- pred code_util__neg_rval(rval::in, rval::out) is det.
-
-:- pred code_util__negate_the_test(list(instruction)::in,
-	list(instruction)::out) is det.
+:- pred negate_the_test(list(instruction)::in, list(instruction)::out) is det.
 
 	% These predicates return the set of lvals referenced in an rval
 	% and an lval respectively. Lvals referenced indirectly through
 	% lvals of the form var(_) are not counted.
-
-:- pred code_util__lvals_in_rval(rval::in, list(lval)::out) is det.
-:- pred code_util__lvals_in_lval(lval::in, list(lval)::out) is det.
-:- pred code_util__lvals_in_lvals(list(lval)::in, list(lval)::out) is det.
+    %
+:- pred lvals_in_rval(rval::in, list(lval)::out) is det.
+:- pred lvals_in_lval(lval::in, list(lval)::out) is det.
+:- pred lvals_in_lvals(list(lval)::in, list(lval)::out) is det.
 
 	% Given a procedure that already has its arg_info field filled in,
 	% return a list giving its input variables and their initial locations.
-
-:- pred build_input_arg_list(proc_info::in,
-	assoc_list(prog_var, lval)::out) is det.
+    %
+:- pred build_input_arg_list(proc_info::in, assoc_list(prog_var, lval)::out)
+    is det.
 
 %---------------------------------------------------------------------------%
 
@@ -105,6 +102,7 @@
 :- import_module hlds__special_pred.
 :- import_module libs__globals.
 :- import_module libs__options.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_util.
 
 :- import_module bool.
@@ -118,35 +116,33 @@
 
 %---------------------------------------------------------------------------%
 
-code_util__make_entry_label(ModuleInfo, PredId, ProcId, Immed, ProcAddr) :-
+make_entry_label(ModuleInfo, PredId, ProcId, Immed, ProcAddr) :-
 	RttiProcLabel = rtti__make_rtti_proc_label(ModuleInfo, PredId, ProcId),
-	code_util__make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr).
+    make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr).
 
-code_util__make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr) :-
+make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr) :-
 	( RttiProcLabel ^ proc_is_imported = yes ->
 		ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
 		ProcAddr = imported(ProcLabel)
 	;
-		code_util__make_local_entry_label_from_rtti(RttiProcLabel,
-			Immed, Label),
+        make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label),
 		ProcAddr = label(Label)
 	).
 
-code_util__make_local_entry_label(ModuleInfo, PredId, ProcId, Immed, Label) :-
+make_local_entry_label(ModuleInfo, PredId, ProcId, Immed, Label) :-
 	RttiProcLabel = rtti__make_rtti_proc_label(ModuleInfo, PredId, ProcId),
-	code_util__make_local_entry_label_from_rtti(RttiProcLabel,
-		Immed, Label).
+    make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label).
 
-:- pred code_util__make_local_entry_label_from_rtti(rtti_proc_label::in,
+:- pred make_local_entry_label_from_rtti(rtti_proc_label::in,
 	immed::in, label::out) is det.
 
-code_util__make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label) :-
+make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label) :-
 	ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
 	(
 		Immed = no,
-		% If we want to define the label or use it to put it
-		% into a data structure, a label that is usable only
-		% within the current C module won't do.
+        % If we want to define the label or use it to put it into a data
+        % structure, a label that is usable only within the current C module
+        % won't do.
 		( RttiProcLabel ^ proc_is_exported = yes ->
 			EntryType = exported
 		;
@@ -166,10 +162,9 @@
 choose_local_label_type(ProcsPerFunc, CurPredId, CurProcId,
 		PredId, ProcId, ProcLabel, Label) :-
 	(
-		% If we want to branch to the label now,
-		% we prefer a form that are usable only within
-		% the current C module, since it is likely
-		% to be faster.
+        % If we want to branch to the label now, we prefer a form that is
+        % usable only within the current C module, since it is likely to be
+        % faster.
 		(
 			ProcsPerFunc = 0
 		;
@@ -185,250 +180,244 @@
 
 %-----------------------------------------------------------------------------%
 
-code_util__make_internal_label(ModuleInfo, PredId, ProcId, LabelNum, Label) :-
+make_internal_label(ModuleInfo, PredId, ProcId, LabelNum, Label) :-
 	ProcLabel = make_proc_label(ModuleInfo, PredId, ProcId),
 	Label = internal(LabelNum, ProcLabel).
 
-code_util__extract_proc_label_from_code_addr(CodeAddr, ProcLabel) :-
+extract_proc_label_from_code_addr(CodeAddr, ProcLabel) :-
 	( CodeAddr = label(Label) ->
 		ProcLabel = get_proc_label(Label)
 	; CodeAddr = imported(ProcLabelPrime) ->
 		ProcLabel = ProcLabelPrime
 	;
-		error("code_util__extract_label_from_code_addr failed")
+        unexpected(this_file, "extract_label_from_code_addr failed")
 	).
 
 %-----------------------------------------------------------------------------%
 
-code_util__arg_loc_to_register(ArgLoc, reg(r, ArgLoc)).
+arg_loc_to_register(ArgLoc, reg(r, ArgLoc)).
 
 %-----------------------------------------------------------------------------%
 
-code_util__max_mentioned_reg(Lvals, MaxRegNum) :-
-	code_util__max_mentioned_reg_2(Lvals, 0, MaxRegNum).
+max_mentioned_reg(Lvals, MaxRegNum) :-
+    max_mentioned_reg_2(Lvals, 0, MaxRegNum).
 
-:- pred code_util__max_mentioned_reg_2(list(lval)::in, int::in, int::out)
-	is det.
+:- pred max_mentioned_reg_2(list(lval)::in, int::in, int::out) is det.
 
-code_util__max_mentioned_reg_2([], !MaxRegNum).
-code_util__max_mentioned_reg_2([Lval | Lvals], !MaxRegNum) :-
+max_mentioned_reg_2([], !MaxRegNum).
+max_mentioned_reg_2([Lval | Lvals], !MaxRegNum) :-
 	( Lval = reg(r, N) ->
 		int__max(N, !MaxRegNum)
 	;
 		true
 	),
-	code_util__max_mentioned_reg_2(Lvals, !MaxRegNum).
+    max_mentioned_reg_2(Lvals, !MaxRegNum).
 
-code_util__max_mentioned_abs_reg(Lvals, MaxRegNum) :-
-	code_util__max_mentioned_abs_reg_2(Lvals, 0, MaxRegNum).
+max_mentioned_abs_reg(Lvals, MaxRegNum) :-
+    max_mentioned_abs_reg_2(Lvals, 0, MaxRegNum).
 
-:- pred code_util__max_mentioned_abs_reg_2(list(abs_locn)::in,
-	int::in, int::out) is det.
+:- pred max_mentioned_abs_reg_2(list(abs_locn)::in, int::in, int::out) is det.
 
-code_util__max_mentioned_abs_reg_2([], !MaxRegNum).
-code_util__max_mentioned_abs_reg_2([Lval | Lvals], !MaxRegNum) :-
+max_mentioned_abs_reg_2([], !MaxRegNum).
+max_mentioned_abs_reg_2([Lval | Lvals], !MaxRegNum) :-
 	( Lval = abs_reg(N) ->
 		int__max(N, !MaxRegNum)
 	;
 		true
 	),
-	code_util__max_mentioned_abs_reg_2(Lvals, !MaxRegNum).
+    max_mentioned_abs_reg_2(Lvals, !MaxRegNum).
 
 %-----------------------------------------------------------------------------%
 
-code_util__goal_may_alloc_temp_frame(Goal) :-
-	code_util__goal_may_alloc_temp_frame(Goal, yes).
+goal_may_alloc_temp_frame(Goal) :-
+    goal_may_alloc_temp_frame(Goal, yes).
 
-:- pred code_util__goal_may_alloc_temp_frame(hlds_goal::in, bool::out) is det.
+:- pred goal_may_alloc_temp_frame(hlds_goal::in, bool::out) is det.
 
-code_util__goal_may_alloc_temp_frame(Goal - _GoalInfo, May) :-
-	code_util__goal_may_alloc_temp_frame_2(Goal, May).
+goal_may_alloc_temp_frame(Goal - _GoalInfo, May) :-
+    goal_may_alloc_temp_frame_2(Goal, May).
 
-:- pred code_util__goal_may_alloc_temp_frame_2(hlds_goal_expr::in, bool::out)
+:- pred goal_may_alloc_temp_frame_2(hlds_goal_expr::in, bool::out)
 	is det.
 
-code_util__goal_may_alloc_temp_frame_2(generic_call(_, _, _, _), no).
-code_util__goal_may_alloc_temp_frame_2(call(_, _, _, _, _, _), no).
-code_util__goal_may_alloc_temp_frame_2(unify(_, _, _, _, _), no).
+goal_may_alloc_temp_frame_2(generic_call(_, _, _, _), no).
+goal_may_alloc_temp_frame_2(call(_, _, _, _, _, _), no).
+goal_may_alloc_temp_frame_2(unify(_, _, _, _, _), no).
 	% We cannot safely say that a foreign code fragment does not allocate
 	% temporary nondet frames without knowing all the #defined macros
 	% that expand to mktempframe and variants thereof. The performance
 	% impact of being too conservative is probably not too bad.
-code_util__goal_may_alloc_temp_frame_2(foreign_proc(_, _, _, _, _, _), yes).
-code_util__goal_may_alloc_temp_frame_2(scope(_, Goal), May) :-
+goal_may_alloc_temp_frame_2(foreign_proc(_, _, _, _, _, _), yes).
+goal_may_alloc_temp_frame_2(scope(_, Goal), May) :-
 	Goal = _ - GoalInfo,
 	goal_info_get_code_model(GoalInfo, CodeModel),
 	( CodeModel = model_non ->
 		May = yes
 	;
-		code_util__goal_may_alloc_temp_frame(Goal, May)
+        goal_may_alloc_temp_frame(Goal, May)
 	).
-code_util__goal_may_alloc_temp_frame_2(not(Goal), May) :-
-	code_util__goal_may_alloc_temp_frame(Goal, May).
-code_util__goal_may_alloc_temp_frame_2(conj(Goals), May) :-
-	code_util__goal_list_may_alloc_temp_frame(Goals, May).
-code_util__goal_may_alloc_temp_frame_2(par_conj(Goals), May) :-
-	code_util__goal_list_may_alloc_temp_frame(Goals, May).
-code_util__goal_may_alloc_temp_frame_2(disj(Goals), May) :-
-	code_util__goal_list_may_alloc_temp_frame(Goals, May).
-code_util__goal_may_alloc_temp_frame_2(switch(_Var, _Det, Cases), May) :-
-	code_util__cases_may_alloc_temp_frame(Cases, May).
-code_util__goal_may_alloc_temp_frame_2(if_then_else(_Vars, C, T, E), May) :-
-	( code_util__goal_may_alloc_temp_frame(C, yes) ->
+goal_may_alloc_temp_frame_2(not(Goal), May) :-
+    goal_may_alloc_temp_frame(Goal, May).
+goal_may_alloc_temp_frame_2(conj(Goals), May) :-
+    goal_list_may_alloc_temp_frame(Goals, May).
+goal_may_alloc_temp_frame_2(par_conj(Goals), May) :-
+    goal_list_may_alloc_temp_frame(Goals, May).
+goal_may_alloc_temp_frame_2(disj(Goals), May) :-
+    goal_list_may_alloc_temp_frame(Goals, May).
+goal_may_alloc_temp_frame_2(switch(_Var, _Det, Cases), May) :-
+    cases_may_alloc_temp_frame(Cases, May).
+goal_may_alloc_temp_frame_2(if_then_else(_Vars, C, T, E), May) :-
+    ( goal_may_alloc_temp_frame(C, yes) ->
 		May = yes
-	; code_util__goal_may_alloc_temp_frame(T, yes) ->
+    ; goal_may_alloc_temp_frame(T, yes) ->
 		May = yes
 	;
-		code_util__goal_may_alloc_temp_frame(E, May)
+        goal_may_alloc_temp_frame(E, May)
 	).
-code_util__goal_may_alloc_temp_frame_2(shorthand(ShorthandGoal), May) :-
-	code_util__goal_may_alloc_temp_frame_2_shorthand(ShorthandGoal,May).
+goal_may_alloc_temp_frame_2(shorthand(ShorthandGoal), May) :-
+    goal_may_alloc_temp_frame_2_shorthand(ShorthandGoal,May).
 
-:- pred code_util__goal_may_alloc_temp_frame_2_shorthand(
-		shorthand_goal_expr::in, bool::out) is det.
+:- pred goal_may_alloc_temp_frame_2_shorthand(shorthand_goal_expr::in,
+    bool::out) is det.
 
-code_util__goal_may_alloc_temp_frame_2_shorthand(bi_implication(G1, G2),
-		May) :-
-	( code_util__goal_may_alloc_temp_frame(G1, yes) ->
+goal_may_alloc_temp_frame_2_shorthand(bi_implication(G1, G2), May) :-
+    ( goal_may_alloc_temp_frame(G1, yes) ->
 		May = yes
 	;
-		code_util__goal_may_alloc_temp_frame(G2, May)
+        goal_may_alloc_temp_frame(G2, May)
 	).
 
-:- pred code_util__goal_list_may_alloc_temp_frame(list(hlds_goal)::in,
-	bool::out) is det.
+:- pred goal_list_may_alloc_temp_frame(list(hlds_goal)::in, bool::out) is det.
 
-code_util__goal_list_may_alloc_temp_frame([], no).
-code_util__goal_list_may_alloc_temp_frame([Goal | Goals], May) :-
-	( code_util__goal_may_alloc_temp_frame(Goal, yes) ->
+goal_list_may_alloc_temp_frame([], no).
+goal_list_may_alloc_temp_frame([Goal | Goals], May) :-
+    ( goal_may_alloc_temp_frame(Goal, yes) ->
 		May = yes
 	;
-		code_util__goal_list_may_alloc_temp_frame(Goals, May)
+        goal_list_may_alloc_temp_frame(Goals, May)
 	).
 
-:- pred code_util__cases_may_alloc_temp_frame(list(case)::in, bool::out)
-	is det.
+:- pred cases_may_alloc_temp_frame(list(case)::in, bool::out) is det.
 
-code_util__cases_may_alloc_temp_frame([], no).
-code_util__cases_may_alloc_temp_frame([case(_, Goal) | Cases], May) :-
-	( code_util__goal_may_alloc_temp_frame(Goal, yes) ->
+cases_may_alloc_temp_frame([], no).
+cases_may_alloc_temp_frame([case(_, Goal) | Cases], May) :-
+    ( goal_may_alloc_temp_frame(Goal, yes) ->
 		May = yes
 	;
-		code_util__cases_may_alloc_temp_frame(Cases, May)
+        cases_may_alloc_temp_frame(Cases, May)
 	).
 
 %-----------------------------------------------------------------------------%
 
-	% Negate a condition.
-	% This is used mostly just to make the generated code more readable.
-
-code_util__neg_rval(Rval, NegRval) :-
-	( code_util__neg_rval_2(Rval, NegRval0) ->
+neg_rval(Rval, NegRval) :-
+    ( neg_rval_2(Rval, NegRval0) ->
 		NegRval = NegRval0
 	;
 		NegRval = unop(not, Rval)
 	).
 
-:- pred code_util__neg_rval_2(rval::in, rval::out) is semidet.
+:- pred neg_rval_2(rval::in, rval::out) is semidet.
 
-code_util__neg_rval_2(const(Const), const(NegConst)) :-
+neg_rval_2(const(Const), const(NegConst)) :-
 	(
-		Const = true, NegConst = false
+        Const = true,
+        NegConst = false
 	;
-		Const = false, NegConst = true
+        Const = false,
+        NegConst = true
 	).
-code_util__neg_rval_2(unop(not, Rval), Rval).
-code_util__neg_rval_2(binop(Op, X, Y), binop(NegOp, X, Y)) :-
-	code_util__neg_op(Op, NegOp).
-
-:- pred code_util__neg_op(binary_op::in, binary_op::out) is semidet.
-
-code_util__neg_op(eq, ne).
-code_util__neg_op(ne, eq).
-code_util__neg_op(<, >=).
-code_util__neg_op(<=, >).
-code_util__neg_op(>, <=).
-code_util__neg_op(>=, <).
-code_util__neg_op(str_eq, str_ne).
-code_util__neg_op(str_ne, str_eq).
-code_util__neg_op(str_lt, str_ge).
-code_util__neg_op(str_le, str_gt).
-code_util__neg_op(str_gt, str_le).
-code_util__neg_op(str_ge, str_lt).
-code_util__neg_op(float_eq, float_ne).
-code_util__neg_op(float_ne, float_eq).
-code_util__neg_op(float_lt, float_ge).
-code_util__neg_op(float_le, float_gt).
-code_util__neg_op(float_gt, float_le).
-code_util__neg_op(float_ge, float_lt).
-
-code_util__negate_the_test([], _) :-
-	error("code_util__negate_the_test on empty list").
-code_util__negate_the_test([Instr0 | Instrs0], Instrs) :-
+neg_rval_2(unop(not, Rval), Rval).
+neg_rval_2(binop(Op, X, Y), binop(NegOp, X, Y)) :-
+    neg_op(Op, NegOp).
+
+:- pred neg_op(binary_op::in, binary_op::out) is semidet.
+
+neg_op(eq, ne).
+neg_op(ne, eq).
+neg_op(<, >=).
+neg_op(<=, >).
+neg_op(>, <=).
+neg_op(>=, <).
+neg_op(str_eq, str_ne).
+neg_op(str_ne, str_eq).
+neg_op(str_lt, str_ge).
+neg_op(str_le, str_gt).
+neg_op(str_gt, str_le).
+neg_op(str_ge, str_lt).
+neg_op(float_eq, float_ne).
+neg_op(float_ne, float_eq).
+neg_op(float_lt, float_ge).
+neg_op(float_le, float_gt).
+neg_op(float_gt, float_le).
+neg_op(float_ge, float_lt).
+
+negate_the_test([], _) :-
+    unexpected(this_file, "negate_the_test on empty list").
+negate_the_test([Instr0 | Instrs0], Instrs) :-
 	( Instr0 = if_val(Test, Target) - Comment ->
-		code_util__neg_rval(Test, NewTest),
+        neg_rval(Test, NewTest),
 		Instrs = [if_val(NewTest, Target) - Comment]
 	;
-		code_util__negate_the_test(Instrs0, Instrs1),
+        negate_the_test(Instrs0, Instrs1),
 		Instrs = [Instr0 | Instrs1]
 	).
 
 %-----------------------------------------------------------------------------%
 
-code_util__lvals_in_lvals([], []).
-code_util__lvals_in_lvals([First | Rest], Lvals) :-
-	code_util__lvals_in_lval(First, FirstLvals),
-	code_util__lvals_in_lvals(Rest, RestLvals),
+lvals_in_lvals([], []).
+lvals_in_lvals([First | Rest], Lvals) :-
+    lvals_in_lval(First, FirstLvals),
+    lvals_in_lvals(Rest, RestLvals),
 	list__append(FirstLvals, RestLvals, Lvals).
 
-code_util__lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
-	code_util__lvals_in_lval(Lval, Lvals).
-code_util__lvals_in_rval(var(_), []).
-code_util__lvals_in_rval(mkword(_, Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_rval(const(_), []).
-code_util__lvals_in_rval(unop(_, Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_rval(binop(_, Rval1, Rval2), Lvals) :-
-	code_util__lvals_in_rval(Rval1, Lvals1),
-	code_util__lvals_in_rval(Rval2, Lvals2),
+lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
+    lvals_in_lval(Lval, Lvals).
+lvals_in_rval(var(_), []).
+lvals_in_rval(mkword(_, Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_rval(const(_), []).
+lvals_in_rval(unop(_, Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_rval(binop(_, Rval1, Rval2), Lvals) :-
+    lvals_in_rval(Rval1, Lvals1),
+    lvals_in_rval(Rval2, Lvals2),
 	list__append(Lvals1, Lvals2, Lvals).
-code_util__lvals_in_rval(mem_addr(MemRef), Lvals) :-
-	code_util__lvals_in_mem_ref(MemRef, Lvals).
+lvals_in_rval(mem_addr(MemRef), Lvals) :-
+    lvals_in_mem_ref(MemRef, Lvals).
 
-code_util__lvals_in_lval(reg(_, _), []).
-code_util__lvals_in_lval(stackvar(_), []).
-code_util__lvals_in_lval(framevar(_), []).
-code_util__lvals_in_lval(succip, []).
-code_util__lvals_in_lval(maxfr, []).
-code_util__lvals_in_lval(curfr, []).
-code_util__lvals_in_lval(succip(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_lval(redofr(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_lval(redoip(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_lval(succfr(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_lval(prevfr(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-code_util__lvals_in_lval(hp, []).
-code_util__lvals_in_lval(sp, []).
-code_util__lvals_in_lval(field(_, Rval1, Rval2), Lvals) :-
-	code_util__lvals_in_rval(Rval1, Lvals1),
-	code_util__lvals_in_rval(Rval2, Lvals2),
+lvals_in_lval(reg(_, _), []).
+lvals_in_lval(stackvar(_), []).
+lvals_in_lval(framevar(_), []).
+lvals_in_lval(succip, []).
+lvals_in_lval(maxfr, []).
+lvals_in_lval(curfr, []).
+lvals_in_lval(succip(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_lval(redofr(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_lval(redoip(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_lval(succfr(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_lval(prevfr(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+lvals_in_lval(hp, []).
+lvals_in_lval(sp, []).
+lvals_in_lval(field(_, Rval1, Rval2), Lvals) :-
+    lvals_in_rval(Rval1, Lvals1),
+    lvals_in_rval(Rval2, Lvals2),
 	list__append(Lvals1, Lvals2, Lvals).
-code_util__lvals_in_lval(lvar(_), []).
-code_util__lvals_in_lval(temp(_, _), []).
-code_util__lvals_in_lval(mem_ref(Rval), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
-
-:- pred code_util__lvals_in_mem_ref(mem_ref::in, list(lval)::out) is det.
-
-code_util__lvals_in_mem_ref(stackvar_ref(_), []).
-code_util__lvals_in_mem_ref(framevar_ref(_), []).
-code_util__lvals_in_mem_ref(heap_ref(Rval, _, _), Lvals) :-
-	code_util__lvals_in_rval(Rval, Lvals).
+lvals_in_lval(lvar(_), []).
+lvals_in_lval(temp(_, _), []).
+lvals_in_lval(mem_ref(Rval), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
+
+:- pred lvals_in_mem_ref(mem_ref::in, list(lval)::out) is det.
+
+lvals_in_mem_ref(stackvar_ref(_), []).
+lvals_in_mem_ref(framevar_ref(_), []).
+lvals_in_mem_ref(heap_ref(Rval, _, _), Lvals) :-
+    lvals_in_rval(Rval, Lvals).
 
 %-----------------------------------------------------------------------------%
 
@@ -445,11 +434,17 @@
 build_input_arg_list_2([V - Arg | Rest0], VarArgs) :-
 	Arg = arg_info(Loc, Mode),
 	( Mode = top_in ->
-		code_util__arg_loc_to_register(Loc, Reg),
+        arg_loc_to_register(Loc, Reg),
 		VarArgs = [V - Reg | VarArgs0]
 	;
 		VarArgs = VarArgs0
 	),
 	build_input_arg_list_2(Rest0, VarArgs0).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "code_util.m".
 
 %-----------------------------------------------------------------------------%
Index: compiler/commit_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/commit_gen.m,v
retrieving revision 1.6
diff -u -b -r1.6 commit_gen.m
--- compiler/commit_gen.m	24 Mar 2005 02:00:18 -0000	1.6
+++ compiler/commit_gen.m	12 Oct 2005 06:55:23 -0000
@@ -1,4 +1,6 @@
 %---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%---------------------------------------------------------------------------%
 % Copyright (C) 1997-1998, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -28,6 +30,7 @@
 
 :- import_module libs__tree.
 :- import_module ll_backend__code_gen.
+:- import_module parse_tree__error_util.
 
 :- import_module require.
 :- import_module std_util.
@@ -39,43 +42,41 @@
 		OuterCodeModel = model_det,
 		(
 			InnerCodeModel = model_det,
-			code_gen__generate_goal(InnerCodeModel, Goal, Code,
-				!Info)
+            code_gen__generate_goal(InnerCodeModel, Goal, Code, !Info)
 		;
 			InnerCodeModel = model_semi,
-			error("semidet model in det context")
+            unexpected(this_file, "semidet model in det context")
 		;
 			InnerCodeModel = model_non,
-			code_info__prepare_for_det_commit(CommitInfo,
-				PreCommit, !Info),
-			code_gen__generate_goal(InnerCodeModel, Goal, GoalCode,
-				!Info),
-			code_info__generate_det_commit(CommitInfo, Commit,
-				!Info),
+            code_info__prepare_for_det_commit(CommitInfo, PreCommit, !Info),
+            code_gen__generate_goal(InnerCodeModel, Goal, GoalCode, !Info),
+            code_info__generate_det_commit(CommitInfo, Commit, !Info),
 			Code = tree(PreCommit, tree(GoalCode, Commit))
 		)
 	;
 		OuterCodeModel = model_semi,
 		(
 			InnerCodeModel = model_det,
-			code_gen__generate_goal(InnerCodeModel, Goal, Code,
-				!Info)
+            code_gen__generate_goal(InnerCodeModel, Goal, Code, !Info)
 		;
 			InnerCodeModel = model_semi,
-			code_gen__generate_goal(InnerCodeModel, Goal, Code,
-				!Info)
+            code_gen__generate_goal(InnerCodeModel, Goal, Code, !Info)
 		;
 			InnerCodeModel = model_non,
-			code_info__prepare_for_semi_commit(CommitInfo,
-				PreCommit,
-					!Info),
-			code_gen__generate_goal(InnerCodeModel, Goal, GoalCode,
-				!Info),
-			code_info__generate_semi_commit(CommitInfo, Commit,
-				!Info),
+            code_info__prepare_for_semi_commit(CommitInfo, PreCommit, !Info),
+            code_gen__generate_goal(InnerCodeModel, Goal, GoalCode, !Info),
+            code_info__generate_semi_commit(CommitInfo, Commit, !Info),
 			Code = tree(PreCommit, tree(GoalCode, Commit))
 		)
 	;
 		OuterCodeModel = model_non,
 		code_gen__generate_goal(InnerCodeModel, Goal, Code, !Info)
 	).
+
+%---------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "commit_gen.m".
+
+%---------------------------------------------------------------------------%
Index: compiler/compile_target_code.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/compile_target_code.m,v
retrieving revision 1.70
diff -u -b -r1.70 compile_target_code.m
--- compiler/compile_target_code.m	13 Sep 2005 08:25:28 -0000	1.70
+++ compiler/compile_target_code.m	12 Oct 2005 06:27:53 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -24,56 +26,64 @@
 :- import_module list.
 :- import_module std_util.
 
-	% Are we generating position independent code (for use in a
-	% shared library)? On some architectures, pic and non-pic
-	% code is incompatible, so we need to generate `.o' and `.pic_o'
-	% files.
+    % Are we generating position independent code (for use in a shared
+    % library)? On some architectures, pic and non-pic code are incompatible,
+    % so we need to generate `.o' and `.pic_o' files.
 :- type pic
 	--->	pic
 	;	link_with_pic
 	;	non_pic.
 
-	% compile_c_file(ErrorStream, PIC, CFile, ObjFile, Succeeded).
+    % compile_c_file(ErrorStream, PIC, CFile, ObjFile, Succeeded)
+    %
 :- pred compile_c_file(io__output_stream::in, pic::in, string::in, string::in,
 	bool::out, io::di, io::uo) is det.
 
-	% compile_c_file(ErrorStream, PIC, ModuleName, Succeeded).
+    % compile_c_file(ErrorStream, PIC, ModuleName, Succeeded)
+    %
 :- pred compile_c_file(io__output_stream::in, pic::in, module_name::in,
 	bool::out, io::di, io::uo) is det.
 
-	% assemble(ErrorStream, PIC, ModuleName, Succeeded).
+    % assemble(ErrorStream, PIC, ModuleName, Succeeded)
+    %
 :- pred assemble(io__output_stream::in, pic::in, module_name::in,
 	bool::out, io::di, io::uo) is det.
 
-	% compile_java_file(ErrorStream, JavaFile, Succeeded).
+    % compile_java_file(ErrorStream, JavaFile, Succeeded)
+    %
 :- pred compile_java_file(io__output_stream::in, string::in, bool::out,
 	io::di, io::uo) is det.
 
-	% il_assemble(ErrorStream, ModuleName, HasMain, Succeeded).
+    % il_assemble(ErrorStream, ModuleName, HasMain, Succeeded)
+    %
 :- pred il_assemble(io__output_stream::in, module_name::in, has_main::in,
 	bool::out, io::di, io::uo) is det.
 
-	% il_assemble(ErrorStream, ILFile, DLLFile, HasMain, Succeeded).
+    % il_assemble(ErrorStream, ILFile, DLLFile, HasMain, Succeeded)
+    %
 :- pred il_assemble(io__output_stream::in, file_name::in, file_name::in,
 	has_main::in, bool::out, io::di, io::uo) is det.
 
-	% compile_managed_cplusplus_file(ErrorStream,
-	%		MCPPFile, DLLFile, Succeeded).
+    % compile_managed_cplusplus_file(ErrorStream, MCPPFile, DLLFile, Succeeded)
+    %
 :- pred compile_managed_cplusplus_file(io__output_stream::in,
 	file_name::in, file_name::in, bool::out, io::di, io::uo) is det.
 
-	% compile_csharp_file(ErrorStream, C#File, DLLFile, Succeeded).
+    % compile_csharp_file(ErrorStream, C#File, DLLFile, Succeeded)
+    %
 :- pred compile_csharp_file(io__output_stream::in, module_imports::in,
 	file_name::in, file_name::in, bool::out, io::di, io::uo) is det.
 
-	% make_init_file(ErrorStream, MainModuleName, ModuleNames, Succeeded).
+    % make_init_file(ErrorStream, MainModuleName, ModuleNames, Succeeded):
 	%
 	% Make the `.init' file for a library containing the given modules.
+    %
 :- pred make_init_file(io__output_stream::in, module_name::in,
 	list(module_name)::in, bool::out, io::di, io::uo) is det.
 
-	% make_init_obj_file(ErrorStream, MainModuleName,
-	%		AllModuleNames, MaybeInitObjFileName).
+    % make_init_obj_file(ErrorStream, MainModuleName, AllModuleNames,
+    %   MaybeInitObjFileName)
+    %
 :- pred make_init_obj_file(io__output_stream::in, module_name::in,
 	list(module_name)::in, maybe(file_name)::out, io::di, io::uo) is det.
 
@@ -83,75 +93,86 @@
 	;	shared_library
 	;	java_archive.
 
-	% link(TargetType, MainModuleName, ObjectFileNames, Succeeded).
+    % link(TargetType, MainModuleName, ObjectFileNames, Succeeded)
+    %
 :- pred link(io__output_stream::in, linked_target_type::in, module_name::in,
 	list(string)::in, bool::out, io::di, io::uo) is det.
 
-	% link_module_list(ModulesToLink, FactTableObjFiles, Succeeded).
+    % link_module_list(ModulesToLink, FactTableObjFiles, Succeeded):
 	%
 	% The elements of ModulesToLink are the output of
 	% `module_name_to_filename(ModuleName, "", no, ModuleToLink)'
 	% for each module in the program.
+    %
 :- pred link_module_list(list(string)::in, list(string)::in, bool::out,
 	io::di, io::uo) is det.
 
-	% get_object_code_type(TargetType, PIC)
+    % get_object_code_type(TargetType, PIC):
 	%
 	% Work out whether we should be generating position-independent
 	% object code.
+    %
 :- pred get_object_code_type(linked_target_type::in, pic::out, io::di, io::uo)
 	is det.
 
 %-----------------------------------------------------------------------------%
-	% Code to deal with `--split-c-files'.
+%
+% Code to deal with `--split-c-files'.
 
-	% split_c_to_obj(ErrorStream, ModuleName, NumChunks, Succeeded).
+    % split_c_to_obj(ErrorStream, ModuleName, NumChunks, Succeeded):
+    %
 	% Compile the `.c' files produced for a module with `--split-c-files'.
+    %
 :- pred split_c_to_obj(io__output_stream::in, module_name::in,
 	int::in, bool::out, io::di, io::uo) is det.
 
-	% Write the number of `.c' files written by this
-	% compilation with `--split-c-files'.
+    % Write the number of `.c' files written by this compilation
+    % with `--split-c-files'.
+    %
 :- pred write_num_split_c_files(module_name::in, int::in, bool::out,
 	io::di, io::uo) is det.
 
-	% Find the number of `.c' files written by a previous
-	% compilation with `--split-c-files'.
+    % Find the number of `.c' files written by a previous compilation
+    % with `--split-c-files'.
+    %
 :- pred read_num_split_c_files(module_name::in, maybe_error(int)::out,
 	io::di, io::uo) is det.
 
-	% remove_split_c_output_files(ModuleName, NumChunks).
+    % remove_split_c_output_files(ModuleName, NumChunks):
+    %
+    % Remove the `.c' and `.o' files written by a previous compilation
+    % with `--split-c-files'.
 	%
-	% Remove the `.c' and `.o' files written by a previous
-	% compilation with `--split-c-files'.
 :- pred remove_split_c_output_files(module_name::in, int::in,
 	io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 
-	% make_all_module_command(CommandName, MainModule,
-	%		AllModuleNames, CommandString)
+    % make_all_module_command(CommandName, MainModule, AllModuleNames,
+    %   CommandString):
 	%
 	% Create a command string which passes the source file names
 	% for AllModuleNames to CommandName, with MainModule given first.
+    %
 :- pred make_all_module_command(string::in, module_name::in,
 	list(module_name)::in, string::out, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 
 	% maybe_pic_object_file_extension(Globals, PIC, Ext) is true iff
-	% Ext is the extension which should be used on object files according
-	% to the value of PIC.  The value of PIC should be obtained
-	% from a call to `get_object_code_type'.  In particular, on
-	% architectures for which no special handling for PIC is
-	% necessary, only a value of `non_pic' should be used.
-	% The `(in, out, in)' mode guarantees that the returned
+    % Ext is the extension which should be used on object files according to
+    % the value of PIC. The value of PIC should be obtained from a call to
+    % `get_object_code_type'. In particular, on architectures for which
+    % no special handling for PIC is necessary, only a value of `non_pic'
+    % should be used. The `(in, out, in)' mode guarantees that the returned
 	% value of PIC meets this requirement.
+    %
 :- pred maybe_pic_object_file_extension(globals, pic, string).
 :- mode maybe_pic_object_file_extension(in, in, out) is det.
 :- mode maybe_pic_object_file_extension(in, out, in) is semidet.
 
 	% Same as above except the globals are obtained from the io__state.
+    %
 :- pred maybe_pic_object_file_extension(pic::in, string::out, io::di, io::uo)
 	is det.
 
@@ -181,7 +202,6 @@
 	module_name_to_file_name(ModuleName, ".il", no, IL_File, !IO),
 	module_name_to_file_name(ModuleName, ".dll", yes, DllFile, !IO),
 
-	%
 	% If the module contains main/2 then we it should be built as an
 	% executable.  Unfortunately MC++ or C# code may refer to the dll
 	% so we always need to build the dll.
@@ -189,8 +209,7 @@
 	il_assemble(ErrorStream, IL_File, DllFile, no_main, DllSucceeded, !IO),
 	( HasMain = has_main ->
 		module_name_to_file_name(ModuleName, ".exe", yes, ExeFile, !IO),
-		il_assemble(ErrorStream, IL_File, ExeFile, HasMain,
-			ExeSucceeded, !IO),
+        il_assemble(ErrorStream, IL_File, ExeFile, HasMain, ExeSucceeded, !IO),
 		Succeeded = DllSucceeded `and` ExeSucceeded
 	;
 		Succeeded = DllSucceeded
@@ -205,20 +224,26 @@
 	globals__io_lookup_string_option(il_assembler, ILASM, !IO),
 	globals__io_lookup_accumulating_option(ilasm_flags, ILASMFlagsList, !IO),
 	join_string_list(ILASMFlagsList, "", "", " ", ILASMFlags),
-	( SignAssembly = yes ->
+    (
+        SignAssembly = yes,
 		SignOpt = "/keyf=mercury.sn "
 	;
+        SignAssembly = no,
 		SignOpt = ""
 	),
-	( Verbose = yes ->
+    (
+        Verbose = yes,
 		VerboseOpt = ""
 	;
+        Verbose = no,
 		VerboseOpt = "/quiet "
 	),
 	globals__io_lookup_bool_option(target_debug, Debug, !IO),
-	( Debug = yes ->
+    (
+        Debug = yes,
 		DebugOpt = "/debug "
 	;
+        Debug = no,
 		DebugOpt = ""
 	),
 	( HasMain = has_main ->
@@ -227,10 +252,9 @@
 		TargetOpt = "/dll "
 	),
 	string__append_list([ILASM, " ", SignOpt, VerboseOpt, DebugOpt,
-		TargetOpt, ILASMFlags, " /out=", TargetFile,
-		" ", IL_File], Command),
-	invoke_system_command(ErrorStream, verbose_commands, Command,
-		Succeeded, !IO).
+        TargetOpt, ILASMFlags, " /out=", TargetFile, " ", IL_File], Command),
+    invoke_system_command(ErrorStream, verbose_commands, Command, Succeeded,
+        !IO).
 
 compile_managed_cplusplus_file(ErrorStream, MCPPFileName, DLLFileName,
 		Succeeded, !IO) :-
@@ -263,10 +287,8 @@
 		string__append_list(list__condense(list__map(
 			(func(DLLDir) = ["-AI", DLLDir, " "]), DLLDirs))),
 
-	string__append_list([MCPP, " -CLR ", DebugOpt, InclOpts,
-		DLLDirOpts, MCPPFlags, " ", MCPPFileName,
-		" -LD -o ", DLLFileName],
-		Command),
+    string__append_list([MCPP, " -CLR ", DebugOpt, InclOpts, DLLDirOpts,
+        MCPPFlags, " ", MCPPFileName, " -LD -o ", DLLFileName], Command),
 	invoke_system_command(ErrorStream, verbose_commands, Command,
 		Succeeded, !IO).
 
@@ -277,8 +299,7 @@
 	maybe_write_string(Verbose, CSharpFileName, !IO),
 	maybe_write_string(Verbose, "':\n", !IO),
 	globals__io_lookup_string_option(csharp_compiler, CSC, !IO),
-	globals__io_lookup_accumulating_option(csharp_flags, CSCFlagsList,
-		!IO),
+    globals__io_lookup_accumulating_option(csharp_flags, CSCFlagsList, !IO),
 	join_string_list(CSCFlagsList, "", "", " ", CSCFlags),
 
 		% XXX This is because the MS C# compiler doesn't understand
@@ -288,9 +309,9 @@
 	globals__io_lookup_bool_option(target_debug, Debug, !IO),
 	(
 		Debug = yes,
-		% XXX This needs testing before it can be enabled
-		% (see the comments for install_debug_library in
-		% library/Mmakefile).
+        % XXX This needs testing before it can be enabled (see the comments
+        % for install_debug_library in library/Mmakefile).
+
 		% DebugOpt = "/debug+ /debug:full "
 		DebugOpt = ""
 	;
@@ -299,8 +320,8 @@
 	),
 
 	% XXX Should we use a separate dll_directories options?
-	globals__io_lookup_accumulating_option(link_library_directories,
-		DLLDirs, !IO),
+    globals__io_lookup_accumulating_option(link_library_directories, DLLDirs,
+        !IO),
 	DLLDirOpts = "/lib:Mercury/dlls " ++
 		string__append_list(list__condense(list__map(
 			(func(DLLDir) = ["/lib:", DLLDir, " "]), DLLDirs))),
@@ -311,15 +332,13 @@
 		Prefix = "/r:"
 	),
 	ForeignDeps = list__map(
-		(func(M) =
-			foreign_import_module_name(M, Imports ^ module_name)
-		), Imports ^ foreign_import_module_info ),
+        (func(M) = foreign_import_module_name(M, Imports ^ module_name)),
+        Imports ^ foreign_import_module_info ),
 	ReferencedDlls = referenced_dlls(Imports ^ module_name,
 		Imports ^ int_deps ++ Imports ^ impl_deps ++ ForeignDeps),
 	list__map_foldl(
 		(pred(Mod::in, Result::out, IO0::di, IO::uo) is det :-
-			module_name_to_file_name(Mod, ".dll", no, FileName,
-				IO0, IO),
+            module_name_to_file_name(Mod, ".dll", no, FileName, IO0, IO),
 			Result = [Prefix, FileName, " "]
 		), ReferencedDlls, ReferencedDllsList, !IO),
 	ReferencedDllsStr = string__append_list(
@@ -336,7 +355,8 @@
 split_c_to_obj(ErrorStream, ModuleName, NumChunks, Succeeded, !IO) :-
 	split_c_to_obj(ErrorStream, ModuleName, 0, NumChunks, Succeeded, !IO).
 
-	% compile each of the C files in `<module>.dir'
+    % Compile each of the C files in `<module>.dir'.
+    %
 :- pred split_c_to_obj(io__output_stream::in, module_name::in,
 	int::in, int::in, bool::out, io::di, io::uo) is det.
 
@@ -345,27 +365,29 @@
 		Succeeded = yes
 	;
 		% XXX should this use maybe_pic_object_file_extension?
-		globals__io_lookup_string_option(object_file_extension, Obj,
-			!IO),
-		module_name_to_split_c_file_name(ModuleName, Chunk,
-			".c", C_File, !IO),
-		module_name_to_split_c_file_name(ModuleName, Chunk,
-			Obj, O_File, !IO),
-		compile_c_file(ErrorStream, non_pic,
-			C_File, O_File, Succeeded0, !IO),
-		( Succeeded0 = no ->
+        globals__io_lookup_string_option(object_file_extension, Obj, !IO),
+        module_name_to_split_c_file_name(ModuleName, Chunk, ".c", C_File, !IO),
+        module_name_to_split_c_file_name(ModuleName, Chunk, Obj, O_File, !IO),
+        compile_c_file(ErrorStream, non_pic, C_File, O_File, Succeeded0, !IO),
+        (
+            Succeeded0 = no,
 			Succeeded = no
 		;
+            Succeeded0 = yes,
 			Chunk1 = Chunk + 1,
-			split_c_to_obj(ErrorStream, ModuleName,
-				Chunk1, NumChunks, Succeeded, !IO)
+            split_c_to_obj(ErrorStream, ModuleName, Chunk1, NumChunks,
+                Succeeded, !IO)
 		)
 	).
 
 % WARNING: The code here duplicates the functionality of scripts/mgnuc.in.
 % Any changes there may also require changes here, and vice versa.
 
-:- type compiler_type ---> gcc ; lcc ; cl ; unknown.
+:- type compiler_type
+    --->    gcc
+    ;       lcc
+    ;       cl
+    ;       unknown.
 
 compile_c_file(ErrorStream, PIC, ModuleName, Succeeded, !IO) :-
 	module_name_to_file_name(ModuleName, ".c", yes, C_File, !IO),
@@ -386,12 +408,15 @@
 
 	globals__io_lookup_bool_option(use_subdirs, UseSubdirs, !IO),
 	globals__io_lookup_bool_option(split_c_files, SplitCFiles, !IO),
-	( (UseSubdirs = yes ; SplitCFiles = yes) ->
-		% the source file (foo.c) will be compiled in a subdirectory
-		% (either Mercury/cs, foo.dir, or Mercury/dirs/foo.dir,
-		% depending on which of these two options is set)
-		% so we need to add `-I.' so it can
-		% include header files in the source directory.
+    (
+        ( UseSubdirs = yes
+        ; SplitCFiles = yes
+        )
+    ->
+        % The source file (foo.c) will be compiled in a subdirectory
+        % (either Mercury/cs, foo.dir, or Mercury/dirs/foo.dir, depending
+        % on which of these two options is set) so we need to add `-I.'
+        % so it can include header files in the source directory.
 		SubDirInclOpt = "-I. "
 	;
 		SubDirInclOpt = ""
@@ -401,59 +426,75 @@
 	InclOpt = string__append_list(list__condense(list__map(
 		(func(C_INCL) = ["-I", C_INCL, " "]), C_Incl_Dirs))),
 	globals__io_lookup_bool_option(split_c_files, Split_C_Files, !IO),
-	( Split_C_Files = yes ->
+    (
+        Split_C_Files = yes,
 		SplitOpt = "-DMR_SPLIT_C_FILES "
 	;
+        Split_C_Files = no,
 		SplitOpt = ""
 	),
 	globals__io_lookup_bool_option(highlevel_code, HighLevelCode, !IO),
-	( HighLevelCode = yes ->
+    (
+        HighLevelCode = yes,
 		HighLevelCodeOpt = "-DMR_HIGHLEVEL_CODE "
 	;
+        HighLevelCode = no,
 		HighLevelCodeOpt = ""
 	),
 	globals__io_lookup_bool_option(gcc_nested_functions,
 		GCC_NestedFunctions, !IO),
-	( GCC_NestedFunctions = yes ->
+    (
+        GCC_NestedFunctions = yes,
 		NestedFunctionsOpt = "-DMR_USE_GCC_NESTED_FUNCTIONS "
 	;
+        GCC_NestedFunctions = no,
 		NestedFunctionsOpt = ""
 	),
 	globals__io_lookup_bool_option(highlevel_data, HighLevelData, !IO),
-	( HighLevelData = yes ->
+    (
+        HighLevelData = yes,
 		HighLevelDataOpt = "-DMR_HIGHLEVEL_DATA "
 	;
+        HighLevelData = no,
 		HighLevelDataOpt = ""
 	),
 	globals__io_lookup_bool_option(gcc_global_registers, GCC_Regs, !IO),
-	( GCC_Regs = yes ->
-		globals__io_lookup_string_option(cflags_for_regs,
-			CFLAGS_FOR_REGS, !IO),
+    (
+        GCC_Regs = yes,
+        globals__io_lookup_string_option(cflags_for_regs, CFLAGS_FOR_REGS,
+            !IO),
 		RegOpt = "-DMR_USE_GCC_GLOBAL_REGISTERS "
 	;
+        GCC_Regs = no,
 		CFLAGS_FOR_REGS = "",
 		RegOpt = ""
 	),
 	globals__io_lookup_bool_option(gcc_non_local_gotos, GCC_Gotos, !IO),
-	( GCC_Gotos = yes ->
+    (
+        GCC_Gotos = yes,
 		GotoOpt = "-DMR_USE_GCC_NONLOCAL_GOTOS ",
 		globals__io_lookup_string_option(cflags_for_gotos,
 			CFLAGS_FOR_GOTOS, !IO)
 	;
+        GCC_Gotos = no,
 		GotoOpt = "",
 		CFLAGS_FOR_GOTOS = ""
 	),
 	globals__io_lookup_bool_option(asm_labels, ASM_Labels, !IO),
-	( ASM_Labels = yes ->
+    (
+        ASM_Labels = yes,
 		AsmOpt = "-DMR_USE_ASM_LABELS "
 	;
+        ASM_Labels = no,
 		AsmOpt = ""
 	),
 	globals__io_lookup_bool_option(parallel, Parallel, !IO),
-	( Parallel = yes ->
+    (
+        Parallel = yes,
 		globals__io_lookup_string_option(cflags_for_threads,
 			CFLAGS_FOR_THREADS, !IO)
 	;
+        Parallel = no,
 		CFLAGS_FOR_THREADS = ""
 	),
 	globals__io_get_gc_method(GC_Method, !IO),
@@ -474,27 +515,35 @@
 		GC_Opt = "-DMR_NATIVE_GC "
 	),
 	globals__io_lookup_bool_option(profile_calls, ProfileCalls, !IO),
-	( ProfileCalls = yes ->
+    (
+        ProfileCalls = yes,
 		ProfileCallsOpt = "-DMR_MPROF_PROFILE_CALLS "
 	;
+        ProfileCalls = no,
 		ProfileCallsOpt = ""
 	),
 	globals__io_lookup_bool_option(profile_time, ProfileTime, !IO),
-	( ProfileTime = yes ->
+    (
+        ProfileTime = yes,
 		ProfileTimeOpt = "-DMR_MPROF_PROFILE_TIME "
 	;
+        ProfileTime = no,
 		ProfileTimeOpt = ""
 	),
 	globals__io_lookup_bool_option(profile_memory, ProfileMemory, !IO),
-	( ProfileMemory = yes ->
+    (
+        ProfileMemory = yes,
 		ProfileMemoryOpt = "-DMR_MPROF_PROFILE_MEMORY "
 	;
+        ProfileMemory = no,
 		ProfileMemoryOpt = ""
 	),
 	globals__io_lookup_bool_option(profile_deep, ProfileDeep, !IO),
-	( ProfileDeep = yes ->
+    (
+        ProfileDeep = yes,
 		ProfileDeepOpt = "-DMR_DEEP_PROFILING "
 	;
+        ProfileDeep = no,
 		ProfileDeepOpt = ""
 	),
 	globals__io_lookup_bool_option(record_term_sizes_as_words,
@@ -522,8 +571,7 @@
 	),
 	(
 		PIC = pic,
-		globals__io_lookup_string_option(cflags_for_pic,
-			CFLAGS_FOR_PIC, !IO),
+        globals__io_lookup_string_option(cflags_for_pic, CFLAGS_FOR_PIC, !IO),
 		PIC_Reg = yes
 	;
 		PIC = link_with_pic,
@@ -534,12 +582,13 @@
 		CFLAGS_FOR_PIC = "",
 		globals__io_lookup_bool_option(pic_reg, PIC_Reg, !IO)
 	),
-	( PIC_Reg = yes ->
-		% This will be ignored for architectures/grades
-		% where use of position independent code does not
-		% reserve a register.
+    (
+        PIC_Reg = yes,
+        % This will be ignored for architectures/grades where use of position
+        % independent code does not reserve a register.
 		PIC_Reg_Opt = "-DMR_PIC_REG "
 	;
+        PIC_Reg = no,
 		PIC_Reg_Opt = ""
 	),
 
@@ -551,18 +600,22 @@
 	),
 	globals__io_lookup_int_option(num_tag_bits, NumTagBits, !IO),
 	string__int_to_string(NumTagBits, NumTagBitsString),
-	string__append_list(
-		["-DMR_TAGBITS=", NumTagBitsString, " "], NumTagBitsOpt),
+    string__append_list(["-DMR_TAGBITS=", NumTagBitsString, " "],
+        NumTagBitsOpt),
 	globals__io_lookup_bool_option(decl_debug, DeclDebug, !IO),
-	( DeclDebug = yes ->
+    (
+        DeclDebug = yes,
 		DeclDebugOpt = "-DMR_DECL_DEBUG "
 	;
+        DeclDebug = no,
 		DeclDebugOpt = ""
 	),
 	globals__io_lookup_bool_option(exec_trace, ExecTrace, !IO),
-	( ExecTrace = yes ->
+    (
+        ExecTrace = yes,
 		ExecTraceOpt = "-DMR_EXEC_TRACE "
 	;
+        ExecTrace = no,
 		ExecTraceOpt = ""
 	),
 	globals__io_lookup_bool_option(extend_stacks_when_needed, Extend, !IO),
@@ -574,29 +627,37 @@
 		ExtendOpt = ""
 	),
 	globals__io_lookup_bool_option(target_debug, Target_Debug, !IO),
-	( Target_Debug = yes ->
-		globals__io_lookup_string_option(cflags_for_debug,
-			Target_DebugOpt0, !IO),
+    (
+        Target_Debug = yes,
+        globals__io_lookup_string_option(cflags_for_debug, Target_DebugOpt0,
+            !IO),
 		string__append(Target_DebugOpt0, " ", Target_DebugOpt)
 	;
+        Target_Debug = no,
 		Target_DebugOpt = ""
 	),
 	globals__io_lookup_bool_option(low_level_debug, LL_Debug, !IO),
-	( LL_Debug = yes ->
+    (
+        LL_Debug = yes,
 		LL_DebugOpt = "-DMR_LOW_LEVEL_DEBUG "
 	;
+        LL_Debug = no,
 		LL_DebugOpt = ""
 	),
 	globals__io_lookup_bool_option(use_trail, UseTrail, !IO),
-	( UseTrail = yes ->
+    (
+        UseTrail = yes,
 		UseTrailOpt = "-DMR_USE_TRAIL "
 	;
+        UseTrail = no,
 		UseTrailOpt = ""
 	),
 	globals__io_lookup_bool_option(reserve_tag, ReserveTag, !IO),
-	( ReserveTag = yes ->
+    (
+        ReserveTag = yes,
 		ReserveTagOpt = "-DMR_RESERVE_TAG "
 	;
+        ReserveTag = no,
 		ReserveTagOpt = ""
 	),
 	globals__io_lookup_bool_option(use_minimal_model_stack_copy,
@@ -626,55 +687,63 @@
 	(
 		MinimalModelDebug = yes,
 		( MinimalModelBaseOpt = "" ->
-			% We ignore the debug flag unless one of the base flags
-			% is set.
+            % We ignore the debug flag unless one of the base flags is set.
 			MinimalModelOpt = MinimalModelBaseOpt
 		;
-			MinimalModelOpt = MinimalModelBaseOpt ++
-				"-DMR_MINIMAL_MODEL_DEBUG"
+            MinimalModelOpt = MinimalModelBaseOpt ++ "-DMR_MINIMAL_MODEL_DEBUG"
 		)
 	;
 		MinimalModelDebug = no,
 		MinimalModelOpt = MinimalModelBaseOpt
 	),
 	globals__io_lookup_bool_option(type_layout, TypeLayoutOption, !IO),
-	( TypeLayoutOption = no ->
+    (
+        TypeLayoutOption = no,
 		TypeLayoutOpt = "-DMR_NO_TYPE_LAYOUT "
 	;
+        TypeLayoutOption = yes,
 		TypeLayoutOpt = ""
 	),
 	globals__io_lookup_bool_option(c_optimize, C_optimize, !IO),
-	( C_optimize = yes ->
-		globals__io_lookup_string_option(cflags_for_optimization,
-			OptimizeOpt, !IO)
+    (
+        C_optimize = yes,
+        globals__io_lookup_string_option(cflags_for_optimization, OptimizeOpt,
+            !IO)
 	;
+        C_optimize = no,
 		OptimizeOpt = ""
 	),
 	globals__io_lookup_bool_option(ansi_c, Ansi, !IO),
-	( Ansi = yes ->
+    (
+        Ansi = yes,
 		globals__io_lookup_string_option(cflags_for_ansi, AnsiOpt, !IO)
 	;
+        Ansi = no,
 		AnsiOpt = ""
 	),
 	globals__io_lookup_bool_option(inline_alloc, InlineAlloc, !IO),
-	( InlineAlloc = yes ->
+    (
+        InlineAlloc = yes,
 		InlineAllocOpt = "-DMR_INLINE_ALLOC -DSILENT "
 	;
+        InlineAlloc = no,
 		InlineAllocOpt = ""
 	),
 	globals__io_lookup_bool_option(warn_target_code, Warn, !IO),
-	( Warn = yes ->
+    (
+        Warn = yes,
 		globals__io_lookup_string_option(cflags_for_warnings,
 			WarningOpt, !IO)
 	;
+        Warn = no,
 		WarningOpt = ""
 	),
-	%
+
 	% The -floop-optimize option is incompatible with the global
 	% register code we generate on Darwin PowerPC.
 	% See the hard_coded/ppc_bug test case for an example
 	% program which fails with this optimization.
-	%
+
 	globals__io_lookup_string_option(fullarch, FullArch, !IO),
 	(
 		HighLevelCode = no,
@@ -734,8 +803,8 @@
 	globals__io_lookup_accumulating_option(java_flags, JavaFlagsList, !IO),
 	join_string_list(JavaFlagsList, "", "", " ", JAVAFLAGS),
 
-	globals__io_lookup_accumulating_option(java_classpath,
-		Java_Incl_Dirs, !IO),
+    globals__io_lookup_accumulating_option(java_classpath, Java_Incl_Dirs,
+        !IO),
 	% XXX PathSeparator should be ";" on Windows
 	PathSeparator = ":",
 	% We prepend the current CLASSPATH to preserve the accumulating
@@ -751,9 +820,11 @@
 	),
 
 	globals__io_lookup_bool_option(target_debug, Target_Debug, !IO),
-	( Target_Debug = yes ->
+    (
+        Target_Debug = yes,
 		Target_DebugOpt = "-g "
 	;
+        Target_Debug = no,
 		Target_DebugOpt = ""
 	),
 
@@ -761,19 +832,23 @@
 	globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs, !IO),
 	globals__io_lookup_string_option(fullarch, FullArch, !IO),
 	globals__io_get_globals(Globals, !IO),
-	( UseSubdirs = yes ->
-		( UseGradeSubdirs = yes ->
+    (
+        UseSubdirs = yes,
+        (
+            UseGradeSubdirs = yes,
 			grade_directory_component(Globals, Grade),
 			DirName = "Mercury"/Grade/FullArch/"Mercury"/"classs"
 		;
+            UseGradeSubdirs = no,
 			DirName = "Mercury"/"classs"
 		),
-		% javac won't create the destination directory for
-		% class files, so we need to do it.
+        % Javac won't create the destination directory for class files,
+        % so we need to do it.
 		dir__make_directory(DirName, _, !IO),
 		% Set destination directory for class files.
 		DestDir = "-d " ++ DirName ++ " "
 	;
+        UseSubdirs = no,
 		DestDir = ""
 	),
 
@@ -781,8 +856,8 @@
 	% Also be careful that each option is separated by spaces.
 	string__append_list([JavaCompiler, " ", InclOpt, DestDir,
 		Target_DebugOpt, JAVAFLAGS, " ", JavaFile], Command),
-	invoke_system_command(ErrorStream, verbose_commands, Command,
-		Succeeded, !IO).
+    invoke_system_command(ErrorStream, verbose_commands, Command, Succeeded,
+        !IO).
 
 %-----------------------------------------------------------------------------%
 
@@ -821,29 +896,28 @@
 	% Be careful with the order here.
 	% Also be careful that each option is separated by spaces.
 	string__append_list([CC, " ", CFLAGS, " ", GCCFLAGS_FOR_PIC,
-		GCCFLAGS_FOR_ASM, "-c ", AsmFile, " ",
-		NameObjectFile, ObjFile], Command),
-	invoke_system_command(ErrorStream, verbose_commands, Command,
-		Succeeded, !IO).
+        GCCFLAGS_FOR_ASM, "-c ", AsmFile, " ", NameObjectFile, ObjFile],
+        Command),
+    invoke_system_command(ErrorStream, verbose_commands, Command, Succeeded,
+        !IO).
 
 %-----------------------------------------------------------------------------%
 
 make_init_file(ErrorStream, MainModuleName, AllModules, Succeeded, !IO) :-
-	module_name_to_file_name(MainModuleName, ".init.tmp",
-		yes, TmpInitFileName, !IO),
+    module_name_to_file_name(MainModuleName, ".init.tmp", yes, TmpInitFileName,
+        !IO),
 	io__open_output(TmpInitFileName, InitFileRes, !IO),
 	(
 		InitFileRes = ok(InitFileStream),
 		globals__io_lookup_bool_option(aditi, Aditi, !IO),
-		list__foldl(make_init_file_aditi(InitFileStream, Aditi),
-			AllModules, !IO),
+        list__foldl(make_init_file_aditi(InitFileStream, Aditi), AllModules,
+            !IO),
 		globals__io_lookup_maybe_string_option(extra_init_command,
 			MaybeInitFileCommand, !IO),
 		(
 			MaybeInitFileCommand = yes(InitFileCommand),
-			make_all_module_command(InitFileCommand,
-				MainModuleName, AllModules, CommandString,
-				!IO),
+            make_all_module_command(InitFileCommand, MainModuleName,
+                AllModules, CommandString, !IO),
 			invoke_system_command(InitFileStream, verbose_commands,
 				CommandString, Succeeded0, !IO)
 		;
@@ -852,8 +926,8 @@
 		),
 
 		io__close_output(InitFileStream, !IO),
-		module_name_to_file_name(MainModuleName, ".init",
-			yes, InitFileName, !IO),
+        module_name_to_file_name(MainModuleName, ".init", yes, InitFileName,
+            !IO),
 		update_interface(InitFileName, Succeeded1, !IO),
 		Succeeded = Succeeded0 `and` Succeeded1
 	;
@@ -878,24 +952,26 @@
 	io__write_string(InitFileStream, "INIT ", !IO),
 	io__write_string(InitFileStream, InitFuncName, !IO),
 	io__nl(InitFileStream, !IO),
-	( Aditi = yes ->
+    (
+        Aditi = yes,
 		RLName = make_rl_data_name(ModuleName),
 		io__write_string(InitFileStream, "ADITI_DATA ", !IO),
 		io__write_string(InitFileStream, RLName, !IO),
 		io__nl(InitFileStream, !IO)
 	;
-		true
+        Aditi = no
 	).
 
 %-----------------------------------------------------------------------------%
 
 link_module_list(Modules, FactTableObjFiles, Succeeded, !IO) :-
-	globals__io_lookup_string_option(output_file_name, OutputFileName0,
-		!IO),
+    globals__io_lookup_string_option(output_file_name, OutputFileName0, !IO),
 	( OutputFileName0 = "" ->
-		( Modules = [Module | _] ->
+        (
+            Modules = [Module | _],
 			OutputFileName = Module
 		;
+            Modules = [],
 			error("link_module_list: no modules")
 		)
 	;
@@ -904,10 +980,9 @@
 
 	file_name_to_module_name(OutputFileName, MainModuleName),
 
-	globals__io_lookup_bool_option(compile_to_shared_lib,
-		CompileToSharedLib, !IO),
-	TargetType =
-		(CompileToSharedLib = yes -> shared_library ; executable),
+    globals__io_lookup_bool_option(compile_to_shared_lib, CompileToSharedLib,
+        !IO),
+    TargetType = (CompileToSharedLib = yes -> shared_library ; executable),
 	get_object_code_type(TargetType, PIC, !IO),
 	maybe_pic_object_file_extension(PIC, Obj, !IO),
 
@@ -915,42 +990,42 @@
 	globals__io_lookup_bool_option(split_c_files, SplitFiles, !IO),
 	io__output_stream(OutputStream, !IO),
 	( Target = asm ->
-		% for --target asm, we generate everything into
-		% a single object file
-		( Modules = [FirstModule | _] ->
+        % For --target asm, we generate everything into a single object file.
+        (
+            Modules = [FirstModule | _],
 			join_module_list([FirstModule], Obj, ObjectsList, !IO)
 		;
+            Modules = [],
 			error("link_module_list: no modules")
 		),
 		MakeLibCmdOK = yes
 	; SplitFiles = yes ->
-		globals__io_lookup_string_option(library_extension, LibExt,
+        globals__io_lookup_string_option(library_extension, LibExt, !IO),
+        module_name_to_file_name(MainModuleName, LibExt, yes, SplitLibFileName,
 			!IO),
-		module_name_to_file_name(MainModuleName, LibExt, yes,
-			SplitLibFileName, !IO),
 		string__append(".dir/*", Obj, DirObj),
 		join_module_list(Modules, DirObj, ObjectList, !IO),
-		create_archive(OutputStream, SplitLibFileName, no,
-			ObjectList, MakeLibCmdOK, !IO),
+        create_archive(OutputStream, SplitLibFileName, no, ObjectList,
+            MakeLibCmdOK, !IO),
 		ObjectsList = [SplitLibFileName]
 	;
 		MakeLibCmdOK = yes,
 		join_module_list(Modules, Obj, ObjectsList, !IO)
 	),
-	( MakeLibCmdOK = no ->
+    (
+        MakeLibCmdOK = no,
 		Succeeded = no
 	;
+        MakeLibCmdOK = yes,
 		( TargetType = executable ->
 			list__map(
 				(pred(ModuleStr::in, ModuleName::out) is det :-
-					file_name_to_module_name(
-						dir__basename_det(ModuleStr),
+                    file_name_to_module_name(dir__basename_det(ModuleStr),
 						ModuleName)
 				), Modules, ModuleNames),
 			MustCompile = yes,
-			make_init_obj_file(OutputStream, MustCompile,
-				MainModuleName, ModuleNames, InitObjResult,
-				!IO)
+            make_init_obj_file(OutputStream, MustCompile, MainModuleName,
+                ModuleNames, InitObjResult, !IO)
 		;
 			InitObjResult = yes("")
 		),
@@ -966,8 +1041,8 @@
 				;
 					[InitObjFileName | AllObjects0]
 				),
-			link(OutputStream, TargetType, MainModuleName,
-				AllObjects, Succeeded, !IO)
+            link(OutputStream, TargetType, MainModuleName, AllObjects,
+                Succeeded, !IO)
 		;
 			InitObjResult = no,
 			Succeeded = no
@@ -976,8 +1051,8 @@
 
 make_init_obj_file(ErrorStream, ModuleName, ModuleNames, Result, !IO) :-
 	globals__io_lookup_bool_option(rebuild, MustCompile, !IO),
-	make_init_obj_file(ErrorStream,
-		MustCompile, ModuleName, ModuleNames, Result, !IO).
+    make_init_obj_file(ErrorStream, MustCompile, ModuleName, ModuleNames,
+        Result, !IO).
 
 % WARNING: The code here duplicates the functionality of scripts/c2init.in.
 % Any changes there may also require changes here, and vice versa.
@@ -990,8 +1065,7 @@
 		!IO) :-
 	globals__io_lookup_bool_option(verbose, Verbose, !IO),
 	globals__io_lookup_bool_option(statistics, Stats, !IO),
-	maybe_write_string(Verbose, "% Creating initialization file...\n",
-		!IO),
+    maybe_write_string(Verbose, "% Creating initialization file...\n", !IO),
 
 	globals__io_get_globals(Globals, !IO),
 	compute_grade(Globals, Grade),
@@ -1000,22 +1074,18 @@
 	maybe_pic_object_file_extension(PIC, ObjExt, !IO),
 	InitObj = "_init" ++ ObjExt,
 
-	module_name_to_file_name(ModuleName, "_init.c", yes, InitCFileName,
-		!IO),
-	module_name_to_file_name(ModuleName, InitObj, yes, InitObjFileName,
-		!IO),
+    module_name_to_file_name(ModuleName, "_init.c", yes, InitCFileName, !IO),
+    module_name_to_file_name(ModuleName, InitObj, yes, InitObjFileName, !IO),
 
 	list__map_foldl(
 		(pred(ThisModule::in, CFileName::out, IO0::di, IO::uo) is det :-
-			module_name_to_file_name(ThisModule, ".c", no,
-				CFileName, IO0, IO)
+            module_name_to_file_name(ThisModule, ".c", no, CFileName, IO0, IO)
 		), ModuleNames, CFileNameList, !IO),
 	join_quoted_string_list(CFileNameList, "", "", " ", CFileNames),
 
 	globals__io_lookup_accumulating_option(init_file_directories,
 		InitFileDirsList, !IO),
-	join_quoted_string_list(InitFileDirsList, "-I ", "", " ",
-		InitFileDirs),
+    join_quoted_string_list(InitFileDirsList, "-I ", "", " ", InitFileDirs),
 
 	globals__io_lookup_accumulating_option(init_files, InitFileNamesList0,
 		!IO),
@@ -1041,8 +1111,7 @@
 	globals__io_get_trace_level(TraceLevel, !IO),
 	( given_trace_level_is_none(TraceLevel) = no ->
 		TraceOpt = "-t",
-		InitFileNamesList =
-			InitFileNamesList1 ++ TraceInitFileNamesList
+        InitFileNamesList = InitFileNamesList1 ++ TraceInitFileNamesList
 	;
 		TraceOpt = "",
 		InitFileNamesList = InitFileNamesList1
@@ -1051,11 +1120,10 @@
 
 	globals__io_lookup_accumulating_option(runtime_flags, RuntimeFlagsList,
 		!IO),
-	join_quoted_string_list(RuntimeFlagsList, "-r ", "", " ",
-		RuntimeFlags),
+    join_quoted_string_list(RuntimeFlagsList, "-r ", "", " ", RuntimeFlags),
 
-	globals__io_lookup_bool_option(extra_initialization_functions,
-		ExtraInits, !IO),
+    globals__io_lookup_bool_option(extra_initialization_functions, ExtraInits,
+        !IO),
 	ExtraInitsOpt = ( ExtraInits = yes -> "-x" ; "" ),
 
 	globals__io_lookup_bool_option(main, Main, !IO),
@@ -1097,11 +1165,9 @@
 				io__file_modification_time(InitObjFileName,
 					InitObjModTimeResult, !IO),
 				(
-					InitObjModTimeResult =
-						ok(InitObjModTime),
+                    InitObjModTimeResult = ok(InitObjModTime),
 					InitCModTimeResult = ok(InitCModTime),
-					compare(TimeCompare, InitObjModTime,
-						InitCModTime),
+                    compare(TimeCompare, InitObjModTime, InitCModTime),
 					( TimeCompare = (=)
 					; TimeCompare = (>)
 					)
@@ -1148,10 +1214,9 @@
 
 	maybe_write_string(Verbose, "% Linking...\n", !IO),
 	globals__io_lookup_string_option(library_extension, LibExt, !IO),
-	globals__io_lookup_string_option(shared_library_extension,
-		SharedLibExt, !IO),
-	globals__io_lookup_string_option(executable_file_extension, ExeExt,
+    globals__io_lookup_string_option(shared_library_extension, SharedLibExt,
 		!IO),
+    globals__io_lookup_string_option(executable_file_extension, ExeExt, !IO),
 	( LinkTargetType = static_library ->
 		Ext = LibExt,
 		module_name_to_lib_file_name("lib", ModuleName, LibExt, yes,
@@ -1160,8 +1225,7 @@
 			LinkSucceeded, !IO)
 	; LinkTargetType = java_archive ->
 		Ext = ".jar",
-		module_name_to_file_name(ModuleName, Ext, yes, OutputFileName,
-			!IO),
+        module_name_to_file_name(ModuleName, Ext, yes, OutputFileName, !IO),
 		create_java_archive(ErrorStream, ModuleName, OutputFileName,
 			ObjectsList, LinkSucceeded, !IO)
 	;
@@ -1174,20 +1238,19 @@
 			ThreadFlagsOpt = shlib_linker_thread_flags,
 			DebugFlagsOpt = shlib_linker_debug_flags,
 			TraceFlagsOpt = shlib_linker_trace_flags,
-			globals__io_lookup_bool_option(allow_undefined,
-				AllowUndef, !IO),
-			( AllowUndef = yes ->
+            globals__io_lookup_bool_option(allow_undefined, AllowUndef, !IO),
+            (
+                AllowUndef = yes,
 				globals__io_lookup_string_option(
-					linker_allow_undefined_flag, UndefOpt,
-					!IO)
+                    linker_allow_undefined_flag, UndefOpt, !IO)
 			;
+                AllowUndef = no,
 				globals__io_lookup_string_option(
-					linker_error_undefined_flag, UndefOpt,
-					!IO)
+                    linker_error_undefined_flag, UndefOpt, !IO)
 			),
 			Ext = SharedLibExt,
-			module_name_to_lib_file_name("lib", ModuleName,
-				Ext, yes, OutputFileName, !IO)
+            module_name_to_lib_file_name("lib", ModuleName, Ext, yes,
+                OutputFileName, !IO)
 		;
 			LinkTargetType = static_library,
 			error("compile_target_code__link")
@@ -1205,86 +1268,77 @@
 			TraceFlagsOpt = linker_trace_flags,
 			UndefOpt = "",
 			Ext = ExeExt,
-			module_name_to_file_name(ModuleName, Ext,
-				yes, OutputFileName, !IO)
+            module_name_to_file_name(ModuleName, Ext, yes, OutputFileName, !IO)
 		),
 
-		%
 		% Should the executable be stripped?
-		%
 		globals__io_lookup_bool_option(strip, Strip, !IO),
-		( LinkTargetType = executable, Strip = yes ->
-			globals__io_lookup_string_option(linker_strip_flag,
-				StripOpt, !IO)
+        (
+            LinkTargetType = executable,
+            Strip = yes
+        ->
+            globals__io_lookup_string_option(linker_strip_flag, StripOpt, !IO)
 		;
 			StripOpt = ""
 		),
 
 		globals__io_lookup_bool_option(target_debug, TargetDebug, !IO),
-		( TargetDebug = yes ->
-			globals__io_lookup_string_option(DebugFlagsOpt,
-				DebugOpts, !IO)
+        (
+            TargetDebug = yes,
+            globals__io_lookup_string_option(DebugFlagsOpt, DebugOpts, !IO)
 		;
+            TargetDebug = no,
 			DebugOpts = ""
 		),
 
-		%
 		% Should the executable be statically linked?
-		%
 		globals__io_lookup_string_option(linkage, Linkage, !IO),
-		( LinkTargetType = executable, Linkage = "static" ->
-			globals__io_lookup_string_option(linker_static_flags,
-				StaticOpts, !IO)
+        (
+            LinkTargetType = executable,
+            Linkage = "static"
+        ->
+            globals__io_lookup_string_option(linker_static_flags, StaticOpts,
+                !IO)
 		;
 			StaticOpts = ""
 		),
 
-		%
 		% Are the thread libraries needed?
-		%
 		use_thread_libs(UseThreadLibs, !IO),
-		( UseThreadLibs = yes ->
-			globals__io_lookup_string_option(ThreadFlagsOpt,
-				ThreadOpts, !IO)
+        (
+            UseThreadLibs = yes,
+            globals__io_lookup_string_option(ThreadFlagsOpt, ThreadOpts, !IO)
 		;
+            UseThreadLibs = no,
 			ThreadOpts = ""
 		),
 
-		%
 		% Find the Mercury standard libraries.
-		%
 		globals__io_lookup_maybe_string_option(
-			mercury_standard_library_directory, MaybeStdLibDir,
-			!IO),
+            mercury_standard_library_directory, MaybeStdLibDir, !IO),
 		(
 			MaybeStdLibDir = yes(StdLibDir),
-			get_mercury_std_libs(LinkTargetType,
-				StdLibDir, MercuryStdLibs, !IO)
+            get_mercury_std_libs(LinkTargetType, StdLibDir, MercuryStdLibs,
+                !IO)
 		;
 			MaybeStdLibDir = no,
 			MercuryStdLibs = ""
 		),
 
-		%
 		% Find which system libraries are needed.
-		%
 		get_system_libs(LinkTargetType, SystemLibs, !IO),
 
 		join_quoted_string_list(ObjectsList, "", "", " ", Objects),
-		globals__io_lookup_accumulating_option(LDFlagsOpt,
-			LDFlagsList, !IO),
+        globals__io_lookup_accumulating_option(LDFlagsOpt, LDFlagsList, !IO),
 		join_string_list(LDFlagsList, "", "", " ", LDFlags),
-		globals__io_lookup_accumulating_option(
-			link_library_directories,
+        globals__io_lookup_accumulating_option(link_library_directories,
 			LinkLibraryDirectoriesList, !IO),
-		globals__io_lookup_string_option(linker_path_flag,
-			LinkerPathFlag, !IO),
-		join_quoted_string_list(LinkLibraryDirectoriesList,
-			LinkerPathFlag, "", " ", LinkLibraryDirectories),
+        globals__io_lookup_string_option(linker_path_flag, LinkerPathFlag,
+            !IO),
+        join_quoted_string_list(LinkLibraryDirectoriesList, LinkerPathFlag, "",
+            " ", LinkLibraryDirectories),
 
-		%
 		% Set up the runtime library path.
-		%
 		globals__io_lookup_bool_option(shlib_linker_use_install_name,
 			UseInstallName, !IO),
 		(
@@ -1295,32 +1349,25 @@
 			)
 		->
 			globals__io_lookup_accumulating_option(
-				runtime_link_library_directories,
-				RpathDirs, !IO),
+                runtime_link_library_directories, RpathDirs, !IO),
 			( RpathDirs = [] ->
 				RpathOpts = ""
 			;
-				globals__io_lookup_string_option(RpathSepOpt,
-					RpathSep, !IO),
-				globals__io_lookup_string_option(RpathFlagOpt,
-					RpathFlag, !IO),
-				RpathOpts0 = string__join_list(RpathSep,
-					RpathDirs),
+                globals__io_lookup_string_option(RpathSepOpt, RpathSep, !IO),
+                globals__io_lookup_string_option(RpathFlagOpt, RpathFlag, !IO),
+                RpathOpts0 = string__join_list(RpathSep, RpathDirs),
 				RpathOpts = RpathFlag ++ RpathOpts0
 			)
 		;
 			RpathOpts = ""
 		),
 				
-		%
 		% Set up the installed name for shared libraries.
-		%
 		(
 			UseInstallName = yes,
 			LinkTargetType = shared_library
 		->
-			get_install_name_option(OutputFileName, InstallNameOpt,
-				!IO)
+            get_install_name_option(OutputFileName, InstallNameOpt, !IO)
 		;
 			InstallNameOpt = ""
 		),
@@ -1329,15 +1376,13 @@
 		( given_trace_level_is_none(TraceLevel) = yes ->
 			TraceOpts = ""
 		;
-			globals__io_lookup_string_option(TraceFlagsOpt,
-				TraceOpts, !IO)
+            globals__io_lookup_string_option(TraceFlagsOpt, TraceOpts, !IO)
 		),
 
-		%
 		% Pass either `-llib' or `PREFIX/lib/GRADE/FULLARCH/liblib.a',
 		% depending on whether we are linking with static or shared
 		% Mercury libraries.
-		%
+
 		globals__io_lookup_accumulating_option(
 			mercury_library_directories, MercuryLibDirs0, !IO),
 		globals__io_lookup_string_option(fullarch, FullArch, !IO),
@@ -1356,13 +1401,12 @@
 			LinkOptSep, !IO),
 		(
 			LibrariesSucceeded = yes,
-			join_quoted_string_list(LinkLibrariesList,
-				"", "", " ", LinkLibraries),
+            join_quoted_string_list(LinkLibrariesList, "", "", " ",
+                LinkLibraries),
 
-			% Note that LDFlags may contain `-l' options
-			% so it should come after Objects.
-			globals__io_lookup_string_option(CommandOpt, Command,
-				!IO),
+            % Note that LDFlags may contain `-l' options so it should come
+            % after Objects.
+            globals__io_lookup_string_option(CommandOpt, Command, !IO),
 			string__append_list(
 				[Command, " ",
 				StaticOpts, " ", StripOpt, " ", UndefOpt, " ",
@@ -1374,26 +1418,26 @@
 				MercuryStdLibs, " ", SystemLibs],
 				LinkCmd),
 
-			globals__io_lookup_bool_option(demangle, Demangle,
-				!IO),
-			( Demangle = yes ->
-				globals__io_lookup_string_option(
-					demangle_command, DemamngleCmd, !IO),
+            globals__io_lookup_bool_option(demangle, Demangle, !IO),
+            (
+                Demangle = yes,
+                globals__io_lookup_string_option(demangle_command,
+                    DemamngleCmd, !IO),
 				MaybeDemangleCmd = yes(DemamngleCmd)
 			;
+                Demangle = no,
 				MaybeDemangleCmd = no
 			),
 
-			invoke_system_command(ErrorStream, verbose_commands,
-				LinkCmd, MaybeDemangleCmd, LinkSucceeded, !IO)
+            invoke_system_command(ErrorStream, verbose_commands, LinkCmd,
+                MaybeDemangleCmd, LinkSucceeded, !IO)
 		;
 			LibrariesSucceeded = no,
 			LinkSucceeded = no
 		)
 	),
 	maybe_report_stats(Stats, !IO),
-	globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs,
-		!IO),
+    globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs, !IO),
 	(
 		LinkSucceeded = yes,
 		UseGradeSubdirs = yes
@@ -1402,11 +1446,10 @@
 		globals__io_set_option(use_subdirs, bool(no), !IO),
 		globals__io_set_option(use_grade_subdirs, bool(no), !IO),
 		( LinkTargetType = executable ->
-			module_name_to_file_name(ModuleName, Ext,
-				no, UserDirFileName, !IO)
+            module_name_to_file_name(ModuleName, Ext, no, UserDirFileName, !IO)
 		;
-			module_name_to_lib_file_name("lib", ModuleName, Ext,
-				no, UserDirFileName, !IO)
+            module_name_to_lib_file_name("lib", ModuleName, Ext, no,
+                UserDirFileName, !IO)
 		),
 		globals__io_set_option(use_subdirs, bool(yes), !IO),
 		globals__io_set_option(use_grade_subdirs, bool(yes), !IO),
@@ -1421,6 +1464,7 @@
 
 	% Find the standard Mercury libraries, and the system
 	% libraries needed by them.
+    %
 :- pred get_mercury_std_libs(linked_target_type::in, dir_name::in, string::out,
 	io::di, io::uo) is det.
 
@@ -1431,9 +1475,7 @@
 	globals__io_get_globals(Globals, !IO),
 	grade_directory_component(Globals, GradeDir),
 
-	%
 	% GC libraries.
-	%
 	(
 		GCMethod = automatic,
 		StaticGCLibs = "",
@@ -1446,15 +1488,21 @@
 		GCMethod = boehm,
 		globals__io_lookup_bool_option(profile_time, ProfTime, !IO),
 		globals__io_lookup_bool_option(profile_deep, ProfDeep, !IO),
-		( ( ProfTime = yes ; ProfDeep = yes ) ->
+        (
+            ( ProfTime = yes
+            ; ProfDeep = yes
+            )
+        ->
 			GCGrade0 = "gc_prof"
 		;
 			GCGrade0 = "gc"
 		),
 		globals__io_lookup_bool_option(parallel, Parallel, !IO),
-		( Parallel = yes ->
+        (
+            Parallel = yes,
 			GCGrade = "par_" ++ GCGrade0
 		;
+            Parallel = no,
 			GCGrade = GCGrade0
 		),
 		make_link_lib(TargetType, GCGrade, SharedGCLibs, !IO),
@@ -1471,9 +1519,7 @@
 		SharedGCLibs = ""
 	),
 
-	%
 	% Trace libraries.
-	%
 	globals__io_get_trace_level(TraceLevel, !IO),
 	( given_trace_level_is_none(TraceLevel) = yes ->
 		StaticTraceLibs = "",
@@ -1540,43 +1586,35 @@
 	is det.
 
 get_system_libs(TargetType, SystemLibs, !IO) :-
-	%
 	% System libraries used when tracing.
-	%
 	globals__io_get_trace_level(TraceLevel, !IO),
 	( given_trace_level_is_none(TraceLevel) = yes ->
 		SystemTraceLibs = ""
 	;
-		globals__io_lookup_string_option(trace_libs, SystemTraceLibs0,
-			!IO),
+        globals__io_lookup_string_option(trace_libs, SystemTraceLibs0, !IO),
 		globals__io_lookup_bool_option(use_readline, UseReadline, !IO),
 		( UseReadline = yes ->
-			globals__io_lookup_string_option(readline_libs,
-				ReadlineLibs, !IO),
-			SystemTraceLibs =
-				SystemTraceLibs0 ++ " " ++ ReadlineLibs
+            globals__io_lookup_string_option(readline_libs, ReadlineLibs, !IO),
+            SystemTraceLibs = SystemTraceLibs0 ++ " " ++ ReadlineLibs
 		;
 			SystemTraceLibs = SystemTraceLibs0
 		)
 	),
 
-	%
 	% Thread libraries
-	%
 	use_thread_libs(UseThreadLibs, !IO),
-	( UseThreadLibs = yes ->
+    (
+        UseThreadLibs = yes,
 		globals__io_lookup_string_option(thread_libs, ThreadLibs, !IO)
 	;
+        UseThreadLibs = no,
 		ThreadLibs = ""
 	),
 
-	%
 	% Other system libraries.
-	%
 	(
 		TargetType = shared_library,
-		globals__io_lookup_string_option(shared_libs, OtherSystemLibs,
-			!IO)
+        globals__io_lookup_string_option(shared_libs, OtherSystemLibs, !IO)
 	;
 		TargetType = static_library,
 		error("compile_target_code__get_std_libs: static library")
@@ -1585,8 +1623,7 @@
 		error("compile_target_code__get_std_libs: java archive")
 	;
 		TargetType = executable,
-		globals__io_lookup_string_option(math_lib, OtherSystemLibs,
-			!IO)
+        globals__io_lookup_string_option(math_lib, OtherSystemLibs, !IO)
 	),
 
 	SystemLibs = string__join_list(" ",
@@ -1612,21 +1649,18 @@
 		MercuryLinkage = "static",
 		list__member(LibName, MercuryLibs)
 	->
-		% If we are linking statically with Mercury libraries,
-		% pass the absolute pathname of the `.a' file for
-		% the library.
-		globals__io_lookup_bool_option(use_grade_subdirs,
-			UseGradeSubdirs, !IO),
+        % If we are linking statically with Mercury libraries, pass the
+        % absolute pathname of the `.a' file for the library.
+        globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs,
+            !IO),
 
 		file_name_to_module_name(LibName, LibModuleName),
-		globals__io_lookup_string_option(library_extension, LibExt,
-			!IO),
+        globals__io_lookup_string_option(library_extension, LibExt, !IO),
 
 		globals__io_set_option(use_grade_subdirs, bool(no), !IO),
-		module_name_to_lib_file_name("lib", LibModuleName, LibExt,
-			no, LibFileName, !IO),
-		globals__io_set_option(use_grade_subdirs,
-			bool(UseGradeSubdirs), !IO),
+        module_name_to_lib_file_name("lib", LibModuleName, LibExt, no,
+            LibFileName, !IO),
+        globals__io_set_option(use_grade_subdirs, bool(UseGradeSubdirs), !IO),
 
 		io__input_stream(InputStream, !IO),
 		search_for_file_returning_dir(MercuryLibDirs, LibFileName,
@@ -1639,8 +1673,7 @@
 		;
 			SearchResult = error(Error),
 			LinkerOpt = "",
-			write_error_pieces_maybe_with_context(no,
-				0, [words(Error)], !IO),
+            write_error_pieces_maybe_with_context(no, 0, [words(Error)], !IO),
 			!:Succeeded = no
 		)
 	;
@@ -1652,11 +1685,11 @@
 
 create_archive(ErrorStream, LibFileName, Quote, ObjectList, Succeeded, !IO) :-
 	globals__io_lookup_string_option(create_archive_command, ArCmd, !IO),
-	globals__io_lookup_accumulating_option(
-		create_archive_command_flags, ArFlagsList, !IO),
+    globals__io_lookup_accumulating_option(create_archive_command_flags,
+        ArFlagsList, !IO),
 	join_string_list(ArFlagsList, "", "", " ", ArFlags),
-	globals__io_lookup_string_option(
-		create_archive_command_output_flag, ArOutputFlag, !IO),
+    globals__io_lookup_string_option(create_archive_command_output_flag,
+        ArOutputFlag, !IO),
 	globals__io_lookup_string_option(ranlib_command, RanLib, !IO),
 	(
 		Quote = yes,
@@ -1681,8 +1714,8 @@
 		Succeeded = MakeLibCmdSucceeded
 	;
 		RanLibCmd = string__append_list([RanLib, " ", LibFileName]),
-		invoke_system_command(ErrorStream, verbose_commands,
-			RanLibCmd, Succeeded, !IO)
+        invoke_system_command(ErrorStream, verbose_commands, RanLibCmd,
+            Succeeded, !IO)
 	).
 
 :- pred create_java_archive(io__output_stream::in, module_name::in,
@@ -1697,11 +1730,9 @@
 	join_quoted_string_list(ObjectList, "", "", " ", Objects),
 	list_class_files_for_jar(ModuleName, Objects, ListClassFiles, !IO),
 	Cmd = string__append_list([
-		Jar, " ", JarCreateFlags, " ", JarFileName, " ", ListClassFiles
-		]),
+        Jar, " ", JarCreateFlags, " ", JarFileName, " ", ListClassFiles ]),
 
-	invoke_system_command(ErrorStream, verbose_commands, Cmd, Succeeded,
-		!IO).
+    invoke_system_command(ErrorStream, verbose_commands, Cmd, Succeeded, !IO).
 
 get_object_code_type(FileType, ObjectCodeType, !IO) :-
 	globals__io_lookup_string_option(pic_object_file_extension, PicObjExt,
@@ -1725,8 +1756,7 @@
 			ObjectCodeType = non_pic
 		;
 			FileType = shared_library,
-			ObjectCodeType =
-				( if PicObjExt = ObjExt then non_pic else pic )
+            ObjectCodeType = ( if PicObjExt = ObjExt then non_pic else pic )
 		;
 			FileType = java_archive,
 			ObjectCodeType = non_pic
@@ -1734,11 +1764,9 @@
 			FileType = executable,
 			( MercuryLinkage = "shared" ->
 				(
-					% We only need to create `.lpic'
-					% files if `-DMR_PIC_REG' has an
-					% effect, which currently is only
-					% with grades using GCC global
-					% registers on x86 Unix.
+                    % We only need to create `.lpic' files if `-DMR_PIC_REG'
+                    % has an effect, which currently is only with grades using
+                    % GCC global registers on x86 Unix.
 					( LinkWithPicObjExt = ObjExt
 					; HighLevelCode = yes
 					; GCCGlobals = no
@@ -1767,17 +1795,18 @@
 :- pred standard_library_directory_option(string::out, io::di, io::uo) is det.
 
 standard_library_directory_option(Opt, !IO) :-
-	globals__io_lookup_maybe_string_option(
-		mercury_standard_library_directory, MaybeStdLibDir, !IO),
-	globals__io_lookup_maybe_string_option(
-		mercury_configuration_directory, MaybeConfDir, !IO),
+    globals__io_lookup_maybe_string_option(mercury_standard_library_directory,
+        MaybeStdLibDir, !IO),
+    globals__io_lookup_maybe_string_option(mercury_configuration_directory,
+        MaybeConfDir, !IO),
 	(
 		MaybeStdLibDir = yes(StdLibDir),
-		Opt0 = "--mercury-standard-library-directory "
-			++ StdLibDir ++ " ",
-		( MaybeConfDir = yes(ConfDir), ConfDir \= StdLibDir ->
-			Opt = Opt0 ++ "--mercury-configuration-directory "
-					++ ConfDir ++ " "
+        Opt0 = "--mercury-standard-library-directory " ++ StdLibDir ++ " ",
+        (
+            MaybeConfDir = yes(ConfDir),
+            ConfDir \= StdLibDir
+        ->
+            Opt = Opt0 ++ "--mercury-configuration-directory " ++ ConfDir ++ " "
 		;
 			Opt = Opt0
 		)
@@ -1788,42 +1817,44 @@
 
 %-----------------------------------------------------------------------------%
 
-	% join_string_list(Strings, Prefix, Suffix, Serarator, Result)
+    % join_string_list(Strings, Prefix, Suffix, Serarator, Result):
+    %
+    % Appends the strings in the list `Strings' together into the string
+    % Result. Each string is prefixed by Prefix, suffixed by Suffix and
+    % separated by Separator.
 	%
-	% Appends the strings in the list `Strings' together into the
-	% string Result. Each string is prefixed by Prefix, suffixed by
-	% Suffix and separated by Separator.
-
 :- pred join_string_list(list(string)::in, string::in, string::in, string::in,
 	string::out) is det.
 
 join_string_list([], _Prefix, _Suffix, _Separator, "").
 join_string_list([String | Strings], Prefix, Suffix, Separator, Result) :-
-	( Strings = [] ->
+    (
+        Strings = [],
 		string__append_list([Prefix, String, Suffix], Result)
 	;
+        Strings = [_ | _],
 		join_string_list(Strings, Prefix, Suffix, Separator, Result0),
-		string__append_list([Prefix, String, Suffix, Separator,
-			Result0], Result)
+        string__append_list([Prefix, String, Suffix, Separator, Result0],
+            Result)
 	).
 
-	% As above, but quote the strings first.
-	% Note that the strings in values of the *flags options are
-	% already quoted.
+    % As above, but quote the strings first. Note that the strings in values
+    % of the *flags options are already quoted.
+    %
 :- pred join_quoted_string_list(list(string)::in, string::in, string::in,
 	string::in, string::out) is det.
 
 join_quoted_string_list(Strings, Prefix, Suffix, Separator, Result) :-
-	join_string_list(map(quote_arg, Strings),
-		Prefix, Suffix, Separator, Result).
+    join_string_list(map(quote_arg, Strings), Prefix, Suffix, Separator,
+        Result).
 
-	% join_module_list(ModuleNames, Extension, Result)
+    % join_module_list(ModuleNames, Extension, Result):
 	%
 	% The list of strings `Result' is computed from the list of strings
-	% `ModuleNames', by removing any directory paths, and
-	% converting the strings to file names and then back,
-	% adding the specified Extension.  (This conversion ensures
-	% that we follow the usual file naming conventions.)
+    % `ModuleNames', by removing any directory paths, and converting the
+    % strings to file names and then back, adding the specified Extension.
+    % (This conversion ensures that we follow the usual file naming
+    % conventions.)
 
 :- pred join_module_list(list(string)::in, string::in, list(string)::out,
 	io::di, io::uo) is det.
@@ -1837,8 +1868,8 @@
 %-----------------------------------------------------------------------------%
 
 write_num_split_c_files(ModuleName, NumChunks, Succeeded, !IO) :-
-	module_name_to_file_name(ModuleName, ".num_split", yes,
-		NumChunksFileName, !IO),
+    module_name_to_file_name(ModuleName, ".num_split", yes, NumChunksFileName,
+        !IO),
 	io__open_output(NumChunksFileName, Res, !IO),
 	( Res = ok(OutputStream) ->
 		io__write_int(OutputStream, NumChunks, !IO),
@@ -1855,8 +1886,8 @@
 	).
 
 read_num_split_c_files(ModuleName, MaybeNumChunks, !IO) :-
-	module_name_to_file_name(ModuleName, ".num_split", no,
-		NumChunksFileName, !IO),
+    module_name_to_file_name(ModuleName, ".num_split", no, NumChunksFileName,
+        !IO),
 	io__open_input(NumChunksFileName, Res, !IO),
 	(
 		Res = ok(FileStream),
@@ -1865,27 +1896,23 @@
 		(
 			MaybeNumChunksString = ok(NumChunksString),
 			(
-				string__to_int(
-					string__from_char_list(NumChunksString),
+                string__to_int(string__from_char_list(NumChunksString),
 					NumChunks)
 			->
 				MaybeNumChunks = ok(NumChunks)
 			;
-				MaybeNumChunks = error(
-					"Software error: error in `"
+                MaybeNumChunks = error("Software error: error in `"
 					++ NumChunksFileName
 					++ "': expected single int.\n")
 			)
 		;
 			MaybeNumChunksString = eof,
-			MaybeNumChunks = error(
-				"Software error: error in `"
+            MaybeNumChunks = error("Software error: error in `"
 				++ NumChunksFileName
 				++ "': expected single int.\n")
 		;
 			MaybeNumChunksString = error(_),
-			MaybeNumChunks = error(
-				"Software error: error in `"
+            MaybeNumChunks = error("Software error: error in `"
 				++ NumChunksFileName
 				++ "': expected single int.\n")
 		)
@@ -1902,16 +1929,14 @@
 
 remove_split_c_output_files(ModuleName, ThisChunk, NumChunks, !IO) :-
 	( ThisChunk =< NumChunks ->
-		globals__io_lookup_string_option(object_file_extension, Obj,
-			!IO),
-		module_name_to_split_c_file_name(ModuleName, ThisChunk,
-			".c", CFileName, !IO),
-		module_name_to_split_c_file_name(ModuleName, ThisChunk,
-			Obj, ObjFileName, !IO),
+        globals__io_lookup_string_option(object_file_extension, Obj, !IO),
+        module_name_to_split_c_file_name(ModuleName, ThisChunk, ".c",
+            CFileName, !IO),
+        module_name_to_split_c_file_name(ModuleName, ThisChunk, Obj,
+            ObjFileName, !IO),
 		io__remove_file(CFileName, _, !IO),
 		io__remove_file(ObjFileName, _, !IO),
-		remove_split_c_output_files(ModuleName, ThisChunk, NumChunks,
-			!IO)
+        remove_split_c_output_files(ModuleName, ThisChunk, NumChunks, !IO)
 	;
 		true
 	).
@@ -1922,8 +1947,7 @@
 	% Pass the main module first.
 	list__map_foldl(
 		(pred(Module::in, FileName::out, IO0::di, IO::uo) is det :-
-			module_name_to_file_name(Module, ".m", no, FileName,
-				IO0, IO)
+            module_name_to_file_name(Module, ".m", no, FileName, IO0, IO)
 		),
 		[MainModule | list__delete_all(AllModules, MainModule)],
 		ModuleNameStrings, !IO),
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.63
diff -u -b -r1.63 continuation_info.m
--- compiler/continuation_info.m	5 Oct 2005 06:33:33 -0000	1.63
+++ compiler/continuation_info.m	12 Oct 2005 06:57:00 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1997-2000,2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -71,86 +73,83 @@
 :- import_module set.
 :- import_module std_util.
 
-	%
 	% Information for any procedure, includes information about the
 	% procedure itself, and any internal labels within it.
-	%
 :- type proc_layout_info
 	--->	proc_layout_info(
 			rtti_proc_label	:: rtti_proc_label,
 					% The identity of the procedure.
+
 			entry_label	:: label,
-					% Determines which stack is used.
+
 			detism		:: determinism,
-					% Number of stack slots.
+                % Determines which stack is used.
+
 			stack_slot_count :: int,
-					% Location of succip on stack.
+                % Number of stack slots.
+
 			succip_slot	:: maybe(int),
-					% If the trace level is not none, this
-					% contains the label associated with
-					% the call event, whose stack layout
-					% gives the locations of the input
-					% arguments on procedure entry, for
-					% use in implementing retry in the
-					% debugger.
+                % Location of succip on stack.
+
 			eval_method	:: eval_method,
-					% Of the procedure.
+                % The evaluation method of the procedure.
+
 			eff_trace_level	:: trace_level,
-					% The effective trace level of the
-					% procedure.
+                % The effective trace level of the procedure.
+
 			call_label	:: maybe(label),
-					% If the trace level is not none,
-					% this contains the label associated
-					% with the call event, whose stack
-					% layout says which variables were
-					% live and where on entry.
+                % If the trace level is not none, this contains the label
+                % associated with the call event, whose stack layout says
+                % which variables were live and where on entry.
+
 			max_trace_reg	:: int,
-					% The number of the highest numbered
-					% rN register that can contain useful
-					% information during a call to MR_trace
-					% from within this procedure.
+                % The number of the highest numbered rN register that can
+                % contain useful information during a call to MR_trace from
+                % within this procedure.
+
 			head_vars	:: list(prog_var),
-					% The head variables, in order,
-					% including the ones introduced by the
-					% compiler.
+                % The head variables, in order, including the ones introduced
+                % by the compiler.
+
 			arg_modes	:: list(mode),
 					% The modes of the head variables.
+
 			proc_body	:: hlds_goal,
 					% The body of the procedure.
+
 			needs_body_rep	:: bool,
-					% Do we need to include a
-					% representation of the procedure body
+                % Do we need to include a representation of the procedure body
 					% in the exec trace layout?
+
 			initial_instmap	:: instmap,
-					% The instmap at the start of the
-					% procedure body.
+                % The instmap at the start of the procedure body.
+
 			trace_slot_info	:: trace_slot_info,
-					% Info about the stack slots used
-					% for tracing.
+                % Info about the stack slots used for tracing.
+
 			need_proc_id	:: bool,
-					% Do we require the procedure id
-					% section of the procedure layout
-					% to be present, even if the option
-					% procid_stack_layout is not set?
+                % Do we require the procedure id section of the procedure
+                % layout to be present, even if the option procid_stack_layout
+                % is not set?
+
 			varset		:: prog_varset,
-					% The names of all the variables.
 			vartypes	:: vartypes,
+                % The names and types of all the variables.
+
 			internal_map	:: proc_label_layout_info,
-					% Info for each internal label,
-					% needed for basic_stack_layouts.
+                % Info for each internal label, needed for basic_stack_layouts.
+
 			maybe_table_info :: maybe(proc_table_info),
+
 			need_all_names	:: bool,
-					% True iff we need the names of all the
-					% variables.
+                % True iff we need the names of all the variables.
+
 			deep_prof	:: maybe(proc_layout_proc_static)
 		).
 
-	%
 	% Information about the labels internal to a procedure.
-	%
 :- type proc_label_layout_info	==	map(int, internal_layout_info).
 
-	%
 	% Information for an internal label.
 	%
 	% There are three ways for the compiler to generate labels for
@@ -225,7 +224,6 @@
 	% possible for both fields to be set. In this case, stack_layout.m
 	% will take the union of the relevant info. If neither field is set,
 	% then the label's layout is required only for stack tracing.
-	%
 :- type internal_layout_info
 	--->	internal_layout_info(
 			maybe(trace_port_layout_info),
@@ -248,35 +246,33 @@
 			layout_label_info
 		).
 
-	%
 	% Information about the layout of live data for a label.
-	%
 :- type layout_label_info
 	--->	layout_label_info(
 			set(layout_var_info),
-				% live vars and their locations/names
+                % Live vars and their locations/names.
+
 			map(tvar, set(layout_locn))
-				% locations of polymorphic type vars
+                % Locations of polymorphic type vars.
 		).
 
 :- type layout_var_info
 	--->	layout_var_info(
-			layout_locn,		% the location of the variable
-			live_value_type, 	% info about the variable
-			string			% where in the compiler
-						% this layout_var_info was
-						% created
+                layout_locn,        % The location of the variable.
+                live_value_type,    % Info about the variable.
+                string              % Where in the compiler this
+                                    % layout_var_info was created
 		).
 
 :- type closure_layout_info
 	--->	closure_layout_info(
 			list(closure_arg_info),
-				% there is one closure_arg_info for each
-				% argument of the called procedure,
-				% even the args which are not in the closure
+                % There is one closure_arg_info for each argument of the called
+                % procedure, even the args which are not in the closure
+
 			map(tvar, set(layout_locn))
-				% locations of polymorphic type vars,
-				% encoded so that rN refers to argument N
+                % Locations of polymorphic type vars,
+                % encoded so that rN refers to argument N.
 		).
 
 :- type closure_arg_info
@@ -295,17 +291,17 @@
 		).
 
 :- type slot_contents
-	--->	ticket			% a ticket (trail pointer)
-	;	ticket_counter		% a copy of the ticket counter
+    --->    ticket          % A ticket (trail pointer).
+    ;       ticket_counter  % A copy of the ticket counter.
 	;	trace_data
-	;	sync_term		% a syncronization term used
+    ;       sync_term       % A syncronization term used
 					% at the end of par_conjs.
-					% see par_conj_gen.m for details.
+                            % See par_conj_gen.m for details.
 	;	lval(lval).
 
-	% Call continuation_info__maybe_process_proc_llds on the code
-	% of every procedure in the list.
-:- pred continuation_info__maybe_process_llds(list(c_procedure)::in,
+    % Call maybe_process_proc_llds on the code of every procedure in the list.
+    %
+:- pred maybe_process_llds(list(c_procedure)::in,
 	module_info::in, global_data::in, global_data::out) is det.
 
 	% Check whether this procedure ought to have any layout structures
@@ -313,19 +309,21 @@
 	% include all the continuation labels within a proc. Whether or not
 	% the information about a continuation label includes the variables
 	% live at that label depends on the values of options.
-:- pred continuation_info__maybe_process_proc_llds(list(instruction)::in,
+    %
+:- pred maybe_process_proc_llds(list(instruction)::in,
 	pred_proc_id::in, module_info::in,
 	global_data::in, global_data::out) is det.
 
 	% Check whether the given procedure should have at least (a) a basic
 	% stack layout, and (b) a procedure id layout generated for it.
 	% The two bools returned answer these two questions respectively.
-:- pred continuation_info__basic_stack_layout_for_proc(pred_info::in,
+    %
+:- pred basic_stack_layout_for_proc(pred_info::in,
 	globals::in, bool::out, bool::out) is det.
 
-	% Generate the layout information we need for the return point
-	% of a call.
-:- pred continuation_info__generate_return_live_lvalues(
+    % Generate the layout information we need for the return point of a call.
+    %
+:- pred generate_return_live_lvalues(
 	assoc_list(prog_var, arg_loc)::in, instmap::in, list(prog_var)::in,
 	map(prog_var, set(lval))::in, assoc_list(lval, slot_contents)::in,
 	proc_info::in, module_info::in, globals::in, bool::in,
@@ -333,21 +331,24 @@
 
 	% Generate the layout information we need for a resumption point,
 	% a label where forward execution can restart after backtracking.
-:- pred continuation_info__generate_resume_layout(map(prog_var, set(lval))::in,
+    %
+:- pred generate_resume_layout(map(prog_var, set(lval))::in,
 	assoc_list(lval, slot_contents)::in, instmap::in, proc_info::in,
 	module_info::in, layout_label_info::out) is det.
 
 	% Generate the layout information we need to include in a closure.
-:- pred continuation_info__generate_closure_layout(module_info::in,
+    %
+:- pred generate_closure_layout(module_info::in,
 	pred_id::in, proc_id::in, closure_layout_info::out) is det.
 
 	% For each type variable in the given list, find out where the
 	% typeinfo var for that type variable is.
-:- pred continuation_info__find_typeinfos_for_tvars(list(tvar)::in,
+    %
+:- pred find_typeinfos_for_tvars(list(tvar)::in,
 	map(prog_var, set(lval))::in, proc_info::in,
 	map(tvar, set(layout_locn))::out) is det.
 
-:- pred continuation_info__generate_table_arg_type_info(proc_info::in,
+:- pred generate_table_arg_type_info(proc_info::in,
 	assoc_list(prog_var, int)::in, table_arg_infos::out) is det.
 
 %-----------------------------------------------------------------------------%
@@ -361,95 +362,84 @@
 :- import_module hlds__hlds_llds.
 :- import_module libs__options.
 :- import_module ll_backend__code_util.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_type.
 
 :- import_module int.
 :- import_module require.
 :- import_module string.
+:- import_module svmap.
+:- import_module svset.
 :- import_module term.
 :- import_module varset.
 
 %-----------------------------------------------------------------------------%
 
-	% Exported predicates.
-
-continuation_info__maybe_process_llds([], _, !GlobalData).
-continuation_info__maybe_process_llds([Proc | Procs], ModuleInfo,
-		!GlobalData) :-
+maybe_process_llds([], _, !GlobalData).
+maybe_process_llds([Proc | Procs], ModuleInfo, !GlobalData) :-
 	Proc = c_procedure(_, _, PredProcId, Instrs, _, _, _),
-	continuation_info__maybe_process_proc_llds(Instrs, PredProcId,
-		ModuleInfo, !GlobalData),
-	continuation_info__maybe_process_llds(Procs, ModuleInfo, !GlobalData).
+    maybe_process_proc_llds(Instrs, PredProcId, ModuleInfo, !GlobalData),
+    maybe_process_llds(Procs, ModuleInfo, !GlobalData).
 
-continuation_info__maybe_process_proc_llds(Instructions, PredProcId,
-		ModuleInfo, !ContInfo) :-
+maybe_process_proc_llds(Instructions, PredProcId, ModuleInfo, !ContInfo) :-
 	PredProcId = proc(PredId, _),
 	module_info_pred_info(ModuleInfo, PredId, PredInfo),
 	module_info_get_globals(ModuleInfo, Globals),
-	continuation_info__basic_stack_layout_for_proc(PredInfo, Globals,
-		Layout, _),
+    basic_stack_layout_for_proc(PredInfo, Globals, Layout, _),
 	(
 		Layout = yes,
 		globals__want_return_var_layouts(Globals, WantReturnLayout),
-		continuation_info__process_proc_llds(PredProcId, Instructions,
-			WantReturnLayout, !ContInfo)
+        process_proc_llds(PredProcId, Instructions, WantReturnLayout,
+            !ContInfo)
 	;
 		Layout = no
 	).
 
 :- type call_info
 	--->	call_info(
-			label,		% the return label
-			code_addr,	% the target of the call
-			list(liveinfo),	% what is live on return
-			term__context,	% the position of the call in source
-			goal_path	% the position of the call in the body;
-					% meaningful only if tracing is enabled
+                label,          % The return label.
+                code_addr,      % The target of the call.
+                list(liveinfo), % What is live on return.
+                term__context,  % The position of the call in source.
+                goal_path       % The position of the call in the body;
+                                % meaningful only if tracing is enabled.
 		).
 
-	%
 	% Process the list of instructions for this proc, adding
 	% all internal label information to global_data.
 	%
-:- pred continuation_info__process_proc_llds(pred_proc_id::in,
-	list(instruction)::in, bool::in,
+:- pred process_proc_llds(pred_proc_id::in, list(instruction)::in, bool::in,
 	global_data::in, global_data::out) is det.
 
-continuation_info__process_proc_llds(PredProcId, Instructions,
-		WantReturnInfo, !GlobalData) :-
-
+process_proc_llds(PredProcId, Instructions, WantReturnInfo, !GlobalData) :-
 		% Get all the continuation info from the call instructions.
 	global_data_get_proc_layout(!.GlobalData, PredProcId, ProcLayoutInfo0),
 	Internals0 = ProcLayoutInfo0^internal_map,
 	GetCallInfo = (pred(Instr::in, Call::out) is semidet :-
 		Instr = call(Target, label(ReturnLabel), LiveInfo, Context,
 			GoalPath, _) - _Comment,
-		Call = call_info(ReturnLabel, Target, LiveInfo, Context,
-			GoalPath)
+        Call = call_info(ReturnLabel, Target, LiveInfo, Context, GoalPath)
 	),
 	list__filter_map(GetCallInfo, Instructions, Calls),
 
 		% Process the continuation label info.
-	list__foldl(continuation_info__process_continuation(WantReturnInfo),
-		Calls, Internals0, Internals),
+    list__foldl(process_continuation(WantReturnInfo), Calls,
+        Internals0, Internals),
 
 	ProcLayoutInfo = ProcLayoutInfo0^internal_map := Internals,
-	global_data_update_proc_layout(PredProcId, ProcLayoutInfo,
-		!GlobalData).
+    global_data_update_proc_layout(PredProcId, ProcLayoutInfo, !GlobalData).
 
 %-----------------------------------------------------------------------------%
 
-	%
 	% Collect the liveness information from a single return label
 	% and add it to the internals.
 	%
-:- pred continuation_info__process_continuation(bool::in, call_info::in,
+:- pred process_continuation(bool::in, call_info::in,
 	proc_label_layout_info::in, proc_label_layout_info::out) is det.
 
-continuation_info__process_continuation(WantReturnInfo, CallInfo,
-		!Internals) :-
-	CallInfo = call_info(ReturnLabel, Target, LiveInfoList,
-		Context, MaybeGoalPath),
+process_continuation(WantReturnInfo, CallInfo, !Internals) :-
+    CallInfo = call_info(ReturnLabel, Target, LiveInfoList, Context,
+        MaybeGoalPath),
 	% We could check not only that the return label is an internal label,
 	% but also that it belongs to the current procedure, but this would be
 	% serious paranoia.
@@ -457,7 +447,7 @@
 		ReturnLabel = internal(ReturnLabelNum, _)
 	;
 		ReturnLabel = entry(_, _),
-		error("continuation_info__process_continuation: bad return")
+        error("process_continuation: bad return")
 	),
 	( map__search(!.Internals, ReturnLabelNum, Internal0) ->
 		Internal0 = internal_layout_info(Port0, Resume0, Return0)
@@ -466,49 +456,44 @@
 		Resume0 = no,
 		Return0 = no
 	),
-	( WantReturnInfo = yes ->
-		continuation_info__convert_return_data(LiveInfoList,
-			VarInfoSet, TypeInfoMap),
+    (
+        WantReturnInfo = yes,
+        convert_return_data(LiveInfoList, VarInfoSet, TypeInfoMap),
 		(
 			Return0 = no,
 			Layout = layout_label_info(VarInfoSet, TypeInfoMap),
 			ReturnInfo = return_layout_info(
-				[Target - (Context - MaybeGoalPath)],
-				Layout),
+                [Target - (Context - MaybeGoalPath)], Layout),
 			Return = yes(ReturnInfo)
 		;
-				% If a var is known to be dead
-				% on return from one call, it
-				% cannot be accessed on returning
-				% from the other calls that reach
-				% the same return address either.
+            % If a var is known to be dead on return from one call, it cannot
+            % be accessed on returning from the other calls that reach the same
+            % return address either.
 			Return0 = yes(ReturnInfo0),
-			ReturnInfo0 = return_layout_info(TargetsContexts0,
-				Layout0),
+            ReturnInfo0 = return_layout_info(TargetsContexts0, Layout0),
 			Layout0 = layout_label_info(LV0, TV0),
 			set__intersect(LV0, VarInfoSet, LV),
 			map__intersect(set__intersect, TV0, TypeInfoMap, TV),
 			Layout = layout_label_info(LV, TV),
 			TargetContexts = [Target - (Context - MaybeGoalPath)
 				| TargetsContexts0],
-			ReturnInfo = return_layout_info(TargetContexts,
-				Layout),
+            ReturnInfo = return_layout_info(TargetContexts, Layout),
 			Return = yes(ReturnInfo)
 		)
 	;
+        WantReturnInfo = no,
 		Return = Return0
 	),
 	Internal = internal_layout_info(Port0, Resume0, Return),
 	map__set(!.Internals, ReturnLabelNum, Internal, !:Internals).
 
-:- pred continuation_info__convert_return_data(list(liveinfo)::in,
+:- pred convert_return_data(list(liveinfo)::in,
 	set(layout_var_info)::out, map(tvar, set(layout_locn))::out) is det.
 
-continuation_info__convert_return_data(LiveInfos, VarInfoSet, TypeInfoMap) :-
+convert_return_data(LiveInfos, VarInfoSet, TypeInfoMap) :-
 	GetVarInfo = (pred(LiveLval::in, VarInfo::out) is det :-
 		LiveLval = live_lvalue(Lval, LiveValueType, _),
-		VarInfo = layout_var_info(Lval, LiveValueType,
-			"convert_return_data")
+        VarInfo = layout_var_info(Lval, LiveValueType, "convert_return_data")
 	),
 	list__map(GetVarInfo, LiveInfos, VarInfoList),
 	GetTypeInfo = (pred(LiveLval::in, LiveTypeInfoMap::out) is det :-
@@ -521,12 +506,11 @@
 		), TypeInfoMapList, Empty, TypeInfoMap),
 	set__list_to_set(VarInfoList, VarInfoSet).
 
-:- pred continuation_info__filter_named_vars(list(liveinfo)::in,
-	list(liveinfo)::out) is det.
+:- pred filter_named_vars(list(liveinfo)::in, list(liveinfo)::out) is det.
 
-continuation_info__filter_named_vars([], []).
-continuation_info__filter_named_vars([LiveInfo | LiveInfos], Filtered) :-
-	continuation_info__filter_named_vars(LiveInfos, Filtered1),
+filter_named_vars([], []).
+filter_named_vars([LiveInfo | LiveInfos], Filtered) :-
+    filter_named_vars(LiveInfos, Filtered1),
 	(
 		LiveInfo = live_lvalue(_, LiveType, _),
 		LiveType = var(_, Name, _, _),
@@ -539,12 +523,11 @@
 
 %-----------------------------------------------------------------------------%
 
-continuation_info__basic_stack_layout_for_proc(PredInfo, Globals,
-		BasicLayout, ForceProcIdLayout) :-
+basic_stack_layout_for_proc(PredInfo, Globals, BasicLayout,
+        ForceProcIdLayout) :-
 	(
-		globals__lookup_bool_option(Globals, stack_trace_higher_order,
-			yes),
-		continuation_info__some_arg_is_higher_order(PredInfo)
+        globals__lookup_bool_option(Globals, stack_trace_higher_order, yes),
+        some_arg_is_higher_order(PredInfo)
 	->
 		BasicLayout = yes,
 		ForceProcIdLayout = yes
@@ -558,38 +541,36 @@
 		ForceProcIdLayout = no
 	).
 
-:- pred continuation_info__some_arg_is_higher_order(pred_info::in) is semidet.
+:- pred some_arg_is_higher_order(pred_info::in) is semidet.
 
-continuation_info__some_arg_is_higher_order(PredInfo) :-
+some_arg_is_higher_order(PredInfo) :-
 	pred_info_arg_types(PredInfo, ArgTypes),
-	some([Type], (
+    some [Type] (
 		list__member(Type, ArgTypes),
 		type_is_higher_order(Type, _, _, _, _)
-	)).
+    ).
 
 %-----------------------------------------------------------------------------%
 
-continuation_info__generate_return_live_lvalues(OutputArgLocs, ReturnInstMap,
-		Vars, VarLocs, Temps, ProcInfo, ModuleInfo, Globals,
-		OkToDeleteAny, LiveLvalues) :-
+generate_return_live_lvalues(OutputArgLocs, ReturnInstMap, Vars, VarLocs,
+        Temps, ProcInfo, ModuleInfo, Globals, OkToDeleteAny, LiveLvalues) :-
 	globals__want_return_var_layouts(Globals, WantReturnVarLayout),
 	proc_info_stack_slots(ProcInfo, StackSlots),
-	continuation_info__find_return_var_lvals(Vars, StackSlots,
-		OkToDeleteAny, OutputArgLocs, VarLvals),
-	continuation_info__generate_var_live_lvalues(VarLvals, ReturnInstMap,
-		VarLocs, ProcInfo, ModuleInfo,
-		WantReturnVarLayout, VarLiveLvalues),
-	continuation_info__generate_temp_live_lvalues(Temps, TempLiveLvalues),
+    find_return_var_lvals(Vars, StackSlots, OkToDeleteAny, OutputArgLocs,
+        VarLvals),
+    generate_var_live_lvalues(VarLvals, ReturnInstMap, VarLocs, ProcInfo,
+        ModuleInfo, WantReturnVarLayout, VarLiveLvalues),
+    generate_temp_live_lvalues(Temps, TempLiveLvalues),
 	list__append(VarLiveLvalues, TempLiveLvalues, LiveLvalues).
 
-:- pred continuation_info__find_return_var_lvals(list(prog_var)::in,
+:- pred find_return_var_lvals(list(prog_var)::in,
 	stack_slots::in, bool::in, assoc_list(prog_var, arg_loc)::in,
 	assoc_list(prog_var, lval)::out) is det.
 
-continuation_info__find_return_var_lvals([], _, _, _, []).
-continuation_info__find_return_var_lvals([Var | Vars], StackSlots,
-		OkToDeleteAny, OutputArgLocs, VarLvals) :-
-	continuation_info__find_return_var_lvals(Vars, StackSlots,
+find_return_var_lvals([], _, _, _, []).
+find_return_var_lvals([Var | Vars], StackSlots, OkToDeleteAny, OutputArgLocs,
+        VarLvals) :-
+    find_return_var_lvals(Vars, StackSlots,
 		OkToDeleteAny, OutputArgLocs, TailVarLvals),
 	( assoc_list__search(OutputArgLocs, Var, ArgLoc) ->
 		% On return, output arguments are in their registers.
@@ -601,96 +582,91 @@
 	; OkToDeleteAny = yes ->
 		VarLvals = TailVarLvals
 	;
-		error("continuation_info__find_return_var_lvals: no slot")
+        unexpected(this_file, "find_return_var_lvals: no slot")
 	).
 
-:- pred continuation_info__generate_temp_live_lvalues(
-	assoc_list(lval, slot_contents)::in, list(liveinfo)::out) is det.
+:- pred generate_temp_live_lvalues(assoc_list(lval, slot_contents)::in,
+    list(liveinfo)::out) is det.
 
-continuation_info__generate_temp_live_lvalues([], []).
-continuation_info__generate_temp_live_lvalues([Temp | Temps], [Live | Lives]) :-
+generate_temp_live_lvalues([], []).
+generate_temp_live_lvalues([Temp | Temps], [Live | Lives]) :-
 	Temp = Slot - Contents,
-	continuation_info__live_value_type(Contents, LiveLvalueType),
+    live_value_type(Contents, LiveLvalueType),
 	map__init(Empty),
 	Live = live_lvalue(direct(Slot), LiveLvalueType, Empty),
-	continuation_info__generate_temp_live_lvalues(Temps, Lives).
+    generate_temp_live_lvalues(Temps, Lives).
 
-:- pred continuation_info__generate_var_live_lvalues(
-	assoc_list(prog_var, lval)::in, instmap::in,
+:- pred generate_var_live_lvalues(assoc_list(prog_var, lval)::in, instmap::in,
 	map(prog_var, set(lval))::in, proc_info::in, module_info::in,
 	bool::in, list(liveinfo)::out) is det.
 
-continuation_info__generate_var_live_lvalues([], _, _, _, _, _, []).
-continuation_info__generate_var_live_lvalues([Var - Lval | VarLvals], InstMap,
-		VarLocs, ProcInfo, ModuleInfo, WantReturnVarLayout,
-		[Live | Lives]) :-
-	( WantReturnVarLayout = yes ->
-		continuation_info__generate_layout_for_var(Var, InstMap,
-			ProcInfo, ModuleInfo, LiveValueType, TypeVars),
-		continuation_info__find_typeinfos_for_tvars(TypeVars,
-			VarLocs, ProcInfo, TypeParams),
+generate_var_live_lvalues([], _, _, _, _, _, []).
+generate_var_live_lvalues([Var - Lval | VarLvals], InstMap, VarLocs, ProcInfo,
+        ModuleInfo, WantReturnVarLayout, [Live | Lives]) :-
+    (
+        WantReturnVarLayout = yes,
+        generate_layout_for_var(Var, InstMap, ProcInfo, ModuleInfo,
+            LiveValueType, TypeVars),
+        find_typeinfos_for_tvars(TypeVars, VarLocs, ProcInfo, TypeParams),
 		Live = live_lvalue(direct(Lval), LiveValueType, TypeParams)
 	;
+        WantReturnVarLayout = no,
 		map__init(Empty),
 		Live = live_lvalue(direct(Lval), unwanted, Empty)
 	),
-	continuation_info__generate_var_live_lvalues(VarLvals, InstMap,
-		VarLocs, ProcInfo, ModuleInfo, WantReturnVarLayout, Lives).
+    generate_var_live_lvalues(VarLvals, InstMap, VarLocs, ProcInfo,
+        ModuleInfo, WantReturnVarLayout, Lives).
 
 %---------------------------------------------------------------------------%
 
-continuation_info__generate_resume_layout(ResumeMap, Temps, InstMap,
-		ProcInfo, ModuleInfo, Layout) :-
+generate_resume_layout(ResumeMap, Temps, InstMap, ProcInfo, ModuleInfo,
+        Layout) :-
 	map__to_assoc_list(ResumeMap, ResumeList),
 	set__init(TVars0),
 	proc_info_vartypes(ProcInfo, VarTypes),
-	continuation_info__generate_resume_layout_for_vars(ResumeList,
-		InstMap, VarTypes, ProcInfo, ModuleInfo, [], VarInfos,
-		TVars0, TVars),
+    generate_resume_layout_for_vars(ResumeList, InstMap, VarTypes, ProcInfo,
+        ModuleInfo, [], VarInfos, TVars0, TVars),
 	set__list_to_set(VarInfos, VarInfoSet),
 	set__to_sorted_list(TVars, TVarList),
-	continuation_info__find_typeinfos_for_tvars(TVarList, ResumeMap,
-		ProcInfo, TVarInfoMap),
-	continuation_info__generate_temp_var_infos(Temps, TempInfos),
+    find_typeinfos_for_tvars(TVarList, ResumeMap, ProcInfo, TVarInfoMap),
+    generate_temp_var_infos(Temps, TempInfos),
 	set__list_to_set(TempInfos, TempInfoSet),
 	set__union(VarInfoSet, TempInfoSet, AllInfoSet),
 	Layout = layout_label_info(AllInfoSet, TVarInfoMap).
 
-:- pred continuation_info__generate_resume_layout_for_vars(
-	assoc_list(prog_var, set(lval))::in, instmap::in, vartypes::in,
-	proc_info::in, module_info::in,
+:- pred generate_resume_layout_for_vars(assoc_list(prog_var, set(lval))::in,
+    instmap::in, vartypes::in, proc_info::in, module_info::in,
 	list(layout_var_info)::in, list(layout_var_info)::out,
 	set(tvar)::in, set(tvar)::out) is det.
 
-continuation_info__generate_resume_layout_for_vars([], _, _, _, _,
-		!VarInfos, !TVars).
-continuation_info__generate_resume_layout_for_vars([Var - LvalSet | VarLvals],
-		InstMap, VarTypes, ProcInfo, ModuleInfo, !VarInfos, !TVars) :-
+generate_resume_layout_for_vars([], _, _, _, _, !VarInfos, !TVars).
+generate_resume_layout_for_vars([Var - LvalSet | VarLvals], InstMap,
+        VarTypes, ProcInfo, ModuleInfo, !VarInfos, !TVars) :-
 	(
 		map__lookup(VarTypes, Var, Type),
 		is_dummy_argument_type(ModuleInfo, Type)
 	->
 		true
 	;
-		continuation_info__generate_resume_layout_for_var(Var, LvalSet,
-			InstMap, ProcInfo, ModuleInfo, VarInfo, TypeVars),
+        generate_resume_layout_for_var(Var, LvalSet, InstMap, ProcInfo,
+            ModuleInfo, VarInfo, TypeVars),
 		set__insert_list(!.TVars, TypeVars, !:TVars),
 		!:VarInfos = [VarInfo | !.VarInfos]
 	),
-	continuation_info__generate_resume_layout_for_vars(VarLvals,
-		InstMap, VarTypes, ProcInfo, ModuleInfo, !VarInfos, !TVars).
+    generate_resume_layout_for_vars(VarLvals, InstMap, VarTypes, ProcInfo,
+        ModuleInfo, !VarInfos, !TVars).
 
-:- pred continuation_info__generate_resume_layout_for_var(prog_var::in,
-	set(lval)::in, instmap::in, proc_info::in, module_info::in,
+:- pred generate_resume_layout_for_var(prog_var::in, set(lval)::in,
+    instmap::in, proc_info::in, module_info::in,
 	layout_var_info::out, list(tvar)::out) is det.
 
-continuation_info__generate_resume_layout_for_var(Var, LvalSet, InstMap,
-		ProcInfo, ModuleInfo, VarInfo, TypeVars) :-
+generate_resume_layout_for_var(Var, LvalSet, InstMap, ProcInfo, ModuleInfo,
+        VarInfo, TypeVars) :-
 	set__to_sorted_list(LvalSet, LvalList),
 	( LvalList = [LvalPrime] ->
 		Lval = LvalPrime
 	;
-		error("var has more than one lval in stack resume map")
+        unexpected(this_file, "var has more than one lval in stack resume map")
 	),
 	( Lval = stackvar(N) ->
 		require(N > 0, "generate_resume_layout_for_var: bad stackvar")
@@ -699,31 +675,29 @@
 	;
 		true
 	),
-	continuation_info__generate_layout_for_var(Var, InstMap, ProcInfo,
-		ModuleInfo, LiveValueType, TypeVars),
+    generate_layout_for_var(Var, InstMap, ProcInfo, ModuleInfo, LiveValueType,
+        TypeVars),
 	VarInfo = layout_var_info(direct(Lval), LiveValueType,
 		"generate_result_layout_for_var").
 
-:- pred continuation_info__generate_temp_var_infos(
-	assoc_list(lval, slot_contents)::in, list(layout_var_info)::out)
-	is det.
+:- pred generate_temp_var_infos(assoc_list(lval, slot_contents)::in,
+    list(layout_var_info)::out) is det.
 
-continuation_info__generate_temp_var_infos([], []).
-continuation_info__generate_temp_var_infos([Temp | Temps], [Live | Lives]) :-
+generate_temp_var_infos([], []).
+generate_temp_var_infos([Temp | Temps], [Live | Lives]) :-
 	Temp = Slot - Contents,
-	continuation_info__live_value_type(Contents, LiveLvalueType),
+    live_value_type(Contents, LiveLvalueType),
 	Live = layout_var_info(direct(Slot), LiveLvalueType,
 		"generate_temp_var_infos"),
-	continuation_info__generate_temp_var_infos(Temps, Lives).
+    generate_temp_var_infos(Temps, Lives).
 
 %---------------------------------------------------------------------------%
 
-:- pred continuation_info__generate_layout_for_var(prog_var::in, instmap::in,
-	proc_info::in, module_info::in, live_value_type::out, list(tvar)::out)
-	is det.
+:- pred generate_layout_for_var(prog_var::in, instmap::in, proc_info::in,
+    module_info::in, live_value_type::out, list(tvar)::out) is det.
 
-continuation_info__generate_layout_for_var(Var, InstMap, ProcInfo, ModuleInfo,
-		LiveValueType, TypeVars) :-
+generate_layout_for_var(Var, InstMap, ProcInfo, ModuleInfo, LiveValueType,
+        TypeVars) :-
 	proc_info_varset(ProcInfo, VarSet),
 	proc_info_vartypes(ProcInfo, VarTypes),
 	( varset__search_name(VarSet, Var, GivenName) ->
@@ -743,10 +717,8 @@
 
 %---------------------------------------------------------------------------%
 
-continuation_info__generate_closure_layout(ModuleInfo, PredId, ProcId,
-		ClosureLayout) :-
-	module_info_pred_proc_info(ModuleInfo, PredId, ProcId,
-		PredInfo, ProcInfo),
+generate_closure_layout(ModuleInfo, PredId, ProcId, ClosureLayout) :-
+    module_info_pred_proc_info(ModuleInfo, PredId, ProcId, PredInfo, ProcInfo),
 	proc_info_headvars(ProcInfo, HeadVars),
 	proc_info_arg_info(ProcInfo, ArgInfos),
 	pred_info_arg_types(PredInfo, ArgTypes),
@@ -754,58 +726,51 @@
 	map__init(VarLocs0),
 	set__init(TypeVars0),
 	(
-		continuation_info__build_closure_info(HeadVars, ArgTypes,
-			ArgInfos, ArgLayouts, InstMap, VarLocs0, VarLocs,
-			TypeVars0, TypeVars)
+        build_closure_info(HeadVars, ArgTypes, ArgInfos, ArgLayouts, InstMap,
+            VarLocs0, VarLocs, TypeVars0, TypeVars)
 	->
 		set__to_sorted_list(TypeVars, TypeVarsList),
-		continuation_info__find_typeinfos_for_tvars(TypeVarsList,
-			VarLocs, ProcInfo, TypeInfoDataMap),
-		ClosureLayout = closure_layout_info(ArgLayouts,
-			TypeInfoDataMap)
+        find_typeinfos_for_tvars(TypeVarsList, VarLocs, ProcInfo,
+            TypeInfoDataMap),
+        ClosureLayout = closure_layout_info(ArgLayouts, TypeInfoDataMap)
 	;
-		error("proc headvars and pred argtypes disagree on arity")
+        unexpected(this_file,
+            "proc headvars and pred argtypes disagree on arity")
 	).
 
-:- pred continuation_info__build_closure_info(list(prog_var)::in,
+:- pred build_closure_info(list(prog_var)::in,
 	list(type)::in, list(arg_info)::in,  list(closure_arg_info)::out,
 	instmap::in, map(prog_var, set(lval))::in,
-	map(prog_var, set(lval))::out, set(tvar)::in, set(tvar)::out)
-	is semidet.
+    map(prog_var, set(lval))::out, set(tvar)::in, set(tvar)::out) is semidet.
 
-continuation_info__build_closure_info([], [], [], [], _, VarLocs, VarLocs,
-		TypeVars, TypeVars).
-continuation_info__build_closure_info([Var | Vars], [Type | Types],
+build_closure_info([], [], [], [], _, !VarLocs, !TypeVars).
+build_closure_info([Var | Vars], [Type | Types],
 		[ArgInfo | ArgInfos], [Layout | Layouts], InstMap,
-		VarLocs0, VarLocs, TypeVars0, TypeVars) :-
+        !VarLocs, !TypeVars) :-
 	ArgInfo = arg_info(ArgLoc, _ArgMode),
 	instmap__lookup_var(InstMap, Var, Inst),
 	Layout = closure_arg_info(Type, Inst),
 	set__singleton_set(Locations, reg(r, ArgLoc)),
-	map__det_insert(VarLocs0, Var, Locations, VarLocs1),
+    svmap__det_insert(Var, Locations, !VarLocs),
 	prog_type__vars(Type, VarTypeVars),
-	set__insert_list(TypeVars0, VarTypeVars, TypeVars1),
-	continuation_info__build_closure_info(Vars, Types, ArgInfos, Layouts,
-		InstMap, VarLocs1, VarLocs, TypeVars1, TypeVars).
+    svset__insert_list(VarTypeVars, !TypeVars),
+    build_closure_info(Vars, Types, ArgInfos, Layouts, InstMap,
+        !VarLocs, !TypeVars).
 
 %---------------------------------------------------------------------------%
 
-continuation_info__find_typeinfos_for_tvars(TypeVars, VarLocs, ProcInfo,
-		TypeInfoDataMap) :-
+find_typeinfos_for_tvars(TypeVars, VarLocs, ProcInfo, TypeInfoDataMap) :-
 	proc_info_varset(ProcInfo, VarSet),
 	proc_info_rtti_varmaps(ProcInfo, RttiVarMaps),
 	list__map(rtti_lookup_type_info_locn(RttiVarMaps), TypeVars,
 		TypeInfoLocns),
 	FindLocn = (pred(TypeInfoLocn::in, Locns::out) is det :-
 		type_info_locn_var(TypeInfoLocn, TypeInfoVar),
-		(
-			map__search(VarLocs, TypeInfoVar, TypeInfoLvalSet)
-		->
+        ( map__search(VarLocs, TypeInfoVar, TypeInfoLvalSet) ->
 			ConvertLval = (pred(Locn::out) is nondet :-
 				set__member(Lval, TypeInfoLvalSet),
 				(
-					TypeInfoLocn = typeclass_info(_,
-						FieldNum),
+                    TypeInfoLocn = typeclass_info(_, FieldNum),
 					Locn = indirect(Lval, FieldNum)
 				;
 					TypeInfoLocn = type_info(_),
@@ -814,55 +779,50 @@
 			),
 			solutions_set(ConvertLval, Locns)
 		;
-			varset__lookup_name(VarSet, TypeInfoVar,
-				VarString),
+            varset__lookup_name(VarSet, TypeInfoVar, VarString),
 			string__format("%s: %s %s",
-			    [s("continuation_info__find_typeinfos_for_tvars"),
+                [s("find_typeinfos_for_tvars"),
 				s("can't find rval for type_info var"),
 				s(VarString)], ErrStr),
 			error(ErrStr)
 		)
 	),
 	list__map(FindLocn, TypeInfoLocns, TypeInfoVarLocns),
-	map__from_corresponding_lists(TypeVars, TypeInfoVarLocns,
-		TypeInfoDataMap).
+    map__from_corresponding_lists(TypeVars, TypeInfoVarLocns, TypeInfoDataMap).
 
 %---------------------------------------------------------------------------%
 
-continuation_info__generate_table_arg_type_info(ProcInfo, NumberedVars,
-		TableArgInfos) :-
+generate_table_arg_type_info(ProcInfo, NumberedVars, TableArgInfos) :-
 	proc_info_vartypes(ProcInfo, VarTypes),
 	set__init(TypeVars0),
-	continuation_info__build_table_arg_info(VarTypes,
-		NumberedVars, ArgLayouts, TypeVars0, TypeVars),
+    build_table_arg_info(VarTypes, NumberedVars, ArgLayouts,
+        TypeVars0, TypeVars),
 	set__to_sorted_list(TypeVars, TypeVarsList),
-	continuation_info__find_typeinfos_for_tvars_table(TypeVarsList,
-		NumberedVars, ProcInfo, TypeInfoDataMap),
+    find_typeinfos_for_tvars_table(TypeVarsList, NumberedVars, ProcInfo,
+        TypeInfoDataMap),
 	TableArgInfos = table_arg_infos(ArgLayouts, TypeInfoDataMap).
 
-:- pred continuation_info__build_table_arg_info(vartypes::in,
+:- pred build_table_arg_info(vartypes::in,
 	assoc_list(prog_var, int)::in, list(table_arg_info)::out,
 	set(tvar)::in, set(tvar)::out) is det.
 
-continuation_info__build_table_arg_info(_, [], [], TypeVars, TypeVars).
-continuation_info__build_table_arg_info(VarTypes,
-		[Var - SlotNum | NumberedVars], [ArgLayout | ArgLayouts],
-		TypeVars0, TypeVars) :-
+build_table_arg_info(_, [], [], !TypeVars).
+build_table_arg_info(VarTypes, [Var - SlotNum | NumberedVars],
+        [ArgLayout | ArgLayouts], !TypeVars) :-
 	map__lookup(VarTypes, Var, Type),
 	ArgLayout = table_arg_info(Var, SlotNum, Type),
 	prog_type__vars(Type, VarTypeVars),
-	set__insert_list(TypeVars0, VarTypeVars, TypeVars1),
-	continuation_info__build_table_arg_info(VarTypes,
-		NumberedVars, ArgLayouts, TypeVars1, TypeVars).
+    svset__insert_list(VarTypeVars, !TypeVars),
+    build_table_arg_info(VarTypes, NumberedVars, ArgLayouts, !TypeVars).
 
 %---------------------------------------------------------------------------%
 
-:- pred continuation_info__find_typeinfos_for_tvars_table(
-	list(tvar)::in, assoc_list(prog_var, int)::in, proc_info::in,
+:- pred find_typeinfos_for_tvars_table(list(tvar)::in,
+    assoc_list(prog_var, int)::in, proc_info::in,
 	map(tvar, table_locn)::out) is det.
 
-continuation_info__find_typeinfos_for_tvars_table(TypeVars,
-		NumberedVars, ProcInfo, TypeInfoDataMap) :-
+find_typeinfos_for_tvars_table(TypeVars, NumberedVars, ProcInfo,
+        TypeInfoDataMap) :-
 	proc_info_varset(ProcInfo, VarSet),
 	proc_info_rtti_varmaps(ProcInfo, RttiVarMaps),
 	list__map(rtti_lookup_type_info_locn(RttiVarMaps), TypeVars,
@@ -870,15 +830,12 @@
 	FindLocn = (pred(TypeInfoLocn::in, Locn::out) is det :-
 		(
 			(
-				TypeInfoLocn = typeclass_info(TypeInfoVar,
-					FieldNum),
-				assoc_list__search(NumberedVars, TypeInfoVar,
-					Slot),
+                TypeInfoLocn = typeclass_info(TypeInfoVar, FieldNum),
+                assoc_list__search(NumberedVars, TypeInfoVar, Slot),
 				LocnPrime = indirect(Slot, FieldNum)
 			;
 				TypeInfoLocn = type_info(TypeInfoVar),
-				assoc_list__search(NumberedVars, TypeInfoVar,
-					Slot),
+                assoc_list__search(NumberedVars, TypeInfoVar, Slot),
 				LocnPrime = direct(Slot)
 			)
 		->
@@ -887,43 +844,46 @@
 			type_info_locn_var(TypeInfoLocn, TypeInfoVar),
 			varset__lookup_name(VarSet, TypeInfoVar, VarString),
 			string__format("%s: %s %s",
-				[s("continuation_info__find_typeinfos_for_tvars_table"),
-				s("can't find slot for type_info var"),
-				s(VarString)], ErrStr),
-			error(ErrStr)
+                [s("find_typeinfos_for_tvars_table"),
+                s("can't find slot for type_info var"), s(VarString)], ErrStr),
+            unexpected(this_file, ErrStr)
 		)
 	),
 	list__map(FindLocn, TypeInfoLocns, TypeInfoVarLocns),
-	map__from_corresponding_lists(TypeVars, TypeInfoVarLocns,
-		TypeInfoDataMap).
+    map__from_corresponding_lists(TypeVars, TypeInfoVarLocns, TypeInfoDataMap).
+
+%-----------------------------------------------------------------------------%
+
+:- pred live_value_type(slot_contents::in, live_value_type::out) is det.
+
+live_value_type(lval(succip), succip).
+live_value_type(lval(hp), hp).
+live_value_type(lval(maxfr), maxfr).
+live_value_type(lval(curfr), curfr).
+live_value_type(lval(succfr(_)), unwanted).
+live_value_type(lval(prevfr(_)), unwanted).
+live_value_type(lval(redofr(_)), unwanted).
+live_value_type(lval(redoip(_)), unwanted).
+live_value_type(lval(succip(_)), unwanted).
+live_value_type(lval(sp), unwanted).
+live_value_type(lval(lvar(_)), unwanted).
+live_value_type(lval(field(_, _, _)), unwanted).
+live_value_type(lval(temp(_, _)), unwanted).
+live_value_type(lval(reg(_, _)), unwanted).
+live_value_type(lval(stackvar(_)), unwanted).
+live_value_type(lval(framevar(_)), unwanted).
+live_value_type(lval(mem_ref(_)), unwanted). % XXX
+live_value_type(ticket, unwanted).  % XXX we may need to modify this,
+                                    % if the GC is going to garbage-collect
+                                    % the trail.
+live_value_type(ticket_counter, unwanted).
+live_value_type(sync_term, unwanted).
+live_value_type(trace_data, unwanted).
 
 %-----------------------------------------------------------------------------%
 
-:- pred continuation_info__live_value_type(slot_contents::in,
-	live_value_type::out) is det.
+:- func this_file = string.
 
-continuation_info__live_value_type(lval(succip), succip).
-continuation_info__live_value_type(lval(hp), hp).
-continuation_info__live_value_type(lval(maxfr), maxfr).
-continuation_info__live_value_type(lval(curfr), curfr).
-continuation_info__live_value_type(lval(succfr(_)), unwanted).
-continuation_info__live_value_type(lval(prevfr(_)), unwanted).
-continuation_info__live_value_type(lval(redofr(_)), unwanted).
-continuation_info__live_value_type(lval(redoip(_)), unwanted).
-continuation_info__live_value_type(lval(succip(_)), unwanted).
-continuation_info__live_value_type(lval(sp), unwanted).
-continuation_info__live_value_type(lval(lvar(_)), unwanted).
-continuation_info__live_value_type(lval(field(_, _, _)), unwanted).
-continuation_info__live_value_type(lval(temp(_, _)), unwanted).
-continuation_info__live_value_type(lval(reg(_, _)), unwanted).
-continuation_info__live_value_type(lval(stackvar(_)), unwanted).
-continuation_info__live_value_type(lval(framevar(_)), unwanted).
-continuation_info__live_value_type(lval(mem_ref(_)), unwanted).	% XXX
-continuation_info__live_value_type(ticket, unwanted). % XXX we may need to
-					% modify this, if the GC is going
-					% to garbage-collect the trail.
-continuation_info__live_value_type(ticket_counter, unwanted).
-continuation_info__live_value_type(sync_term, unwanted).
-continuation_info__live_value_type(trace_data, unwanted).
+this_file = "continuation_info.m".
 
 %-----------------------------------------------------------------------------%
Index: compiler/delay_construct.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_construct.m,v
retrieving revision 1.11
diff -u -b -r1.11 delay_construct.m
--- compiler/delay_construct.m	22 Jul 2005 12:31:53 -0000	1.11
+++ compiler/delay_construct.m	12 Oct 2005 06:58:27 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -20,7 +22,7 @@
 % is that this may require storing the input arguments of the construction on
 % the stack, which may cause a slowdown bigger than the speedup available from
 % not having to construct the cell on some execution paths.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module transform_hlds__delay_construct.
@@ -45,6 +47,7 @@
 :- import_module hlds__instmap.
 :- import_module hlds__passes_aux.
 :- import_module libs__globals.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_data.
 
 :- import_module bool.
@@ -60,15 +63,13 @@
 		PredId, ProcId, ModuleInfo, !IO),
 	globals__io_get_globals(Globals, !IO),
 	module_info_pred_info(ModuleInfo, PredId, PredInfo),
-	delay_construct_proc_no_io(PredInfo, ModuleInfo, Globals,
-		!ProcInfo).
+    delay_construct_proc_no_io(PredInfo, ModuleInfo, Globals, !ProcInfo).
 
 :- pred delay_construct_proc_no_io(pred_info::in, module_info::in, globals::in,
 	proc_info::in, proc_info::out) is det.
 
 delay_construct_proc_no_io(PredInfo, ModuleInfo, Globals, !ProcInfo) :-
-	body_should_use_typeinfo_liveness(PredInfo, Globals,
-		BodyTypeinfoLiveness),
+    body_should_use_typeinfo_liveness(PredInfo, Globals, BodyTypeinfoLiveness),
 	proc_info_vartypes(!.ProcInfo, VarTypes),
 	proc_info_rtti_varmaps(!.ProcInfo, RttiVarMaps),
 	proc_info_get_initial_instmap(!.ProcInfo, ModuleInfo, InstMap0),
@@ -97,28 +98,25 @@
 		goal_info_get_determinism(GoalInfo0, Detism),
 		determinism_components(Detism, CanFail, MaxSoln),
 		(
-			% If the conjunction cannot fail, then its conjuncts
-			% cannot fail either, so we have no hope of pushing a
-			% construction past a failing goal.
+            % If the conjunction cannot fail, then its conjuncts cannot fail
+            % either, so we have no hope of pushing a construction past a
+            % failing goal.
 			%
-			% If the conjuntion contains goals that can succeed
-			% more than once, which is possible if MaxSoln is
-			% at_most_many or at_most_many_cc, then moving a
-			% construction to the right may increase the number of
-			% times the construction is executed. We are therefore
-			% careful to make sure delay_construct_in_conj doesn't
-			% move constructions across goals that succeed more
-			% than once.
+            % If the conjuntion contains goals that can succeed more than once,
+            % which is possible if MaxSoln is at_most_many or at_most_many_cc,
+            % then moving a construction to the right may increase the number
+            % of times the construction is executed. We are therefore careful
+            % to make sure delay_construct_in_conj doesn't move constructions
+            % across goals that succeed more than once.
 			%
-			% If the conjunction cannot succeed, i.e. MaxSoln is
-			% at_most_zero, there is no point in trying to speed it
-			% up.
+            % If the conjunction cannot succeed, i.e. MaxSoln is at_most_zero,
+            % there is no point in trying to speed it up.
 
 			CanFail = can_fail,
 			MaxSoln \= at_most_zero
 		->
-			delay_construct_in_conj(Goals0, InstMap0, DelayInfo,
-				set__init, [], Goals1)
+            delay_construct_in_conj(Goals0, InstMap0, DelayInfo, set__init, [],
+                Goals1)
 		;
 			Goals1 = Goals0
 		),
@@ -144,8 +142,7 @@
 		GoalExpr0 = if_then_else(Vars, Cond0, Then0, Else0),
 		Cond0 = _ - CondInfo0,
 		goal_info_get_instmap_delta(CondInfo0, CondInstMapDelta),
-		instmap__apply_instmap_delta(InstMap0, CondInstMapDelta,
-			InstMapThen),
+        instmap__apply_instmap_delta(InstMap0, CondInstMapDelta, InstMapThen),
 		delay_construct_in_goal(Cond0, InstMap0, DelayInfo, Cond),
 		delay_construct_in_goal(Then0, InstMapThen, DelayInfo, Then),
 		delay_construct_in_goal(Else0, InstMap0, DelayInfo, Else),
@@ -168,8 +165,8 @@
 		Goal = GoalExpr0 - GoalInfo0
 	;
 		GoalExpr0 = shorthand(_),
-		% these should have been expanded out by now
-		error("delay_construct_in_goal: unexpected shorthand")
+        % These should have been expanded out by now.
+        unexpected(this_file, "delay_construct_in_goal: unexpected shorthand")
 	).
 
 %-----------------------------------------------------------------------------%
@@ -279,5 +276,11 @@
 		[case(Cons, Goal) | Cases]) :-
 	delay_construct_in_goal(Goal0, InstMap0, DelayInfo, Goal),
 	delay_construct_in_cases(Cases0, InstMap0, DelayInfo, Cases).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "delay_construct.m".
 
 %-----------------------------------------------------------------------------%
Index: compiler/delay_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_info.m,v
retrieving revision 1.22
diff -u -b -r1.22 delay_info.m
--- compiler/delay_info.m	24 Mar 2005 02:00:22 -0000	1.22
+++ compiler/delay_info.m	12 Oct 2005 07:08:49 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1994-1998, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -90,6 +92,7 @@
 
 :- import_module check_hlds__mode_errors.	% for the mode_error_info
 						% and delay_info types.
+:- import_module parse_tree__error_util.
 
 :- import_module int.
 :- import_module map.
@@ -112,23 +115,27 @@
 					% the current conjunction depth,
 					% i.e. the number of nested conjunctions
 					% which are currently active
+
 			delay_goals	:: stack(map(seq_num, delayed_goal)),
 					% DelayedGoalStack:
 					% for each nested conjunction,
 					% we store a collection of delayed goals
 					% associated with that conjunction,
 					% indexed by sequence number
+
 			delay_waiting	:: waiting_goals_table,
 					% WaitingGoalsTable:
 					% for each variable, we keep track of
 					% all the goals which are waiting on
 					% that variable
+
 			delay_pending	:: pending_goals_table,
 					% PendingGoalsTable:
 					% when a variable gets bound, we
 					% mark all the goals which are waiting
 					% on that variable as ready to be
 					% reawakened at the next opportunity
+
 			delay_seqs	:: stack(seq_num)
 					% SeqNumsStack:
 					% For each nested conjunction, the
@@ -137,20 +144,18 @@
 
 :- type waiting_goals_table == map(prog_var, waiting_goals).
 	% Used to store the collection of goals waiting on a variable.
+
 :- type waiting_goals == map(goal_num, list(prog_var)).
 	% For each goal, we store all the variables that it is waiting on.
 
 :- type pending_goals_table == map(depth_num, list(seq_num)).
 
 :- type goal_num == pair(depth_num, seq_num).
-:- type depth_num == int.		/* Eeek! Pointers! */
+:- type depth_num == int.       % Eeek! Pointers!
 :- type seq_num == int.
 
 %-----------------------------------------------------------------------------%
 
-	% Check that the invariants for the delay_info structure
-	% hold, and if not, call error/1.
-
 delay_info__check_invariant(_).
 	% for debugging purposes
 %%% delay_info__check_invariant(DelayInfo) :-
@@ -169,12 +174,12 @@
 	->
 		true
 	;
-		error("delay_info: invariant violated")
+        unexpected(this_file, "delay_info: invariant violated")
 	).
 
-	% For every variable which goals are waiting on, check the
-	% consistency of all the goals waiting on that var.
-
+    % For every variable which goals are waiting on, check the consistency
+    % of all the goals waiting on that var.
+    %
 :- pred waiting_goals_check_invariant(list(prog_var)::in,
 	waiting_goals_table::in) is semidet.
 
@@ -182,13 +187,11 @@
 waiting_goals_check_invariant([Var | Vars], WaitingGoalsTable) :-
 	map__lookup(WaitingGoalsTable, Var, WaitingGoals),
 	map__keys(WaitingGoals, GoalNums),
-	waiting_goal_check_invariant(GoalNums, WaitingGoals,
-		WaitingGoalsTable),
+    waiting_goal_check_invariant(GoalNums, WaitingGoals, WaitingGoalsTable),
 	waiting_goals_check_invariant(Vars, WaitingGoalsTable).
 
-	% Check the consistency of a list of goal_nums in the
-	% waiting_goals_table.
-
+    % Check the consistency of a list of goal_nums in the waiting_goals_table.
+    %
 :- pred waiting_goal_check_invariant(list(goal_num)::in, waiting_goals::in,
 	waiting_goals_table::in) is semidet.
 
@@ -199,14 +202,12 @@
 	set__list_to_set(Vars, VarsSet),
 	waiting_goal_vars_check_invariant(Vars, GoalNum, VarsSet,
 		WaitingGoalsTable),
-	waiting_goal_check_invariant(GoalNums, WaitingGoals,
-		WaitingGoalsTable).
-
-	% For every variable which a goal is waiting on, there should
-	% be an entry in the waiting_goals_table for that goal,
-	% and the set of vars which it is waiting on in that entry
-	% should be the same as in all its other entries.
+    waiting_goal_check_invariant(GoalNums, WaitingGoals, WaitingGoalsTable).
 
+    % For every variable which a goal is waiting on, there should be an entry
+    % in the waiting_goals_table for that goal, and the set of vars which it is
+    % waiting on in that entry should be the same as in all its other entries.
+    %
 :- pred waiting_goal_vars_check_invariant(list(prog_var)::in, goal_num::in,
 	set(prog_var)::in, waiting_goals_table::in) is semidet.
 
@@ -269,12 +270,10 @@
 %-----------------------------------------------------------------------------%
 
 	% When a conjunction flounders, we need to remove the delayed sub-goals
-	% from the waiting goals table before we delay the conjunction as a
-	% whole.
-
+    % from the waiting goals table before we delay the conjunction as a whole.
+    %
 :- pred remove_delayed_goals(list(seq_num)::in, map(seq_num, delayed_goal)::in,
-	depth_num::in, waiting_goals_table::in, waiting_goals_table::out)
-	is det.
+    depth_num::in, waiting_goals_table::in, waiting_goals_table::out) is det.
 
 remove_delayed_goals([], _, _, !WaitingGoalsTable).
 remove_delayed_goals([SeqNum | SeqNums], DelayedGoalsTable, Depth,
@@ -291,7 +290,7 @@
 
 	% We are going to delay a goal.
 	% Update the delay info structure to record the delayed goal.
-
+    %
 delay_info__delay_goal(DelayInfo0, Error, Goal, DelayInfo) :-
 	delay_info__check_invariant(DelayInfo0),
 	Error = mode_error_info(Vars, _, _, _),
@@ -320,11 +319,11 @@
 	delay_info__check_invariant(DelayInfo).
 
 	% add_waiting_vars(Vars, Goal, AllVars, WGT0, WGT):
-	% update the waiting goals table by adding indexes
-	% from each of the variables in Vars to Goal.
-	% AllVars must be the list of all the variables which the goal is
-	% waiting on.
-
+    %
+    % Update the waiting goals table by adding indexes from each of the
+    % variables in Vars to Goal. AllVars must be the list of all the variables
+    % which the goal is waiting on.
+    %
 :- pred add_waiting_vars(list(prog_var)::in, goal_num::in, list(prog_var)::in,
 	waiting_goals_table::in, waiting_goals_table::out) is det.
 
@@ -341,12 +340,12 @@
 
 %-----------------------------------------------------------------------------%
 
-	% Whenever we hit a goal which cannot succeed, we need to wake
-	% up all the delayed goals, so that we don't get mode errors in
-	% unreachable code.  We remove all the goals from the waiting
-	% goals table and add them to the pending goals table.  They
-	% will be woken up next time we get back to their conjunction.
-
+    % Whenever we hit a goal which cannot succeed, we need to wake up all
+    % the delayed goals, so that we don't get mode errors in unreachable code.
+    % We remove all the goals from the waiting goals table and add them
+    % to the pending goals table. They will be woken up next time we get back
+    % to their conjunction.
+    %
 delay_info__bind_all_vars(!DelayInfo) :-
 	map__keys(!.DelayInfo ^ delay_waiting, WaitingVars),
 	delay_info__bind_var_list(WaitingVars, !DelayInfo).
@@ -356,12 +355,11 @@
 	delay_info__bind_var(Var, !DelayInfo),
 	delay_info__bind_var_list(Vars, !DelayInfo).
 
-	% Whenever we bind a variable, we also check to see whether
-	% we need to wake up some goals.  If so, we remove those
-	% goals from the waiting goals table and add them to the pending
-	% goals table.  They will be woken up next time we get back
-	% to their conjunction.
-
+    % Whenever we bind a variable, we also check to see whether we need to wake
+    % up some goals. If so, we remove those goals from the waiting goals table
+    % and add them to the pending goals table. They will be woken up next time
+    % we get back to their conjunction.
+    %
 delay_info__bind_var(Var, !DelayInfo) :-
 	delay_info__check_invariant(!.DelayInfo),
 	!.DelayInfo = delay_info(CurrentDepth, DelayedGoalStack,
@@ -381,7 +379,7 @@
 	% Add a collection of goals, identified by depth_num and seq_num
 	% (depth of nested conjunction and sequence number within conjunction),
 	% to the collection of pending goals.
-
+    %
 :- pred add_pending_goals(list(goal_num)::in,
 	map(goal_num, list(prog_var))::in,
 	pending_goals_table::in, pending_goals_table::out,
@@ -390,30 +388,27 @@
 add_pending_goals([], _WaitingVarsTable, !PendingGoals, !WaitingGoals).
 add_pending_goals([Depth - SeqNum | Rest], WaitingVarsTable,
 		!PendingGoals, !WaitingGoals) :-
-
-		% remove any other indexes to the goal from the waiting
-		% goals table
+    % Remove any other indexes to the goal from the waiting goals table.
 	GoalNum = Depth - SeqNum,
 	map__lookup(WaitingVarsTable, GoalNum, WaitingVars),
 	delete_waiting_vars(WaitingVars, GoalNum, !WaitingGoals),
 
-		% add the goal to the pending goals table
+    % Add the goal to the pending goals table.
 	( map__search(!.PendingGoals, Depth, PendingSeqNums0) ->
-		% XXX should use a queue
+        % XXX Should use a queue.
 		list__append(PendingSeqNums0, [SeqNum], PendingSeqNums)
 	;
 		PendingSeqNums = [SeqNum]
 	),
 	svmap__set(Depth, PendingSeqNums, !PendingGoals),
 
-		% do the same for the rest of the pending goals
-	add_pending_goals(Rest, WaitingVarsTable,
-		!PendingGoals, !WaitingGoals).
+    % Do the same for the rest of the pending goals.
+    add_pending_goals(Rest, WaitingVarsTable, !PendingGoals, !WaitingGoals).
 
 %-----------------------------------------------------------------------------%
 
 	% Remove all references to a goal from the waiting goals table.
-
+    %
 :- pred delete_waiting_vars(list(prog_var)::in, goal_num::in,
 	waiting_goals_table::in, waiting_goals_table::out) is det.
 
@@ -431,11 +426,12 @@
 %-----------------------------------------------------------------------------%
 
 	% delay_info__wakeup_goals(Goals, !DelayInfo):
-	% Goals is the list of pending goal in the order that they should
-	% be woken up, and DelayInfo is the new delay_info, updated to
-	% reflect the fact that the Goals have been woken up and is
-	% hence are longer pending.
-
+    %
+    % Goals is the list of pending goal in the order that they should be
+    % woken up, and DelayInfo is the new delay_info, updated to reflect
+    % the fact that the Goals have been woken up and is hence are longer
+    % pending.
+    %
 delay_info__wakeup_goals(Goals, !DelayInfo) :-
 	( delay_info__wakeup_goal(Goal, !DelayInfo) ->
 		Goals = [Goal | Goals1],
@@ -444,30 +440,29 @@
 		Goals = []
 	).
 
-	% Check if there are any "pending" goals, and if so,
-	% select one to wake up, remove it from the delay_info,
-	% and return it.  If there are no pending goals, this
-	% predicate will fail.
+    % Check if there are any "pending" goals, and if so, select one to wake up,
+    % remove it from the delay_info, and return it. If there are no pending
+    % goals, this predicate will fail.
 	%
 :- pred delay_info__wakeup_goal(hlds_goal::out,
 	delay_info::in, delay_info::out) is semidet.
 
 	% delay_info__wakeup_goal(DelayInfo0, Goal, DelayInfo) is true iff
-	% DelayInfo0 specifies that there is at least one goal which is
-	% pending, Goal is the pending goal which should be reawakened first,
-	% and DelayInfo is the new delay_info, updated to reflect the fact
-	% that Goal has been woken up and is hence no longer pending.
-
+    % DelayInfo0 specifies that there is at least one goal which is pending,
+    % Goal is the pending goal which should be reawakened first, and DelayInfo
+    % is the new delay_info, updated to reflect the fact that Goal has been
+    % woken up and is hence no longer pending.
+    %
 delay_info__wakeup_goal(Goal, !DelayInfo) :-
 	delay_info__check_invariant(!.DelayInfo),
 	!.DelayInfo = delay_info(CurrentDepth, DelayedGoalStack0, WaitingGoals,
 		PendingGoalsTable0, NextSeqNums),
 
-		% is there a goal in the current conjunction which is pending?
+    % Is there a goal in the current conjunction which is pending?
 	map__search(PendingGoalsTable0, CurrentDepth, PendingGoals0),
 
-		% if so, remove it from the pending goals table,
-		% remove it from the delayed goals stack, and return it
+    % If so, remove it from the pending goals table, remove it from the
+    % delayed goals stack, and return it.
 	PendingGoals0 = [SeqNum | PendingGoals],
 	map__set(PendingGoalsTable0, CurrentDepth, PendingGoals,
 		PendingGoalsTable),
@@ -481,4 +476,9 @@
 	delay_info__check_invariant(!.DelayInfo).
 
 %-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "delay_info.m".
+
 %-----------------------------------------------------------------------------%
Index: compiler/delay_slot.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_slot.m,v
retrieving revision 1.11
diff -u -b -r1.11 delay_slot.m
--- compiler/delay_slot.m	24 Mar 2005 02:00:23 -0000	1.11
+++ compiler/delay_slot.m	12 Oct 2005 06:58:58 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1997-1998, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
Index: compiler/dense_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dense_switch.m,v
retrieving revision 1.51
diff -u -b -r1.51 dense_switch.m
--- compiler/dense_switch.m	7 Sep 2005 06:51:51 -0000	1.51
+++ compiler/dense_switch.m	12 Oct 2005 08:53:17 -0000
@@ -33,25 +33,24 @@
     % (we may convert locally semidet switches into locally det
     % switches by adding extra cases whose body is just `fail').
     %
-:- pred dense_switch__is_dense_switch(code_info::in, prog_var::in,
-    cases_list::in, can_fail::in, int::in, int::out, int::out,
-    can_fail::out) is semidet.
+:- pred is_dense_switch(code_info::in, prog_var::in, cases_list::in,
+    can_fail::in, int::in, int::out, int::out, can_fail::out) is semidet.
 
     % Generate code for a switch using a dense jump table.
     %
-:- pred dense_switch__generate(cases_list::in, int::in, int::in, prog_var::in,
+:- pred generate_dense_switch(cases_list::in, int::in, int::in, prog_var::in,
     code_model::in, can_fail::in, hlds_goal_info::in, label::in,
     branch_end::in, branch_end::out, code_tree::out,
     code_info::in, code_info::out) is det.
 
     % Also used by lookup_switch.
     %
-:- pred dense_switch__calc_density(int::in, int::in, int::out) is det.
+:- pred calc_density(int::in, int::in, int::out) is det.
 
     % Also used by lookup_switch.
     %
-:- pred dense_switch__type_range(code_info::in, type_category::in, (type)::in,
-    int::out) is semidet.
+:- pred type_range(code_info::in, type_category::in, (type)::in, int::out)
+    is semidet.
 
 %-----------------------------------------------------------------------------%
 
@@ -72,7 +71,7 @@
 :- import_module require.
 :- import_module std_util.
 
-dense_switch__is_dense_switch(CI, CaseVar, TaggedCases, CanFail0, ReqDensity,
+is_dense_switch(CI, CaseVar, TaggedCases, CanFail0, ReqDensity,
         FirstVal, LastVal, CanFail) :-
     list__length(TaggedCases, NumCases),
     NumCases > 2,
@@ -115,7 +114,7 @@
 
     % Calculate the percentage density given the range and the number of cases.
     %
-dense_switch__calc_density(NumCases, Range, Density) :-
+calc_density(NumCases, Range, Density) :-
     N1 = NumCases * 100,
     Density = N1 // Range.
 
@@ -125,14 +124,14 @@
     % of type that has a range or if the type's range is to big to switch on
     % (e.g. int).
     %
-dense_switch__type_range(CI, TypeCategory, Type, Range) :-
+type_range(CI, TypeCategory, Type, Range) :-
     code_info__get_module_info(CI, ModuleInfo),
     switch_util__type_range(TypeCategory, Type, ModuleInfo, Min, Max),
     Range = Max - Min + 1.
 
 %---------------------------------------------------------------------------%
 
-dense_switch__generate(Cases, StartVal, EndVal, Var, CodeModel, CanFail,
+generate_dense_switch(Cases, StartVal, EndVal, Var, CodeModel, CanFail,
         SwitchGoalInfo, EndLabel, MaybeEnd0, MaybeEnd, Code, !CI) :-
     % Evaluate the variable which we are going to be switching on.
     code_info__produce_variable(Var, VarCode, Rval, !CI),
@@ -156,9 +155,8 @@
         RangeCheck = empty
     ),
     % Now generate the jump table and the cases.
-    dense_switch__generate_cases(Cases, StartVal, EndVal, CodeModel,
-        SwitchGoalInfo, EndLabel, MaybeEnd0, MaybeEnd, Labels,
-        CasesCode, !CI),
+    generate_cases(Cases, StartVal, EndVal, CodeModel, SwitchGoalInfo,
+        EndLabel, MaybeEnd0, MaybeEnd, Labels, CasesCode, !CI),
 
     % XXX We keep track of the code_info at the end of one of the non-fail
     % cases. We have to do this because generating a `fail' slot last would
@@ -170,13 +168,12 @@
     % Assemble the code fragments.
     Code = tree_list([VarCode, RangeCheck, DoJump, CasesCode]).
 
-:- pred dense_switch__generate_cases(cases_list::in, int::in, int::in,
-    code_model::in, hlds_goal_info::in, label::in, branch_end::in,
-    branch_end::out, list(label)::out, code_tree::out,
-    code_info::in, code_info::out) is det.
+:- pred generate_cases(cases_list::in, int::in, int::in, code_model::in,
+    hlds_goal_info::in, label::in, branch_end::in, branch_end::out,
+    list(label)::out, code_tree::out, code_info::in, code_info::out) is det.
 
-dense_switch__generate_cases(Cases0, NextVal, EndVal, CodeModel,
-        SwitchGoalInfo, EndLabel, !MaybeEnd, Labels, Code, !CI) :-
+generate_cases(Cases0, NextVal, EndVal, CodeModel, SwitchGoalInfo, EndLabel,
+        !MaybeEnd, Labels, Code, !CI) :-
     ( NextVal > EndVal ->
         Labels = [],
         Code = node([
@@ -184,7 +181,7 @@
         ])
     ;
         code_info__get_next_label(ThisLabel, !CI),
-        dense_switch__generate_case(Cases0, Cases1, NextVal, CodeModel,
+        generate_case(Cases0, Cases1, NextVal, CodeModel,
             SwitchGoalInfo, !MaybeEnd, ThisCode, Comment, !CI),
         LabelCode = node([
             label(ThisLabel) - Comment
@@ -194,20 +191,20 @@
         ]),
         % Generate the rest of the cases.
         NextVal1 = NextVal + 1,
-        dense_switch__generate_cases(Cases1, NextVal1, EndVal, CodeModel,
-            SwitchGoalInfo, EndLabel, !MaybeEnd, Labels1, OtherCasesCode, !CI),
+        generate_cases(Cases1, NextVal1, EndVal, CodeModel, SwitchGoalInfo,
+            EndLabel, !MaybeEnd, Labels1, OtherCasesCode, !CI),
         Labels = [ThisLabel | Labels1],
         Code = tree_list([LabelCode, ThisCode, JumpCode, OtherCasesCode])
     ).
 
 %---------------------------------------------------------------------------%
 
-:- pred dense_switch__generate_case(cases_list::in, cases_list::out, int::in,
-    code_model::in, hlds_goal_info::in, branch_end::in, branch_end::out,
-    code_tree::out, string::out, code_info::in, code_info::out) is det.
+:- pred generate_case(cases_list::in, cases_list::out, int::in, code_model::in,
+    hlds_goal_info::in, branch_end::in, branch_end::out, code_tree::out,
+    string::out, code_info::in, code_info::out) is det.
 
-dense_switch__generate_case(!Cases, NextVal, CodeModel, SwitchGoalInfo,
-        !MaybeEnd, Code, Comment, !CI) :-
+generate_case(!Cases, NextVal, CodeModel, SwitchGoalInfo, !MaybeEnd, Code,
+        Comment, !CI) :-
     (
         !.Cases = [Case | !:Cases],
         Case = case(_, int_constant(NextVal), _, Goal)
Index: compiler/dupproc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dupproc.m,v
retrieving revision 1.4
diff -u -b -r1.4 dupproc.m
--- compiler/dupproc.m	14 Sep 2005 01:29:08 -0000	1.4
+++ compiler/dupproc.m	12 Oct 2005 07:06:52 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -12,7 +14,6 @@
 % don't matter for code generation, such as in/out vs di/uo, or (in some cases)
 % in/out, vs any/any.
 %
-
 %-----------------------------------------------------------------------------%
 
 :- module ll_backend__dupproc.
@@ -29,8 +30,7 @@
 
 :- pred eliminate_duplicate_procs(assoc_list(proc_label, c_procedure)::in,
 	list(c_procedure)::out,
-	map(proc_label, proc_label)::in, 
-	map(proc_label, proc_label)::out) is det.
+    map(proc_label, proc_label)::in, map(proc_label, proc_label)::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -53,8 +53,8 @@
 		IdProcs = [Id1 - Proc1 | IdProcsTail],
 		IdProcsTail = [_ | _],
 		standardize_proc(Proc1, StdProc1, !.DupProcMap),
-		eliminate_dup_procs([Id1 - StdProc1], IdProcsTail,
-			FinalIdProcsTail, !DupProcMap),
+        eliminate_dup_procs([Id1 - StdProc1], IdProcsTail, FinalIdProcsTail,
+            !DupProcMap),
 		assoc_list__values(FinalIdProcsTail, FinalProcsTail),
 		Procs = [Proc1 | FinalProcsTail]
 	).
@@ -62,16 +62,15 @@
 :- pred eliminate_dup_procs(assoc_list(proc_label, c_procedure)::in,
 	assoc_list(proc_label, c_procedure)::in,
 	assoc_list(proc_label, c_procedure)::out,
-	map(proc_label, proc_label)::in, 
-	map(proc_label, proc_label)::out) is det.
+    map(proc_label, proc_label)::in, map(proc_label, proc_label)::out) is det.
 
 eliminate_dup_procs(_ModelStdProcs, [], [], !DupProcMap).
 eliminate_dup_procs(ModelStdProcs0, [Id - Proc0 | IdProcs0],
 		[Id - Proc | IdProcs], !DupProcMap) :-
 	(
 		Proc0 ^ cproc_may_alter_rtti = may_alter_rtti,
-		find_matching_model_proc(ModelStdProcs0, Id, Proc0,
-			!.DupProcMap, MatchingId),
+        find_matching_model_proc(ModelStdProcs0, Id, Proc0, !.DupProcMap,
+            MatchingId),
 		maybe_redirect_proc(Proc0, MatchingId, MaybeProc),
 		MaybeProc = yes(ProcPrime)
 	->
@@ -124,9 +123,8 @@
 	list__length(LaterInstrs, NumLaterInstrs),
 	(
 		DisallowedInstrs = [],
-		% The threshold here is a guess. I don't think the precise
-		% value has much effect, so I don't think it is worth making
-		% it configurable.
+        % The threshold here is a guess. I don't think the precise value
+        % has much effect, so I don't think it is worth making it configurable.
 		NumLaterInstrs < 6
 	->
 		MaybeProc = no
@@ -186,8 +184,7 @@
 		Instr = call(Target, Cont, LiveInfo, Context, GoalPath, Model),
 		standardize_code_addr(Target, StdTarget, DupProcMap),
 		standardize_code_addr(Cont, StdCont, DupProcMap),
-		StdInstr = call(StdTarget, StdCont, LiveInfo, Context,
-			GoalPath, Model)
+        StdInstr = call(StdTarget, StdCont, LiveInfo, Context, GoalPath, Model)
 	;
 		Instr = mkframe(FrameInfo, MaybeCodeAddr),
 		(
@@ -195,8 +192,7 @@
 			StdFrameInfo = FrameInfo
 		;
 			FrameInfo = ordinary_frame(_, NumSlots, MaybePragma),
-			StdFrameInfo = ordinary_frame("", NumSlots,
-				MaybePragma)
+            StdFrameInfo = ordinary_frame("", NumSlots, MaybePragma)
 		),
 		standardize_maybe_code_addr(MaybeCodeAddr, MaybeStdCodeAddr,
 			DupProcMap),
@@ -283,8 +279,7 @@
 		StdInstr = join_and_continue(Lval, StdLabel)
 	;
 		Instr = pragma_c(_, _, _, _, _, _, _, _, _),
-		% The labels occurring in pragma_c instructions cannot be
-		% substituted.
+        % The labels occurring in pragma_c instructions cannot be substituted.
 		StdInstr = Instr
 	).
 
@@ -390,8 +385,8 @@
 	map(proc_label, proc_label)::in) is det.
 
 standardize_code_addrs([], [], _DupProcMap).
-standardize_code_addrs([CodeAddr | CodeAddrs], [StdCodeAddr |
-		StdCodeAddrs], DupProcMap) :-
+standardize_code_addrs([CodeAddr | CodeAddrs], [StdCodeAddr | StdCodeAddrs],
+        DupProcMap) :-
 	standardize_code_addr(CodeAddr, StdCodeAddr, DupProcMap),
 	standardize_code_addrs(CodeAddrs, StdCodeAddrs, DupProcMap).
 
Index: compiler/follow_code.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/follow_code.m,v
retrieving revision 1.74
diff -u -b -r1.74 follow_code.m
--- compiler/follow_code.m	30 Sep 2005 08:08:19 -0000	1.74
+++ compiler/follow_code.m	12 Oct 2005 07:21:16 -0000
@@ -1,12 +1,30 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1994-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % Main author: conway.
 % Extensive modifications by zs.
-
+%
+% The problem attacked by this module is that sometimes the code generator
+% doesn't know where it should put the values of live variables at the end
+% of a branched control structure. All branches must put each live variable
+% into the same lval, so having each branch leave each live variable where it
+% just happens to be is not an option. We currently just put all live variables
+% into its own rN register or stack slot, but often is not where the variable
+% happens to be at the end of any branch, nor is it where the variable is next
+% needed.
+%
+% The idea used by this module to attack this problem is to try to ensure
+% that the branched control structure is followed immediately either by a call
+% or by the end of the procedure body, because both have clear rules about
+% where every live variable must be. If a branched control structure is
+% followed by builtin goals such as unifications, we push those goals into
+% each branch.
+%
 %-----------------------------------------------------------------------------%
 
 :- module ll_backend__follow_code.
@@ -20,10 +38,10 @@
 :- import_module list.
 
 :- pred move_follow_code_in_proc(pred_id::in, proc_id::in, pred_info::in,
-	proc_info::in, proc_info::out, module_info::in, module_info::out)
-	is det.
+	proc_info::in, proc_info::out, module_info::in, module_info::out) is det.
 
 	% Split a list of goals into the prefix of builtins and the rest.
+    %
 :- pred move_follow_code_select(list(hlds_goal)::in, list(hlds_goal)::out,
 	list(hlds_goal)::out) is det.
 
@@ -61,16 +79,15 @@
 	proc_info_vartypes(!.ProcInfo, VarTypes0),
 	(
 		move_follow_code_in_goal(Goal0, Goal1, Flags, no, Res),
-			% did the goal change?
+        % Did the goal change?
 		Res = yes
 	->
-			% we need to fix up the goal_info by recalculating
-			% the nonlocal vars and the non-atomic instmap deltas.
+        % We need to fix up the goal_info by recalculating the nonlocal vars
+        % and the non-atomic instmap deltas.
 		proc_info_headvars(!.ProcInfo, HeadVars),
-		implicitly_quantify_clause_body(HeadVars, _Warnings,
-			Goal1, Goal2, Varset0, Varset, VarTypes0, VarTypes),
-		proc_info_get_initial_instmap(!.ProcInfo,
-			!.ModuleInfo, InstMap0),
+		implicitly_quantify_clause_body(HeadVars, _Warnings, Goal1, Goal2,
+            Varset0, Varset, VarTypes0, VarTypes),
+		proc_info_get_initial_instmap(!.ProcInfo, !.ModuleInfo, InstMap0),
 		proc_info_inst_varset(!.ProcInfo, InstVarSet),
 		recompute_instmap_delta(no, Goal2, Goal, VarTypes, InstVarSet,
 			InstMap0, !ModuleInfo)
@@ -100,9 +117,8 @@
 move_follow_code_in_goal_2(conj(Goals0), conj(Goals), Flags, !R) :-
 	move_follow_code_in_conj(Goals0, Goals, Flags, !R).
 move_follow_code_in_goal_2(par_conj(Goals0), par_conj(Goals), Flags, !R) :-
-		% move_follow_code_in_disj treats its list of goals as
-		% independent goals, so we can use it to process the
-		% independent parallel conjuncts.
+    % move_follow_code_in_disj treats its list of goals as independent goals,
+    % so we can use it to process the independent parallel conjuncts.
 	move_follow_code_in_disj(Goals0, Goals, Flags, !R).
 move_follow_code_in_goal_2(disj(Goals0), disj(Goals), Flags, !R) :-
 	move_follow_code_in_disj(Goals0, Goals, Flags, !R).
@@ -116,22 +132,22 @@
 	move_follow_code_in_goal(Cond0, Cond, Flags, !R),
 	move_follow_code_in_goal(Then0, Then, Flags, !R),
 	move_follow_code_in_goal(Else0, Else, Flags, !R).
-move_follow_code_in_goal_2(scope(Remove, Goal0),
-		scope(Remove, Goal), Flags, !R) :-
+move_follow_code_in_goal_2(scope(Remove, Goal0), scope(Remove, Goal),
+        Flags, !R) :-
 	move_follow_code_in_goal(Goal0, Goal, Flags, !R).
 move_follow_code_in_goal_2(Goal @ generic_call(_, _, _, _), Goal, _, !R).
 move_follow_code_in_goal_2(Goal @ call(_, _, _, _, _, _), Goal, _, !R).
 move_follow_code_in_goal_2(Goal @ unify(_, _, _, _, _), Goal, _, !R).
 move_follow_code_in_goal_2(Goal @ foreign_proc(_, _, _, _, _, _), Goal, _, !R).
 move_follow_code_in_goal_2(shorthand(_), _, _, _, _) :-
-	% these should have been expanded out by now
+	% These should have been expanded out by now.
 	error("move_follow_code_in_goal_2: unexpected shorthand").
 
 %-----------------------------------------------------------------------------%
 
 	% move_follow_code_in_disj is used both for disjunction and
 	% parallel conjunction.
-
+    %
 :- pred move_follow_code_in_disj(list(hlds_goal)::in, list(hlds_goal)::out,
 	pair(bool)::in, bool::in, bool::out) is det.
 
@@ -146,16 +162,16 @@
 	pair(bool)::in, bool::in, bool::out) is det.
 
 move_follow_code_in_cases([], [], _, !R).
-move_follow_code_in_cases([case(Cons, Goal0)|Goals0], [case(Cons, Goal)|Goals],
-		Flags, !R) :-
+move_follow_code_in_cases([case(Cons, Goal0) | Goals0],
+        [case(Cons, Goal) | Goals], Flags, !R) :-
 	move_follow_code_in_goal(Goal0, Goal, Flags, !R),
 	move_follow_code_in_cases(Goals0, Goals, Flags, !R).
 
 %-----------------------------------------------------------------------------%
 
-	% Find the first branched structure, and split the
-	% conj into those goals before and after it.
-
+	% Find the first branched structure, and split the conj into those goals
+    % before and after it.
+    %
 :- pred move_follow_code_in_conj(list(hlds_goal)::in, list(hlds_goal)::out,
 	pair(bool)::in, bool::in, bool::out) is det.
 
@@ -167,15 +183,14 @@
 	list(hlds_goal)::out, pair(bool)::in, bool::in, bool::out) is det.
 
 move_follow_code_in_conj_2([], !RevPrevGoals, _, !R).
-move_follow_code_in_conj_2([Goal0 | Goals0], !RevPrevGoals,
-		Flags, !R) :-
+move_follow_code_in_conj_2([Goal0 | Goals0], !RevPrevGoals, Flags, !R) :-
 	Flags = PushFollowCode - _PushPrevCode,
 	(
 		PushFollowCode = yes,
 		Goal0 = GoalExpr0 - _,
 		goal_util__goal_is_branched(GoalExpr0),
 		move_follow_code_select(Goals0, FollowGoals, RestGoalsPrime),
-		FollowGoals \= [],
+		FollowGoals = [_ | _],
 		move_follow_code_move_goals(Goal0, FollowGoals, Goal1Prime)
 	->
 		!:R = yes,
@@ -217,10 +232,8 @@
 		Goal = disj(Goals)
 	;
 		Goal0 = if_then_else(Vars, Cond, Then0, Else0),
-		follow_code__conjoin_goal_and_goal_list(Then0,
-			FollowGoals, Then),
-		follow_code__conjoin_goal_and_goal_list(Else0,
-			FollowGoals, Else),
+		follow_code__conjoin_goal_and_goal_list(Then0, FollowGoals, Then),
+		follow_code__conjoin_goal_and_goal_list(Else0, FollowGoals, Else),
 		Goal = if_then_else(Vars, Cond, Then, Else)
 	).
 
@@ -248,10 +261,10 @@
 
 %-----------------------------------------------------------------------------%
 
-	% Takes a goal and a list of goals, and conjoins them
-	% (with a potentially blank goal_info), checking that the
-	% determinism of the goal is not changed.
-
+	% Takes a goal and a list of goals, and conjoins them (with a potentially
+    % blank goal_info), checking that the determinism of the goal is not
+    % changed.
+    %
 :- pred follow_code__conjoin_goal_and_goal_list(hlds_goal::in,
 	list(hlds_goal)::in, hlds_goal::out) is semidet.
 
@@ -272,9 +285,9 @@
 		Goal = GoalExpr - GoalInfo0
 	).
 
-	% This check is necessary to make sure that follow_code
-	% doesn't change the determinism of the goal.
-
+	% This check is necessary to make sure that follow_code doesn't change
+    % the determinism of the goal.
+    %
 :- pred check_follow_code_detism(list(hlds_goal)::in, determinism::in)
 	is semidet.
 
@@ -295,13 +308,3 @@
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
-
-:- pred move_prev_code_forbidden_vars(list(hlds_goal)::in, set(prog_var)::out)
-	is det.
-
-move_prev_code_forbidden_vars([], Empty) :-
-	set__init(Empty).
-move_prev_code_forbidden_vars([_Goal - GoalInfo | Goals], Varset) :-
-	move_prev_code_forbidden_vars(Goals, Varset0),
-	goal_info_get_nonlocals(GoalInfo, NonLocals),
-	set__union(Varset0, NonLocals, Varset).
Index: compiler/global_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/global_data.m,v
retrieving revision 1.9
diff -u -b -r1.9 global_data.m
--- compiler/global_data.m	12 May 2005 04:06:55 -0000	1.9
+++ compiler/global_data.m	12 Oct 2005 07:25:58 -0000
@@ -1,13 +1,15 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % Author: zs.
-
+%
 % This module manages global data structures for the LLDS backend.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module ll_backend__global_data.
@@ -20,6 +22,7 @@
 :- import_module ll_backend__llds.
 :- import_module mdbcomp__prim_data. % for module_name
 
+:- import_module assoc_list.
 :- import_module bool.
 :- import_module list.
 
@@ -60,10 +63,6 @@
 :- pred global_data_set_static_cell_info(static_cell_info::in,
 	global_data::in, global_data::out) is det.
 
-:- import_module assoc_list.
-:- import_module bool.
-:- import_module list.
-
 :- type static_cell_info.
 
 :- func init_static_cell_info(module_name, bool, bool) = static_cell_info.
@@ -84,7 +83,7 @@
 	% the exception is that for boxed floats, the type is data_ptr
 	% (i.e. the type of the boxed value) rather than float
 	% (the type of the unboxed value).
-
+    %
 :- pred rval_type_as_arg(rval::in, exprn_opts::in, llds_type::out) is det.
 
 :- implementation.
@@ -92,6 +91,7 @@
 :- import_module backend_libs__rtti.
 :- import_module ll_backend__layout.
 :- import_module ll_backend__llds_out.
+:- import_module parse_tree__error_util.
 
 :- import_module counter.
 :- import_module int.
@@ -109,10 +109,12 @@
 						% Information about the global
 						% variables defined by each
 						% procedure.
+
 			proc_layout_map		:: proc_layout_map,
 						% Information about the
 						% layout structures defined
 						% by each procedure.
+
 			closure_layouts		:: list(comp_gen_c_data),
 						% The list of all closure
 						% layouts generated in this
@@ -122,6 +124,7 @@
 						% it is possible, although
 						% unlikely, for two closures
 						% to have the same layout.
+
 			static_cell_info	:: static_cell_info
 						% Information about all the
 						% statically allocated cells
@@ -135,31 +138,27 @@
 global_data_init(StaticCellInfo, GlobalData) :-
 	map__init(EmptyDataMap),
 	map__init(EmptyLayoutMap),
-	GlobalData = global_data(EmptyDataMap, EmptyLayoutMap, [],
-		StaticCellInfo).
+    GlobalData = global_data(EmptyDataMap, EmptyLayoutMap, [], StaticCellInfo).
 
-global_data_add_new_proc_var(PredProcId, ProcVar, GlobalData0, GlobalData) :-
-	ProcVarMap0 = GlobalData0 ^ proc_var_map,
+global_data_add_new_proc_var(PredProcId, ProcVar, !GlobalData) :-
+    ProcVarMap0 = !.GlobalData ^ proc_var_map,
 	map__det_insert(ProcVarMap0, PredProcId, ProcVar, ProcVarMap),
-	GlobalData = GlobalData0 ^ proc_var_map := ProcVarMap.
+    !:GlobalData = !.GlobalData ^ proc_var_map := ProcVarMap.
 
-global_data_add_new_proc_layout(PredProcId, ProcLayout,
-		GlobalData0, GlobalData) :-
-	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
+global_data_add_new_proc_layout(PredProcId, ProcLayout, !GlobalData) :-
+    ProcLayoutMap0 = !.GlobalData ^ proc_layout_map,
 	map__det_insert(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	GlobalData = GlobalData0 ^ proc_layout_map := ProcLayoutMap.
+    !:GlobalData = !.GlobalData ^ proc_layout_map := ProcLayoutMap.
 
-global_data_update_proc_layout(PredProcId, ProcLayout,
-		GlobalData0, GlobalData) :-
-	ProcLayoutMap0 = GlobalData0 ^ proc_layout_map,
+global_data_update_proc_layout(PredProcId, ProcLayout, !GlobalData) :-
+    ProcLayoutMap0 = !.GlobalData ^ proc_layout_map,
 	map__det_update(ProcLayoutMap0, PredProcId, ProcLayout, ProcLayoutMap),
-	GlobalData = GlobalData0 ^ proc_layout_map := ProcLayoutMap.
+    !:GlobalData = !.GlobalData ^ proc_layout_map := ProcLayoutMap.
 
-global_data_add_new_closure_layouts(NewClosureLayouts,
-		GlobalData0, GlobalData) :-
-	ClosureLayouts0 = GlobalData0 ^ closure_layouts,
+global_data_add_new_closure_layouts(NewClosureLayouts, !GlobalData) :-
+    ClosureLayouts0 = !.GlobalData ^ closure_layouts,
 	list__append(NewClosureLayouts, ClosureLayouts0, ClosureLayouts),
-	GlobalData = GlobalData0 ^ closure_layouts := ClosureLayouts.
+    !:GlobalData = !.GlobalData ^ closure_layouts := ClosureLayouts.
 
 global_data_maybe_get_proc_layout(GlobalData, PredProcId, ProcLayout) :-
 	ProcLayoutMap = GlobalData ^ proc_layout_map,
@@ -183,8 +182,8 @@
 global_data_get_static_cell_info(GlobalData, StaticCellInfo) :-
 	StaticCellInfo = GlobalData ^ static_cell_info.
 
-global_data_set_static_cell_info(StaticCellInfo, GlobalData0, GlobalData) :-
-	GlobalData = GlobalData0 ^ static_cell_info := StaticCellInfo.
+global_data_set_static_cell_info(StaticCellInfo, !GlobalData) :-
+    !:GlobalData = !.GlobalData ^ static_cell_info := StaticCellInfo.
 
 %-----------------------------------------------------------------------------%
 
@@ -226,21 +225,21 @@
 		counter__init(0), counter__init(0), Cells0, CellMap0).
 
 add_static_cell_natural_types(Args, DataAddr, !Info) :-
-	list__map(associate_natural_type(!.Info ^ unbox_float), Args,
-		ArgsTypes),
+    list__map(associate_natural_type(!.Info ^ unbox_float), Args, ArgsTypes),
 	add_static_cell(ArgsTypes, DataAddr, !Info).
 
 add_static_cell(ArgsTypes0, DataAddr, !Info) :-
 		% If we have an empty cell, place a dummy field in it,
 		% so that the generated C structure isn't empty.
-	( ArgsTypes0 = [] ->
+    (
+        ArgsTypes0 = [],
 		ArgsTypes = [const(int_const(-1)) - integer]
 	;
+        ArgsTypes0 = [_ | _],
 		ArgsTypes = ArgsTypes0
 	),
 	compute_cell_type(ArgsTypes, CellType, CellTypeAndValue),
-	do_add_static_cell(ArgsTypes, CellType, CellTypeAndValue, DataAddr,
-		!Info).
+    do_add_static_cell(ArgsTypes, CellType, CellTypeAndValue, DataAddr, !Info).
 
 :- pred do_add_static_cell(assoc_list(rval, llds_type)::in, cell_type::in,
 	cell_args::in, data_addr::out,
@@ -270,10 +269,8 @@
 		(
 			!.Info ^ common_data = yes,
 			map__set(MembersMap0, Args, DataName, MembersMap),
-			CellGroup = CellGroup1 ^ cell_group_members
-				:= MembersMap,
-			map__set(CellGroupMap0, CellType, CellGroup,
-				CellGroupMap),
+            CellGroup = CellGroup1 ^ cell_group_members := MembersMap,
+            map__set(CellGroupMap0, CellType, CellGroup, CellGroupMap),
 			!:Info = !.Info ^ cell_group_map := CellGroupMap
 		;
 			!.Info ^ common_data = no
@@ -284,12 +281,10 @@
 		Cells0 = !.Info ^ cells,
 		(
 			CellArgs = plain_args(PlainArgs),
-			CellTypeAndValue =
-				plain_type_and_value(TypeNum, PlainArgs)
+            CellTypeAndValue = plain_type_and_value(TypeNum, PlainArgs)
 		;
 			CellArgs = grouped_args(GroupedArgs),
-			CellTypeAndValue =
-				grouped_type_and_value(TypeNum, GroupedArgs)
+            CellTypeAndValue = grouped_type_and_value(TypeNum, GroupedArgs)
 		),
 		Cell = common_data(ModuleName, CellNum, CellTypeAndValue),
 		map__det_insert(Cells0, CellNum, Cell, Cells),
@@ -324,25 +319,20 @@
 		TypeAndArgGroups) :-
 	(
 		LaterArgsTypes = [],
-		make_arg_groups(CurType, RevArgsSoFar,
-			TypeGroup, TypeAndArgGroup),
+        make_arg_groups(CurType, RevArgsSoFar, TypeGroup, TypeAndArgGroup),
 		TypeGroups = [TypeGroup],
 		TypeAndArgGroups = [TypeAndArgGroup]
 	;
 		LaterArgsTypes = [NextArg - NextType | MoreArgsTypes],
 		( CurType = NextType ->
-			threshold_group_types(CurType,
-				[NextArg | RevArgsSoFar], MoreArgsTypes,
-				TypeGroups, TypeAndArgGroups)
+            threshold_group_types(CurType, [NextArg | RevArgsSoFar],
+                MoreArgsTypes, TypeGroups, TypeAndArgGroups)
 		;
-			threshold_group_types(NextType, [NextArg],
-				MoreArgsTypes,
+            threshold_group_types(NextType, [NextArg], MoreArgsTypes,
 				TypeGroupsTail, TypeAndArgGroupsTail),
-			make_arg_groups(CurType, RevArgsSoFar,
-				TypeGroup, TypeAndArgGroup),
+            make_arg_groups(CurType, RevArgsSoFar, TypeGroup, TypeAndArgGroup),
 			TypeGroups = [TypeGroup | TypeGroupsTail],
-			TypeAndArgGroups = [TypeAndArgGroup |
-				TypeAndArgGroupsTail]
+            TypeAndArgGroups = [TypeAndArgGroup | TypeAndArgGroupsTail]
 		)
 	).
 
@@ -377,15 +367,14 @@
 	is det.
 
 offset_into_group([], _, _) :-
-	error("offset_into_group: offset out of bounds").
+    unexpected(this_file, "offset_into_group: offset out of bounds").
 offset_into_group([Group | Groups], Offset, Rval) :-
 	(
 		Group = common_cell_grouped_args(_, NumRvalsInGroup, Rvals),
 		( Offset < NumRvalsInGroup ->
 			list__index0_det(Rvals, Offset, Rval)
 		;
-			offset_into_group(Groups, Offset - NumRvalsInGroup,
-				Rval)
+            offset_into_group(Groups, Offset - NumRvalsInGroup, Rval)
 		)
 	;
 		Group = common_cell_ungrouped_arg(_, GroupRval),
@@ -424,5 +413,11 @@
 
 associate_natural_type(UnboxFloat, Rval, Rval - Type) :-
 	natural_type(UnboxFloat, Rval, Type).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "global_data.m".
 
 %-----------------------------------------------------------------------------%
Index: compiler/goal_store.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_store.m,v
retrieving revision 1.5
diff -u -b -r1.5 goal_store.m
--- compiler/goal_store.m	24 Mar 2005 02:00:27 -0000	1.5
+++ compiler/goal_store.m	12 Oct 2005 07:33:15 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2000, 2003, 2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -12,7 +14,6 @@
 % dictionary which are specific to hlds_goals.
 %
 %-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
 
 :- module transform_hlds__goal_store.
 
@@ -35,8 +36,8 @@
 :- pred goal_store__init(goal_store(T)::out) is det.
 :- func goal_store__init = goal_store(T).
 
-:- pred goal_store__det_insert(goal_store(T)::in, T::in, goal::in,
-	goal_store(T)::out) is det.
+:- pred goal_store__det_insert(T::in, goal::in,
+    goal_store(T)::in, goal_store(T)::out) is det.
 
 :- pred goal_store__lookup(goal_store(T)::in, T::in, goal::out) is det.
 
@@ -67,7 +68,7 @@
 goal_store__init = GS :-
 	goal_store__init(GS).
 
-goal_store__det_insert(GS0, Id, Goal, GS) :-
+goal_store__det_insert(Id, Goal, GS0, GS) :-
 	map__det_insert(GS0, Id, Goal, GS).
 
 goal_store__lookup(GS, Id, Goal) :-
@@ -76,7 +77,7 @@
 goal_store__member(GoalStore, Key, Goal) :-
 	map__member(GoalStore, Key, Goal).
 
-goal_store__all_ancestors(GoalStore, StartId, VarTypes, ModuleInfo, FullyStrict,
+all_ancestors(GoalStore, StartId, VarTypes, ModuleInfo, FullyStrict,
 		AncestorIds) :-
 	AncestorIds = ancestors_2(GoalStore, [StartId], set__init,
 		VarTypes, ModuleInfo, FullyStrict).
@@ -91,15 +92,14 @@
 	(
 		set__member(Id, VisitedIds)
 	->
-		AncestorIds = ancestors_2(GoalStore, Ids, VisitedIds,
-				VarTypes, ModuleInfo, FullyStrict)
+        AncestorIds = ancestors_2(GoalStore, Ids, VisitedIds, VarTypes,
+            ModuleInfo, FullyStrict)
 	;
-		Ancestors = direct_ancestors(GoalStore, Id, VarTypes,
-				ModuleInfo, FullyStrict),
+        Ancestors = direct_ancestors(GoalStore, Id, VarTypes, ModuleInfo,
+            FullyStrict),
 		AncestorIds = set__list_to_set(Ancestors) `union`
 			ancestors_2(GoalStore, Ancestors `append` Ids,
-				set__insert(VisitedIds, Id),
-				VarTypes, ModuleInfo, FullyStrict)
+                set__insert(VisitedIds, Id), VarTypes, ModuleInfo, FullyStrict)
 	).
 
 :- func direct_ancestors(goal_store(T), T, vartypes, module_info, bool)
@@ -107,8 +107,8 @@
 
 direct_ancestors(GoalStore, StartId, VarTypes, ModuleInfo, FullyStrict)
 		= Ancestors :-
-	solutions(direct_ancestor(GoalStore, StartId, VarTypes,
-		ModuleInfo, FullyStrict), Ancestors).
+    solutions(direct_ancestor(GoalStore, StartId, VarTypes, ModuleInfo,
+        FullyStrict), Ancestors).
 
 :- pred direct_ancestor(goal_store(T)::in, T::in, vartypes::in,
 	module_info::in, bool::in, T::out) is nondet.
@@ -119,8 +119,7 @@
 	goal_store__member(GoalStore, EarlierId, EarlierGoal - EarlierInstMap),
 	compare((<), EarlierId, StartId),
 	not goal_util__can_reorder_goals(ModuleInfo, VarTypes, FullyStrict,
-		EarlierInstMap, EarlierGoal,
-		LaterInstMap, LaterGoal).
+        EarlierInstMap, EarlierGoal, LaterInstMap, LaterGoal).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
Index: compiler/graph_colour.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/graph_colour.m,v
retrieving revision 1.13
diff -u -b -r1.13 graph_colour.m
--- compiler/graph_colour.m	24 Mar 2005 02:00:28 -0000	1.13
+++ compiler/graph_colour.m	12 Oct 2005 08:18:24 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1995-1996, 2004-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -8,7 +10,7 @@
 % main author: conway.
 %
 % This file contains functionality to find a 'good' colouring of a graph.
-% The predicate graph_colour__group_elements(set(set(T)), set(set(T))),
+% The predicate group_elements(set(set(T)), set(set(T))),
 % takes a set of sets each containing elements that touch, and returns
 % a set of sets each containing elements that can be assigned the same
 % colour, ensuring that touching elements have different colours.
@@ -23,19 +25,22 @@
 
 :- import_module set.
 
-:- pred graph_colour__group_elements(set(set(T))::in, set(set(T))::out) is det.
+:- pred group_elements(set(set(T))::in, set(set(T))::out) is det.
 
 :- implementation.
 
+:- import_module parse_tree.
+:- import_module parse_tree__error_util.
+
 :- import_module list.
 :- import_module require.
 
-graph_colour__group_elements(Constraints, Colours) :-
+group_elements(Constraints, Colours) :-
 	set__power_union(Constraints, AllVars),
 	set__init(EmptySet),
 	set__delete(Constraints, EmptySet, Constraints1),
 	set__to_sorted_list(Constraints1, ConstraintList),
-	graph_colour__find_all_colours(ConstraintList, AllVars, ColourList),
+    find_all_colours(ConstraintList, AllVars, ColourList),
 	set__list_to_set(ColourList, Colours).
 
 %	% performance reducing sanity check....
@@ -43,94 +48,83 @@
 %		set__power_union(Colours, AllColours),
 %		(set__member(Var, AllVars) => set__member(Var, AllColours))
 %	->
-%		error("graph_colour__group_elements: sanity check failed")
+%       error("group_elements: sanity check failed")
 %	;
 %		true
 %	).
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__find_all_colours(list(set(T))::in, set(T)::in,
+    % Iterate the assignment of a new colour until all constraints
+    % are satisfied.
+    %
+:- pred find_all_colours(list(set(T))::in, set(T)::in,
 	list(set(T))::out) is det.
 
-	% Iterate the assignment of a new colour untill all constraints
-	% are satisfied.
-graph_colour__find_all_colours(ConstraintList, Vars, ColourList) :-
-	( ConstraintList = [] ->
+find_all_colours(ConstraintList, Vars, ColourList) :-
+    (
+        ConstraintList = [],
 		ColourList = []
 	;
-		graph_colour__next_colour(Vars, ConstraintList,
-			RemainingConstraints, Colour),
+        ConstraintList = [_ | _],
+        next_colour(Vars, ConstraintList, RemainingConstraints, Colour),
 		set__difference(Vars, Colour, RestVars),
-		graph_colour__find_all_colours(RemainingConstraints, RestVars,
-			ColourList0),
+        find_all_colours(RemainingConstraints, RestVars, ColourList0),
 		ColourList = [Colour | ColourList0]
 	).
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__next_colour(set(T)::in, list(set(T))::in,
+:- pred next_colour(set(T)::in, list(set(T))::in,
 	list(set(T))::out, set(T)::out) is det.
 
-graph_colour__next_colour(Vars0, ConstraintList, Remainder, SameColour) :-
+next_colour(Vars0, ConstraintList, Remainder, SameColour) :-
 	% Check if there are any constraints left to be satisfied.
 	(
 		ConstraintList = [_ | _],
 			% Select a variable to assign a colour, ...
-		graph_colour__choose_var(Vars0, Var, Vars1),
+        choose_var(Vars0, Var, Vars1),
+
 			% ... and divide the constraints into those that
 			% may be the same colour as that var and those
 			% that may not.
-		graph_colour__divide_constraints(Var, ConstraintList,
-			WereContaining, NotContaining, Vars1, RestVars),
+        divide_constraints(Var, ConstraintList, WereContaining, NotContaining,
+            Vars1, RestVars),
 		(
-				% See if there are sets that can
-				% share a colour with the selected var.
+            % See if there are sets that can share a colour with the
+            % selected var.
 			NotContaining = [_ | _],
 			( set__empty(RestVars) ->
-					% There were no variables left
-					% that could share a colour, so
-					% create a singleton set containing
-					% this variable.
+                % There were no variables left that could share a colour,
+                % so create a singleton set containing this variable.
 				set__singleton_set(SameColour, Var),
 				ResidueSets = NotContaining
 			;
-					% If there is at least one variable
-					% that can share a colour with the
-					% selected variable, then recursively
-					% use the remaining constraints to
-					% assign a colour to one of the
-					% remaining vars, and assemble the
-					% constraint residues.
-				graph_colour__next_colour(RestVars,
-					NotContaining, ResidueSets,
-					SameColour0),
-					% add this variable to the
-					% variables of the current
-					% colour.
+                % If there is at least one variable that can share a colour
+                % with the selected variable, then recursively use the
+                % remaining constraints to assign a colour to one of the
+                % remaining vars, and assemble the constraint residues.
+                next_colour(RestVars, NotContaining, ResidueSets, SameColour0),
+
+                % Add this variable to the variables of the current colour.
 				set__insert(SameColour0, Var, SameColour)
 			)
 		;
 			NotContaining = [],
-				% There were no more constraints
-				% which could be satisfied by assigning
-				% any variable a colour the same as the
-				% current variable, so create a signleton
-				% set with the current var, and assign
-				% the residue to the empty set.
+            % There were no more constraints which could be satisfied
+            % by assigning any variable a colour the same as the current
+            % variable, so create a signleton set with the current var,
+            % and assign the residue to the empty set.
 			set__singleton_set(SameColour, Var),
 			ResidueSets = []
 		),
-			% The remaining constraints are the residue
-			% sets that could not be satisfied by assigning
-			% any variable to the current colour, and the
-			% constraints that were already satisfied by
-			% the assignment of the current variable to
-			% this colour.
+        % The remaining constraints are the residue sets that could not be
+        % satisfied by assigning any variable to the current colour, and the
+        % constraints that were already satisfied by the assignment of the
+        % current variable to this colour.
 		list__append(ResidueSets, WereContaining, Remainder)
 	;
-			% If there were no constraints, then no colours
-			% were needed.
+        % If there were no constraints, then no colours were needed.
 		ConstraintList = [],
 		Remainder = [],
 		set__init(SameColour)
@@ -138,21 +132,20 @@
 
 %------------------------------------------------------------------------------%
 
-% graph_colour__divide_constraints takes a var and a list of sets of var,
-% and divides the list into two lists: a list of sets containing the
-% given variable and a list of sets not containing that variable. The
-% sets in the list containing the variable have that variable removed.
-% Additionally, a set of variables is threaded through the computation,
-% and any variables that were in sets that also contained the given
-% variables are removed from the threaded set.
-
-:- pred graph_colour__divide_constraints(T::in,
-	list(set(T))::in, list(set(T))::out, list(set(T))::out,
-	set(T)::in, set(T)::out) is det.
-
-graph_colour__divide_constraints(_Var, [], [], [], !Vars).
-graph_colour__divide_constraints(Var, [S | Ss], C, NC, !Vars) :-
-	graph_colour__divide_constraints(Var, Ss, C0, NC0, !Vars),
+    % Divide_constraints takes a var and a list of sets of var, and divides
+    % the list into two lists: a list of sets containing the given variable
+    % and a list of sets not containing that variable. The sets in the list
+    % containing the variable have that variable removed. Additionally, a set
+    % of variables is threaded through the computation, and any variables that
+    % were in sets that also contained the given variables are removed from
+    % the threaded set.
+    %
+:- pred divide_constraints(T::in, list(set(T))::in,
+    list(set(T))::out, list(set(T))::out, set(T)::in, set(T)::out) is det.
+
+divide_constraints(_Var, [], [], [], !Vars).
+divide_constraints(Var, [S | Ss], C, NC, !Vars) :-
+    divide_constraints(Var, Ss, C0, NC0, !Vars),
 	( set__member(Var, S) ->
 		set__delete(S, Var, T),
 		( set__empty(T) ->
@@ -169,18 +162,23 @@
 
 %------------------------------------------------------------------------------%
 
-% graph_colour__choose_var/3, given a set of variables, chooses
-% one, returns it and the set with that variable removed.
-
-:- pred graph_colour__choose_var(set(T)::in, T::out, set(T)::out) is det.
+    % Choose_var/3, given a set of variables, chooses one, returns it
+    % and the set with that variable removed.
+    %
+:- pred choose_var(set(T)::in, T::out, set(T)::out) is det.
 
-graph_colour__choose_var(Vars0, Var, Vars) :-
+choose_var(Vars0, Var, Vars) :-
 	( set__remove_least(Vars0, VarPrime, VarsPrime) ->
 		Var = VarPrime,
 		Vars = VarsPrime
 	;
-		error("graph_colour__choose_var: no vars!")
+        unexpected(this_file, "choose_var: no vars!")
 	).
 
 %------------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "graph_colour.m".
+
 %------------------------------------------------------------------------------%
Index: compiler/hhf.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hhf.m,v
retrieving revision 1.9
diff -u -b -r1.9 hhf.m
--- compiler/hhf.m	12 Sep 2005 05:24:06 -0000	1.9
+++ compiler/hhf.m	12 Oct 2005 08:11:35 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2002, 2004-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -21,11 +23,11 @@
 :- import_module bool.
 :- import_module io.
 
-:- pred hhf__process_pred(bool::in, pred_id::in, module_info::in,
-	module_info::out, io__state::di, io__state::uo) is det.
+:- pred process_pred(bool::in, pred_id::in, module_info::in,
+    module_info::out, io::di, io::uo) is det.
 
-:- pred hhf__process_clauses_info(bool::in, module_info::in, clauses_info::in,
-	clauses_info::out, inst_graph::out) is det.
+:- pred process_clauses_info(bool::in, module_info::in,
+    clauses_info::in, clauses_info::out, inst_graph::out) is det.
 
 :- implementation.
 
@@ -35,6 +37,7 @@
 :- import_module hlds__hlds_goal.
 :- import_module hlds__passes_aux.
 :- import_module hlds__quantification.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_util.
 :- import_module parse_tree__prog_type.
 
@@ -46,7 +49,7 @@
 :- import_module term.
 :- import_module varset.
 
-hhf__process_pred(Simple, PredId, !ModuleInfo, !IO) :-
+process_pred(Simple, PredId, !ModuleInfo, !IO) :-
 	module_info_pred_info(!.ModuleInfo, PredId, PredInfo0),
 	( pred_info_is_imported(PredInfo0) ->
 		% AAA
@@ -54,39 +57,42 @@
 		pred_info_clauses_info(PredInfo0, ClausesInfo),
 		clauses_info_headvars(ClausesInfo, HeadVars),
 		clauses_info_varset(ClausesInfo, VarSet),
-		IGI0 = PredInfo0 ^ inst_graph_info,
+        some [!IG] (
+            !:IG = PredInfo0 ^ inst_graph_info,
 		inst_graph__init(HeadVars, InstGraph),
-		IGI1 = IGI0 ^ implementation_inst_graph := InstGraph,
-		IGI2 = IGI1 ^ interface_inst_graph := InstGraph,
-		IGI3 = IGI2 ^ interface_vars := HeadVars,
-		IGI4 = IGI3 ^ interface_varset := VarSet,
-		PredInfo2 = PredInfo0 ^ inst_graph_info := IGI4
+            !:IG = !.IG ^ implementation_inst_graph := InstGraph,
+            !:IG = !.IG ^ interface_inst_graph := InstGraph,
+            !:IG = !.IG ^ interface_vars := HeadVars,
+            !:IG = !.IG ^ interface_varset := VarSet,
+            PredInfo2 = PredInfo0 ^ inst_graph_info := !.IG
+        )
 	;
-		write_pred_progress_message(
-			"% Calculating HHF and inst graph for ",
+        write_pred_progress_message("% Calculating HHF and inst graph for ",
 			PredId, !.ModuleInfo, !IO),
 
 		pred_info_clauses_info(PredInfo0, ClausesInfo0),
-		hhf__process_clauses_info(Simple, !.ModuleInfo, ClausesInfo0,
+        process_clauses_info(Simple, !.ModuleInfo, ClausesInfo0,
 			ClausesInfo, ImplementationInstGraph),
 		pred_info_set_clauses_info(ClausesInfo, PredInfo0, PredInfo1),
-		IGI0 = PredInfo1 ^ inst_graph_info,
-		IGI1 = IGI0 ^ implementation_inst_graph :=
-				ImplementationInstGraph,
+        some [!IG] (
+            !:IG = PredInfo1 ^ inst_graph_info,
+            !:IG = !.IG ^ implementation_inst_graph := ImplementationInstGraph,
 
 		% AAA only for non-imported preds with no mode decls.
 		clauses_info_headvars(ClausesInfo, HeadVars),
 		clauses_info_varset(ClausesInfo, VarSet),
-		IGI2 = IGI1 ^ interface_inst_graph := ImplementationInstGraph,
-		solutions((pred(V::out) is nondet :-
+            !:IG = !.IG ^ interface_inst_graph := ImplementationInstGraph,
+            solutions(
+                (pred(V::out) is nondet :-
 				list__member(V0, HeadVars),
 				inst_graph__reachable(ImplementationInstGraph,
 				V0, V)
 			), InterfaceVars),
-		IGI3 = IGI2 ^ interface_vars := InterfaceVars,
-		IGI = IGI3 ^ interface_varset := VarSet,
+            !:IG = !.IG ^ interface_vars := InterfaceVars,
+            !:IG = !.IG ^ interface_varset := VarSet,
 
-		PredInfo2 = PredInfo1 ^ inst_graph_info := IGI
+            PredInfo2 = PredInfo1 ^ inst_graph_info := !.IG
+        )
 	),
 
 % 	pred_info_get_markers(PredInfo2, Markers),
@@ -102,7 +108,7 @@
 % 		InstGraphInfo0 = ( (PredInfo2 ^ inst_graph_info)
 % 			^ interface_inst_graph := InterfaceInstGraph )
 % 			^ interface_varset := VarSet,
-% 		map__foldl(hhf__process_proc(ModuleInfo0, HeadVars),
+%       map__foldl(process_proc(ModuleInfo0, HeadVars),
 % 			Procedures, InstGraphInfo0, InstGraphInfo1),
 % 
 % 		% Calculate interface vars.
@@ -119,7 +125,7 @@
 	PredInfo = PredInfo2, % AAA
 	module_info_set_pred_info(PredId, PredInfo, !ModuleInfo).
 
-hhf__process_clauses_info(Simple, ModuleInfo, !ClausesInfo, InstGraph) :-
+process_clauses_info(Simple, ModuleInfo, !ClausesInfo, InstGraph) :-
 	clauses_info_varset(!.ClausesInfo, VarSet0),
 	clauses_info_vartypes(!.ClausesInfo, VarTypes0),
 	inst_graph__init(VarTypes0 ^ keys, InstGraph0),
@@ -136,7 +142,7 @@
 	%	Info1 = Info0
 	%;
 	%	Simple = no,
-		list__map_foldl(hhf__process_clause(HeadVars),
+        list__map_foldl(process_clause(HeadVars),
 			Clauses0, Clauses, Info0, Info1)
 	),
 
@@ -147,8 +153,12 @@
 	% Info = Info1,
 
 	Info = hhf_info(InstGraph1, VarSet, VarTypes),
-	( Simple = yes, inst_graph__init(VarTypes ^ keys, InstGraph)
-	; Simple = no,  InstGraph = InstGraph1
+    (
+        Simple = yes,
+        inst_graph__init(VarTypes ^ keys, InstGraph)
+    ;
+        Simple = no,
+        InstGraph = InstGraph1
 	),
 
 	% XXX do we need this (it slows things down a lot (i.e. uses 50%
@@ -166,15 +176,15 @@
 			vartypes	:: vartypes
 		).
 
-:- pred hhf__process_clause(list(prog_var)::in, clause::in, clause::out,
+:- pred process_clause(list(prog_var)::in, clause::in, clause::out,
 	hhf_info::in, hhf_info::out) is det.
 
-hhf__process_clause(_HeadVars, clause(ProcIds, Goal0, Lang, Context),
+process_clause(_HeadVars, clause(ProcIds, Goal0, Lang, Context),
 		clause(ProcIds, Goal, Lang, Context), !HI) :-
 	Goal0 = _ - GoalInfo0,
 	goal_info_get_nonlocals(GoalInfo0, NonLocals),
 
-	hhf__goal(NonLocals, Goal0, Goal, !HI).
+    process_goal(NonLocals, Goal0, Goal, !HI).
 % XXX We probably need to requantify, but it stuffs up the inst_graph to do
 % that.
 % 	VarSet1 = !.HI ^ varset,
@@ -184,88 +194,107 @@
 % 	!:HI = !.HI varset := VarSet,
 % 	!:HI = !.HI vartypes := VarTypes.
 
-:- pred hhf__goal(set(prog_var)::in, hlds_goal::in, hlds_goal::out,
+:- pred process_goal(set(prog_var)::in, hlds_goal::in, hlds_goal::out,
 	hhf_info::in, hhf_info::out) is det.
 
-hhf__goal(NonLocals, GoalExpr0 - GoalInfo, GoalExpr - GoalInfo, !HI) :-
-	hhf__goal_expr(NonLocals, GoalInfo, GoalExpr0, GoalExpr, !HI).
+process_goal(NonLocals, GoalExpr0 - GoalInfo, GoalExpr - GoalInfo, !HI) :-
+    process_goal_expr(NonLocals, GoalInfo, GoalExpr0, GoalExpr, !HI).
 
-:- pred hhf__goal_use_own_nonlocals(hlds_goal::in, hlds_goal::out,
+:- pred goal_use_own_nonlocals(hlds_goal::in, hlds_goal::out,
 	hhf_info::in, hhf_info::out) is det.
 
-hhf__goal_use_own_nonlocals(GoalExpr0 - GoalInfo, GoalExpr - GoalInfo, !HI) :-
+goal_use_own_nonlocals(GoalExpr0 - GoalInfo, GoalExpr - GoalInfo, !HI) :-
 	goal_info_get_nonlocals(GoalInfo, NonLocals),
-	hhf__goal_expr(NonLocals, GoalInfo, GoalExpr0, GoalExpr, !HI).
+    process_goal_expr(NonLocals, GoalInfo, GoalExpr0, GoalExpr, !HI).
 
-:- pred hhf__goal_expr(set(prog_var)::in, hlds_goal_info::in,
+:- pred process_goal_expr(set(prog_var)::in, hlds_goal_info::in,
 	hlds_goal_expr::in, hlds_goal_expr::out, hhf_info::in, hhf_info::out)
 	is det.
 
-hhf__goal_expr(NonLocals, _, conj(Goals0), conj(Goals), !HI) :-
-	list__map_foldl(hhf__goal(NonLocals), Goals0, Goals1, !HI),
-	flatten_conj(Goals1, Goals).
-hhf__goal_expr(_, _, call(A, B, C, D, E, F), call(A, B, C, D, E, F), !HI).
-hhf__goal_expr(_, _, generic_call(A, B, C, D), generic_call(A, B, C, D), !HI).
-hhf__goal_expr(_, _, switch(_, _, _), _, !HI) :-
-	error("hhf_goal_expr: found switch").
-hhf__goal_expr(_, _, foreign_proc(A,B,C,D,E,F), foreign_proc(A,B,C,D,E,F),
-		!HI).
-hhf__goal_expr(_, _, shorthand(_), _, !HI) :-
-	error("hhf_goal_expr: found shorthand").
-hhf__goal_expr(NonLocals, _, scope(Reason, Goal0), scope(Reason, Goal), !HI) :-
-	hhf__goal(NonLocals, Goal0, Goal, !HI).
-hhf__goal_expr(_, _, disj(Goals0), disj(Goals), !HI) :-
-	list__map_foldl(hhf__goal_use_own_nonlocals, Goals0, Goals, !HI).
-hhf__goal_expr(NonLocals, _, not(Goal0), not(Goal), !HI) :-
-	hhf__goal(NonLocals, Goal0, Goal, !HI).
-hhf__goal_expr(NonLocals, _, if_then_else(Vs, Cond0, Then0, Else0),
-		if_then_else(Vs, Cond, Then, Else), !HI) :-
-	hhf__goal(NonLocals, Cond0, Cond, !HI),
+process_goal_expr(NonLocals, GoalInfo, GoalExpr0, GoalExpr, !HI) :-
+    (
+        GoalExpr0 = unify(Var, RHS, Mode, Unif, Context),
+        process_unify(RHS, NonLocals, GoalInfo, Var, Mode, Unif, Context,
+            GoalExpr, !HI)
+    ;
+        GoalExpr0 = call(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0
+    ;
+        GoalExpr0 = generic_call(_, _, _, _),
+        GoalExpr = GoalExpr0
+    ;
+        GoalExpr0 = foreign_proc(_, _, _, _, _, _),
+        GoalExpr = GoalExpr0
+    ;
+        GoalExpr0 = conj(Goals0),
+        list__map_foldl(process_goal(NonLocals), Goals0, Goals1, !HI),
+        flatten_conj(Goals1, Goals),
+        GoalExpr = conj(Goals)
+    ;
+        GoalExpr0 = par_conj(Goals0),
+        list__map_foldl(process_goal(NonLocals), Goals0, Goals, !HI),
+        GoalExpr = par_conj(Goals)
+    ;
+        GoalExpr0 = disj(Goals0),
+        list__map_foldl(goal_use_own_nonlocals, Goals0, Goals, !HI),
+        GoalExpr = disj(Goals)
+    ;
+        GoalExpr0 = switch(_, _, _),
+        unexpected(this_file, "hhf_goal_expr: found switch")
+    ;
+        GoalExpr0 = scope(Reason, SubGoal0),
+        process_goal(NonLocals, SubGoal0, SubGoal, !HI),
+        GoalExpr = scope(Reason, SubGoal)
+    ;
+        GoalExpr0 = not(SubGoal0),
+        process_goal(NonLocals, SubGoal0, SubGoal, !HI),
+        GoalExpr = not(SubGoal)
+    ;
+        GoalExpr0 = if_then_else(Vs, Cond0, Then0, Else0),
+        process_goal(NonLocals, Cond0, Cond, !HI),
 	Then0 = ThenExpr0 - ThenInfo,
 	goal_info_get_nonlocals(ThenInfo, ThenNonLocals),
-	hhf__goal_expr(ThenNonLocals, ThenInfo, ThenExpr0, ThenExpr, !HI),
+        process_goal_expr(ThenNonLocals, ThenInfo, ThenExpr0, ThenExpr, !HI),
 	Then = ThenExpr - ThenInfo,
 	Else0 = ElseExpr0 - ElseInfo,
 	goal_info_get_nonlocals(ElseInfo, ElseNonLocals),
-	hhf__goal_expr(ElseNonLocals, ElseInfo, ElseExpr0, ElseExpr, !HI),
-	Else = ElseExpr - ElseInfo.
-hhf__goal_expr(NonLocals, _, par_conj(Goals0), par_conj(Goals), !HI) :-
-	list__map_foldl(hhf__goal(NonLocals), Goals0, Goals, !HI).
-hhf__goal_expr(NonLocals, GoalInfo, unify(Var, RHS, Mode, Unif, Context),
-		GoalExpr, !HI) :-
-	hhf__unify(RHS, NonLocals, GoalInfo, Var, Mode, Unif, Context,
-		GoalExpr, !HI).
+        process_goal_expr(ElseNonLocals, ElseInfo, ElseExpr0, ElseExpr, !HI),
+        Else = ElseExpr - ElseInfo,
+        GoalExpr = if_then_else(Vs, Cond, Then, Else)
+    ;
+        GoalExpr0 = shorthand(_),
+        unexpected(this_file, "hhf_goal_expr: found shorthand")
+    ).
 
-:- pred hhf__unify(unify_rhs::in, set(prog_var)::in, hlds_goal_info::in,
+:- pred process_unify(unify_rhs::in, set(prog_var)::in, hlds_goal_info::in,
 	prog_var::in, unify_mode::in, unification::in, unify_context::in,
 	hlds_goal_expr::out, hhf_info::in, hhf_info::out) is det.
 
-hhf__unify(var(Y), _, _, X, Mode, Unif, Context, GoalExpr, !HI) :-
+process_unify(var(Y), _, _, X, Mode, Unif, Context, GoalExpr, !HI) :-
 	GoalExpr = unify(X, var(Y), Mode, Unif, Context).
-hhf__unify(lambda_goal(A,B,C,D,E,F,G,H,LambdaGoal0), NonLocals, _, X, Mode,
+process_unify(lambda_goal(A,B,C,D,E,F,G,H,LambdaGoal0), NonLocals, _, X, Mode,
 		Unif, Context, GoalExpr, !HI) :-
-	hhf__goal(NonLocals, LambdaGoal0, LambdaGoal, !HI),
+    process_goal(NonLocals, LambdaGoal0, LambdaGoal, !HI),
 	GoalExpr = unify(X, lambda_goal(A,B,C,D,E,F,G,H,LambdaGoal), Mode,
 		Unif, Context).
-hhf__unify(functor(ConsId0, IsExistConstruct, ArgsA), NonLocals, GoalInfo0,
+process_unify(functor(ConsId0, IsExistConstruct, ArgsA), NonLocals, GoalInfo0,
 		X, Mode, Unif, Context, GoalExpr, !HI) :-
 	TypeOfX = !.HI ^ vartypes ^ det_elem(X),
 	qualify_cons_id(TypeOfX, ArgsA, ConsId0, _, ConsId),
 	InstGraph0 = !.HI ^ inst_graph,
 	map__lookup(InstGraph0, X, node(Functors0, MaybeParent)),
 	( map__search(Functors0, ConsId, ArgsB) ->
-		hhf__make_unifications(ArgsA, ArgsB, GoalInfo0, Mode, Unif,
-			Context, Unifications),
+        make_unifications(ArgsA, ArgsB, GoalInfo0, Mode, Unif, Context,
+            Unifications),
 		Args = ArgsB
 	;
-		hhf__add_unifications(ArgsA, NonLocals, GoalInfo0, Mode, Unif,
-			Context, Args, Unifications, !HI),
+        add_unifications(ArgsA, NonLocals, GoalInfo0, Mode, Unif, Context,
+            Args, Unifications, !HI),
 		InstGraph1 = !.HI ^ inst_graph,
 		map__det_insert(Functors0, ConsId, Args, Functors),
 		map__det_update(InstGraph1, X, node(Functors, MaybeParent),
 			InstGraph2),
-		list__foldl(inst_graph__set_parent(X), Args, InstGraph2,
-			InstGraph),
+        list__foldl(inst_graph__set_parent(X), Args, InstGraph2, InstGraph),
 		!:HI = !.HI ^ inst_graph := InstGraph
 	),
 	goal_info_get_nonlocals(GoalInfo0, GINonlocals0),
@@ -275,31 +304,29 @@
 		Mode, Unif, Context) - GoalInfo,
 	GoalExpr = conj([UnifyGoal | Unifications]).
 
-:- pred hhf__make_unifications(list(prog_var)::in, list(prog_var)::in,
+:- pred make_unifications(list(prog_var)::in, list(prog_var)::in,
 	hlds_goal_info::in, unify_mode::in, unification::in, unify_context::in,
 	hlds_goals::out) is det.
 
-hhf__make_unifications([], [], _, _, _, _, []).
-hhf__make_unifications([_|_], [], _, _, _, _, _) :-
+make_unifications([], [], _, _, _, _, []).
+make_unifications([_ | _], [], _, _, _, _, _) :-
 	error("hhf_make_unifications: length mismatch").
-hhf__make_unifications([], [_|_], _, _, _, _, _) :-
+make_unifications([], [_ | _], _, _, _, _, _) :-
 	error("hhf_make_unifications: length mismatch").
-hhf__make_unifications([A | As], [B | Bs], GI0, M, U, C,
+make_unifications([A | As], [B | Bs], GI0, M, U, C,
 		[unify(A, var(B), M, U, C) - GI | Us]) :-
 	goal_info_get_nonlocals(GI0, GINonlocals0),
 	GINonlocals = GINonlocals0 `set__insert` A `set__insert` B,
 	goal_info_set_nonlocals(GINonlocals, GI0, GI),
-	hhf__make_unifications(As, Bs, GI0, M, U, C, Us).
+    make_unifications(As, Bs, GI0, M, U, C, Us).
 
-:- pred hhf__add_unifications(list(prog_var)::in, set(prog_var)::in,
+:- pred add_unifications(list(prog_var)::in, set(prog_var)::in,
 	hlds_goal_info::in, unify_mode::in, unification::in, unify_context::in,
-	list(prog_var)::out, hlds_goals::out, hhf_info::in, hhf_info::out)
-	is det.
+    list(prog_var)::out, hlds_goals::out, hhf_info::in, hhf_info::out) is det.
 
-hhf__add_unifications([], _, _, _, _, _, [], [], !HI).
-hhf__add_unifications([A | As], NonLocals, GI0, M, U, C, [V | Vs], Goals,
-		!HI) :-
-	hhf__add_unifications(As, NonLocals, GI0, M, U, C, Vs, Goals0, !HI),
+add_unifications([], _, _, _, _, _, [], [], !HI).
+add_unifications([A | As], NonLocals, GI0, M, U, C, [V | Vs], Goals, !HI) :-
+    add_unifications(As, NonLocals, GI0, M, U, C, Vs, Goals0, !HI),
 	InstGraph0 = !.HI ^ inst_graph,
 	(
 		( 
@@ -315,8 +342,7 @@
 		map__lookup(VarTypes0, A, Type),
 		map__det_insert(VarTypes0, V, Type, VarTypes),
 		map__init(Empty),
-		map__det_insert(InstGraph0, V, node(Empty, top_level),
-			InstGraph),
+        map__det_insert(InstGraph0, V, node(Empty, top_level), InstGraph),
 		!:HI = !.HI ^ varset := VarSet,
 		!:HI = !.HI ^ vartypes := VarTypes,
 		!:HI = !.HI ^ inst_graph := InstGraph,
@@ -358,8 +384,7 @@
 		type_constructors(Type, ModuleInfo, Constructors),
 		type_to_ctor_and_args(Type, TypeId, _)
 	->
-		list__foldl(
-			maybe_add_cons_id(Var, ModuleInfo, BaseVars, TypeId),
+        list__foldl(maybe_add_cons_id(Var, ModuleInfo, BaseVars, TypeId),
 			Constructors, !HI)
 	;
 		true
@@ -417,8 +442,7 @@
 	;
 		map__lookup(InstGraph, Var0, node(_, parent(Var1))),
 		\+ Var1 `list__member` BaseVars,
-		find_var_with_type(Var1, Type, InstGraph, VarTypes, BaseVars,
-			Var)
+        find_var_with_type(Var1, Type, InstGraph, VarTypes, BaseVars, Var)
 	).
 
 :- pred same_type((type)::in, (type)::in) is semidet.
@@ -457,43 +481,51 @@
 
 % 	% Add the information from the procedure's mode declaration
 % 	% to the inst_graph.
-% :- pred hhf__process_proc(module_info::in, list(prog_var)::in, proc_id::in,
+% :- pred process_proc(module_info::in, list(prog_var)::in, proc_id::in,
 % 	proc_info::in, inst_graph::out, prog_varset::out) is det.
 % 
-% hhf__process_proc(ModuleInfo, HeadVars, _ProcId, ProcInfo, Info0, Info) :-
+% process_proc(ModuleInfo, HeadVars, _ProcId, ProcInfo, Info0, Info) :-
 % 	proc_info_argmodes(ProcInfo, ArgModes),
 % 
 % 	mode_list_get_initial_insts(ArgModes, ModuleInfo, InstsI),
 % 	assoc_list__from_corresponding_lists(HeadVars, InstsI, VarInstsI),
-% 	list__foldl(hhf__process_arg(ModuleInfo), VarInstsI, Info0, Info),
+%   list__foldl(process_arg(ModuleInfo), VarInstsI, Info0, Info),
 % 
 % 	mode_list_get_final_insts(ArgModes, ModuleInfo, InstsF),
 % 	assoc_list__from_corresponding_lists(HeadVars, InstsF, VarInstsF),
-% 	list__foldl(hhf__process_arg(ModuleInfo), VarInstsF, Info0, Info).
+%   list__foldl(process_arg(ModuleInfo), VarInstsF, Info0, Info).
 % 
-% :- pred hhf__process_arg(module_info::in, pair(prog_var, inst)::in,
+% :- pred process_arg(module_info::in, pair(prog_var, inst)::in,
 % 		inst_graph_info::in, inst_graph_info::out) is det.
 % 
-% hhf__process_arg(ModuleInfo, Var - Inst, Info0, Info) :-
+% process_arg(ModuleInfo, Var - Inst, Info0, Info) :-
 % 	map__init(Seen0),
-% 	hhf__process_arg_inst(ModuleInfo, Var, Seen0, Inst, Info0, Info).
+%   process_arg_inst(ModuleInfo, Var, Seen0, Inst, Info0, Info).
 % 
-% :- pred hhf__process_arg_inst(module_info::in, prog_var::in,
+% :- pred process_arg_inst(module_info::in, prog_var::in,
 % 		map(inst_name, prog_var)::in, inst::in, inst_graph_info::in,
 % 		inst_graph_info::out) is det.
 % 
-% hhf__process_arg_inst(ModuleInfo, Var, Seen0, Inst0, Info0, Info) :-
+% process_arg_inst(ModuleInfo, Var, Seen0, Inst0, Info0, Info) :-
 % 	( Inst0 = defined_inst(InstName) ->
 % 		map__det_insert(Seen0, InstName, Var, Seen),
 % 		inst_lookup(ModuleInfo, InstName, Inst),
-% 		hhf__process_arg_inst(Inst, ModuleInfo, Var, Seen, Info0, Info)
+%       process_arg_inst(Inst, ModuleInfo, Var, Seen, Info0, Info)
 % 	; Inst0 = bound(_, BoundInsts) ->
-% 		list__foldl(hhf__process_bound_inst(ModuleInfo, Var, Seen0),
+%       list__foldl(process_bound_inst(ModuleInfo, Var, Seen0),
 % 			BoundInts, Info0, Info)
 % 	;
 % 		Info = Info0
 % 	).
 % 
-% :- pred hhf__process_bound_inst(module_info::in, prog_var::in,
+% :- pred process_bound_inst(module_info::in, prog_var::in,
 % 		map(inst_name, prog_var)::in, bound_inst::in,
 % 		inst_graph_info::in, inst_graph_info::out) is det.
+
+%------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "hhf.m".
+
+%------------------------------------------------------------------------%
Index: compiler/hlds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds.m,v
retrieving revision 1.217
diff -u -b -r1.217 hlds.m
--- compiler/hlds.m	24 Mar 2005 13:33:32 -0000	1.217
+++ compiler/hlds.m	12 Oct 2005 07:51:58 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -49,8 +51,7 @@
 :- implementation.
 
 :- import_module libs.
-:- import_module check_hlds.		% needed for unify_proc__unify_proc_id,
-					% etc.
+:- import_module check_hlds.        % needed for unify_proc__unify_proc_id, etc
 :- import_module transform_hlds.	% needed for term_util, mmc_analysis
 
 :- end_module hlds.
Index: compiler/hlds_code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_code_util.m,v
retrieving revision 1.19
diff -u -b -r1.19 hlds_code_util.m
--- compiler/hlds_code_util.m	30 Sep 2005 08:08:21 -0000	1.19
+++ compiler/hlds_code_util.m	12 Oct 2005 08:10:01 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -7,7 +9,7 @@
 %
 % file: hlds_code_util.m.
 %
-% various utilities routines for use during hlds generation.
+% Various utilities routines for use during hlds generation.
 %
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -44,6 +46,7 @@
 :- import_module libs__globals.
 :- import_module libs__options.
 :- import_module mdbcomp__prim_data.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_io.
 :- import_module parse_tree__prog_out.
 :- import_module parse_tree__prog_type.
@@ -63,7 +66,9 @@
 	globals__lookup_bool_option(Globals, highlevel_data, HighLevelData),
 	HighLevelData = yes,
 	globals__get_target(Globals, Target),
-	( Target = il ; Target = java).
+    ( Target = il
+    ; Target = java
+    ).
 
 %-----------------------------------------------------------------------------%
 
@@ -90,7 +95,7 @@
 	proc(PredId, ProcId) = unshroud_pred_proc_id(ShroudedPredProcId).
 cons_id_to_tag(cons(Name, Arity), Type, ModuleInfo) = Tag :-
 	(
-			% handle the `character' type specially
+        % Handle the `character' type specially.
 		Type = builtin(character),
 		Name = unqualified(ConsName),
 	 	string__char_to_string(Char, ConsName)
@@ -98,44 +103,42 @@
 		char__to_int(Char, CharCode),
 		Tag = int_constant(CharCode)
 	;
-		% Tuples do not need a tag. Note that unary tuples are not
-		% treated as no_tag types. There's no reason why they
-		% couldn't be, it's just not worth the effort.
+        % Tuples do not need a tag. Note that unary tuples are not treated
+        % as no_tag types. There's no reason why they couldn't be, it's just
+        % not worth the effort.
 		type_is_tuple(Type, _)
 	->
 		Tag = single_functor
 	;
-			% Use the type to determine the type_ctor
+        % Use the type to determine the type_ctor.
 		( type_to_ctor_and_args(Type, TypeCtor0, _) ->
 			TypeCtor = TypeCtor0
 		;
-			% the type-checker should ensure that this never happens
-			error("cons_id_to_tag: invalid type")
+            % The type-checker should ensure that this never happens.
+            unexpected(this_file, "cons_id_to_tag: invalid type")
 		),
-			% Given the type_ctor, lookup up the constructor tag
-			% table for that type
+
+        % Given the type_ctor, lookup up the constructor tag table
+        % for that type.
 		module_info_get_type_table(ModuleInfo, TypeTable),
 		map__lookup(TypeTable, TypeCtor, TypeDefn),
 		hlds_data__get_type_defn_body(TypeDefn, TypeBody),
-		(
-			ConsTable0 = TypeBody ^ du_type_cons_tag_values
-		->
+        ( ConsTable0 = TypeBody ^ du_type_cons_tag_values ->
 			ConsTable = ConsTable0
 		;
-			% this should never happen
-			error("cons_id_to_tag: type is not d.u. type?")
+            unexpected(this_file, "cons_id_to_tag: type is not d.u. type?")
 		),
-			% Finally look up the cons_id in the table
+
+        % Finally look up the cons_id in the table.
 		map__lookup(ConsTable, cons(Name, Arity), Tag)
 	).
 
 %-----------------------------------------------------------------------------%
 
-	% Note that for historical reasons, builtin types
-	% are treated as being unqualified (`int') rather than
-	% being qualified (`builtin:int') at this point.
-
 make_instance_string(InstanceTypes, InstanceString) :-
+    % Note that for historical reasons, builtin types are treated as being
+    % unqualified (`int') rather than being qualified (`builtin.int')
+    % at this point.
 	list__map(type_to_string, InstanceTypes, InstanceStrings),
 	string__append_list(InstanceStrings, InstanceString).
 
@@ -144,14 +147,17 @@
 type_to_string(Type, String) :-
 	( type_to_ctor_and_args(Type, TypeCtor, _) ->
 		TypeCtor = TypeName - TypeArity,
-		mdbcomp__prim_data__sym_name_to_string(TypeName, "__", 
-			TypeNameString),
+        sym_name_to_string(TypeName, "__", TypeNameString),
 		string__int_to_string(TypeArity, TypeArityString),
-		string__append_list(
-			[TypeNameString, "__arity", TypeArityString, "__"],
-			String)
+        String = TypeNameString ++ "__arity" ++ TypeArityString ++ "__"
 	;
-		error("type_to_string: invalid type")
+        unexpected(this_file, "type_to_string: invalid type")
 	).
+
+%----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "hlds_code_util.m".
 
 %----------------------------------------------------------------------------%
Index: compiler/hlds_error_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_error_util.m,v
retrieving revision 1.10
diff -u -b -r1.10 hlds_error_util.m
--- compiler/hlds_error_util.m	15 Apr 2005 15:14:27 -0000	1.10
+++ compiler/hlds_error_util.m	12 Oct 2005 07:56:05 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1997-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -131,23 +133,19 @@
 	% We need to strip off the extra type_info arguments inserted at the
 	% front by polymorphism.m - we only want the last `Arity' of them.
 	( list__drop(NumArgModes - Arity, ArgModes0, ArgModes) ->
-		strip_builtin_qualifiers_from_mode_list(ArgModes,
-			StrippedArgModes)
+        strip_builtin_qualifiers_from_mode_list(ArgModes, StrippedArgModes)
 	;
 		error("describe_one_pred_name_mode: bad argument list")
 	),
 	(
 		PredOrFunc = predicate,
-		ArgModesPart =
-			arg_modes_to_string(InstVarSet, StrippedArgModes)
+        ArgModesPart = arg_modes_to_string(InstVarSet, StrippedArgModes)
 	;
 		PredOrFunc = function,
 		pred_args_to_func_args(StrippedArgModes, FuncArgModes,
 			FuncRetMode),
-		ArgModesPart =
-			arg_modes_to_string(InstVarSet, FuncArgModes) ++
-			" = " ++
-			mercury_mode_to_string(FuncRetMode, InstVarSet)
+        ArgModesPart = arg_modes_to_string(InstVarSet, FuncArgModes)
+            ++ " = " ++ mercury_mode_to_string(FuncRetMode, InstVarSet)
 	),
 	string__append_list([
 		"`",
@@ -158,14 +156,13 @@
 	Pieces = [words(Descr)].
 
 describe_several_pred_names(Module, ShouldModuleQualify, PredIds) = Pieces :-
-	PiecesList = list__map(
-		describe_one_pred_name(Module, ShouldModuleQualify), PredIds),
+    PiecesList = list__map(describe_one_pred_name(Module, ShouldModuleQualify),
+        PredIds),
 	Pieces = component_lists_to_pieces(PiecesList).
 
 describe_one_proc_name(Module, ShouldModuleQualify, proc(PredId, ProcId))
 		= Pieces :-
-	PredPieces = describe_one_pred_name(Module, ShouldModuleQualify,
-		PredId),
+    PredPieces = describe_one_pred_name(Module, ShouldModuleQualify, PredId),
 	proc_id_to_int(ProcId, ProcIdInt),
 	string__int_to_string(ProcIdInt, ProcIdStr),
 	Pieces = PredPieces ++ [words("mode"), words(ProcIdStr)].
@@ -179,8 +176,8 @@
 		PredId, InstVarSet, ArgModes).
 
 describe_several_proc_names(Module, ShouldModuleQualify, PPIds) = Pieces :-
-	PiecesList = list__map(
-		describe_one_proc_name(Module, ShouldModuleQualify), PPIds),
+    PiecesList = list__map(describe_one_proc_name(Module, ShouldModuleQualify),
+        PPIds),
 	Pieces = component_lists_to_pieces(PiecesList).
 
 describe_one_call_site(Module, ShouldModuleQualify, PPId - Context) = Pieces :-
@@ -193,8 +190,8 @@
 		[words("at"), fixed(FileName ++ ":" ++ LineNumberStr)].
 
 describe_several_call_sites(Module, ShouldModuleQualify, Sites) = Pieces :-
-	PiecesList = list__map(
-		describe_one_call_site(Module, ShouldModuleQualify), Sites),
+    PiecesList = list__map(describe_one_call_site(Module, ShouldModuleQualify),
+        Sites),
 	Pieces = component_lists_to_pieces(PiecesList).
 
 :- func module_qualification(module_name, should_module_qualify) = string.
@@ -202,8 +199,7 @@
 module_qualification(ModuleName, ShouldModuleQualify) = ModuleQualification :-
 	(
 		ShouldModuleQualify = should_module_qualify,
-		mdbcomp__prim_data__sym_name_to_string(ModuleName, 
-			ModuleNameString),
+        sym_name_to_string(ModuleName, ModuleNameString),
 		ModuleQualification = string__append(ModuleNameString, ".")
 	;
 		ShouldModuleQualify = should_not_module_qualify,
Index: compiler/inst_graph.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inst_graph.m,v
retrieving revision 1.5
diff -u -b -r1.5 inst_graph.m
--- compiler/inst_graph.m	22 Mar 2005 06:40:01 -0000	1.5
+++ compiler/inst_graph.m	12 Oct 2005 08:00:39 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -45,61 +47,75 @@
 
 	;	parent(prog_var).
 		% The variable in whose node this maybe_parent value occurs
-		% does appear on the right hand side of a var-functor
-		% unification: the argument of parent identifies
-		% the variable on the left hand side. The definition of
-		% hyperhomogeneous form guarantees that this variable is
-		% unique.
+            % does appear on the right hand side of a var-functor unification:
+            % the argument of parent identifies the variable on the left hand
+            % side. The definition of hyperhomogeneous form guarantees that
+            % this variable is unique.
 
 	% Initialise an inst_graph. Adds a node for each variable, and
 	% initializes each node to have no parents and no children.
+    %
 :- pred init(list(prog_var)::in, inst_graph::out) is det.
 
-	% set_parent(Parent, Child, Graph0, Graph)
-	%	Sets Parent to be the parent node of Child.  Aborts if
-	%	Child already has a parent.
+    % set_parent(Parent, Child, Graph0, Graph):
+    %
+    % Sets Parent to be the parent node of Child. Aborts if Child
+    % already has a parent.
+    %
 :- pred set_parent(prog_var::in, prog_var::in, inst_graph::in, inst_graph::out)
 	is det.
 
-	% top_level_node(InstGraph, VarA, VarB)
-	%	Succeeds iff VarB is the top_level node reachable
-	%	from VarA in InstGraph.
+    % top_level_node(InstGraph, VarA, VarB):
+    %
+    % Succeeds iff VarB is the top_level node reachable from VarA in InstGraph.
+    %
 :- pred top_level_node(inst_graph::in, prog_var::in, prog_var::out) is det.
 
-	% descendant(InstGraph, VarA, VarB)
+    % descendant(InstGraph, VarA, VarB):
+    %
 	%	Succeeds iff VarB is a descendant of VarA in InstGraph.
+    %
 :- pred descendant(inst_graph::in, prog_var::in, prog_var::out) is nondet.
 
-	% reachable(InstGraph, VarA, VarB)
+    % reachable(InstGraph, VarA, VarB):
+    %
 	%	Succeeds iff VarB is a descendant of VarA in InstGraph,
 	%	or if VarB *is* VarA.
+    %
 :- pred reachable(inst_graph::in, prog_var::in, prog_var::out) is multi.
 
-	% reachable(InstGraph, Vars, VarB)
-	%	Succeeds iff VarB is a descendant in InstGraph of any VarA
-	%	in Vars.
+    % reachable(InstGraph, Vars, VarB):
+    %
+    % Succeeds iff VarB is a descendant in InstGraph of any VarA in Vars.
+    %
 :- pred reachable_from_list(inst_graph::in, list(prog_var)::in, prog_var::out)
 	is nondet.
 
-	% foldl_reachable(Pred, InstGraph, Var, Acc0, Acc):
+    % foldl_reachable(Pred, InstGraph, Var, !Acc):
+    %
 	%	Performs a foldl operation over all variables V for which
 	%	reachable(InstGraph, Var, V) is true.
+    %
 :- pred foldl_reachable(pred(prog_var, T, T)::pred(in, in, out) is det,
 	inst_graph::in, prog_var::in, T::in, T::out) is det.
 
-	% foldl_reachable_from_list(Pred, InstGraph, Vars, Acc0, Acc):
+    % foldl_reachable_from_list(Pred, InstGraph, Vars, !Acc):
+    %
 	%	Performs a foldl operation over all variables V for which
 	%	reachable_from_list(InstGraph, Vars, V) is true.
+    %
 :- pred foldl_reachable_from_list(
 	pred(prog_var, T, T)::pred(in, in, out) is det,
 	inst_graph::in, list(prog_var)::in, T::in, T::out) is det.
 
 	% A version of foldl_reachable with two accumulators.
+    %
 :- pred foldl_reachable2(
 	pred(prog_var, T, T, U, U)::pred(in, in, out, in, out) is det,
 	inst_graph::in, prog_var::in, T::in, T::out, U::in, U::out) is det.
 
 	% A version of foldl_reachable_from_list with two accumulators.
+    %
 :- pred foldl_reachable_from_list2(
 	pred(prog_var, T, T, U, U)::pred(in, in, out, in, out) is det,
 	inst_graph::in, list(prog_var)::in, T::in, T::out, U::in, U::out)
@@ -117,29 +133,33 @@
 
 	% Merge two inst_graphs by renaming the variables in the second
 	% inst_graph.  Also return the variable substitution map.
+    %
 :- pred merge(inst_graph::in, prog_varset::in, inst_graph::in, prog_varset::in,
 	inst_graph::out, prog_varset::out, map(prog_var, prog_var)::out)
 	is det.
 
 % 	% Join two inst_graphs together by taking the maximum unrolling
 % 	% of the type tree of each variable from the two graphs.
+%   %
 % :- pred join(inst_graph::in, prog_varset::in, inst_graph::in,
 % 	prog_varset::in, inst_graph::out, prog_varset::out) is det.
 
 	% Print the given inst_graph over the given varset in a format
 	% suitable for debugging output.
+    %
 :- pred dump(inst_graph::in, prog_varset::in, io::di, io::uo) is det.
 
-	% XXX this should probably go in list.m.
+    % XXX This should probably go in list.m.
+    %
 :- pred corresponding_members(list(T)::in, list(U)::in, T::out, U::out)
 	is nondet.
 
 	% Values of this type are intended to contain all the info related
-	% to inst_graphs for a predicate that needs to be stored in the
-	% pred_info.
+    % to inst_graphs for a predicate that needs to be stored in the pred_info.
 :- type inst_graph_info.
 
 	% Create an empty inst_graph_info.
+    %
 :- func inst_graph_info_init = inst_graph_info.
 
 :- func interface_inst_graph(inst_graph_info) = inst_graph.
@@ -182,8 +202,8 @@
 set_parent(Parent, Child, InstGraph0, InstGraph) :-
 	map__lookup(InstGraph0, Child, node(Functors, MaybeParent0)),
 	( MaybeParent0 = top_level ->
-		map__det_update(InstGraph0, Child,
-			node(Functors, parent(Parent)), InstGraph)
+        map__det_update(InstGraph0, Child, node(Functors, parent(Parent)),
+            InstGraph)
 	;
 		error("set_parent: node already has parent")
 	).
@@ -215,8 +235,7 @@
 		( Arg `set__member` Seen ->
 			fail
 		;
-			descendant_2(InstGraph, Seen `set__insert` Arg,
-				Arg, Descendant)
+            descendant_2(InstGraph, Seen `set__insert` Arg, Arg, Descendant)
 		)
 	).
 
@@ -229,7 +248,7 @@
 	reachable(InstGraph, Var, Reachable).
 
 foldl_reachable(P, InstGraph, Var, !Acc) :-
-	% a possible alternate implementation:
+    % A possible alternate implementation:
 	% aggregate(reachable(InstGraph, Var), P, !Acc).
 	foldl_reachable_aux(P, InstGraph, Var, set__init, !Acc).
 
@@ -244,8 +263,7 @@
 			( Arg `set__member` Seen ->
 				LAcc = LAcc0
 			;
-				foldl_reachable_aux(P,
-					InstGraph, Arg, Seen `set__insert` Arg,
+                foldl_reachable_aux(P, InstGraph, Arg, Seen `set__insert` Arg,
 					LAcc0, LAcc)
 			)
 		), Args, MAcc0, MAcc)
@@ -255,10 +273,9 @@
 	list__foldl(foldl_reachable(P, InstGraph), Vars).
 
 foldl_reachable2(P, InstGraph, Var, !Acc1, !Acc2) :-
-	% a possible alternate implementation:
+    % A possible alternate implementation:
 	% aggregate2(reachable(InstGraph, Var), P, !Acc1, !Acc2).
-	foldl_reachable_aux2(P, InstGraph, Var, set__init,
-		!Acc1, !Acc2).
+    foldl_reachable_aux2(P, InstGraph, Var, set__init, !Acc1, !Acc2).
 
 :- pred foldl_reachable_aux2(
 	pred(prog_var, T, T, U, U)::pred(in, in, out, in, out) is det,
@@ -276,8 +293,7 @@
 				LAccA = LAccA0,
 				LAccB = LAccB0
 			;
-				foldl_reachable_aux2(P,
-					InstGraph, Arg, Seen `set__insert` Arg,
+                foldl_reachable_aux2(P, InstGraph, Arg, Seen `set__insert` Arg,
 					LAccA0, LAccA, LAccB0, LAccB)
 			)
 		), Args, MAcc10, MAcc1, MAcc20, MAcc2)
@@ -300,7 +316,10 @@
 
 corresponding_nodes_2(_, _, _, _, A, B, A, B).
 corresponding_nodes_2(InstGraphA, InstGraphB, SeenA0, SeenB0, A, B, V, W) :-
-	not ( A `set__member` SeenA0, B `set__member` SeenB0 ),
+    not (
+        A `set__member` SeenA0,
+        B `set__member` SeenB0
+    ),
 
 	map__lookup(InstGraphA, A, node(FunctorsA, _)),
 	map__lookup(InstGraphB, B, node(FunctorsB, _)),
@@ -311,19 +330,19 @@
 	( map__member(FunctorsA, ConsId, ArgsA) ->
 		( map__is_empty(FunctorsB) ->
 			list__member(V0, ArgsA),
-			corresponding_nodes_2(InstGraphA,
-				InstGraphB, SeenA, SeenB, V0, B, V, W)
+            corresponding_nodes_2(InstGraphA, InstGraphB, SeenA, SeenB,
+                V0, B, V, W)
 		;
 			map__search(FunctorsB, ConsId, ArgsB),
 			corresponding_members(ArgsA, ArgsB, V0, W0),
-			corresponding_nodes_2(InstGraphA,
-				InstGraphB, SeenA, SeenB, V0, W0, V, W)
+            corresponding_nodes_2(InstGraphA, InstGraphB, SeenA, SeenB,
+                V0, W0, V, W)
 		)
 	;
 		map__member(FunctorsB, _ConsId, ArgsB),
 		list__member(W0, ArgsB),
-		corresponding_nodes_2(InstGraphA, InstGraphB,
-			SeenA, SeenB, A, W0, V, W)
+        corresponding_nodes_2(InstGraphA, InstGraphB, SeenA, SeenB,
+            A, W0, V, W)
 	).
 
 corresponding_nodes_from_lists(InstGraphA, InstGraphB, VarsA, VarsB, V, W) :-
@@ -337,8 +356,7 @@
 merge(InstGraph0, VarSet0, NewInstGraph, NewVarSet, InstGraph, VarSet, Sub) :-
 	varset__merge_subst_without_names(VarSet0, NewVarSet, VarSet, Sub0),
 	(
-		map__map_values(
-			pred(_::in, term__variable(V)::in, V::out) is semidet,
+        map__map_values(pred(_::in, term__variable(V)::in, V::out) is semidet,
 			Sub0, Sub1)
 	->
 		Sub = Sub1
@@ -417,19 +435,22 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type inst_graph_info --->
-	inst_graph_info(
+:- type inst_graph_info
+    --->    inst_graph_info(
 		interface_inst_graph	:: inst_graph,
 					% Inst graph derived from the mode
 					% declarations, if there are any.
 					% If there are no mode declarations
 					% for the pred, this is the same as
 					% the implementation_inst_graph.
+
 		interface_vars		:: list(prog_var),
 					% Vars that appear in the head of the
 					% mode declaration constraint.
+
 		interface_varset	:: prog_varset,
 					% Varset used for interface_inst_graph.
+
 		implementation_inst_graph :: inst_graph
 					% Inst graph derived from the body of
 					% the predicate.
Index: compiler/layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout.m,v
retrieving revision 1.20
diff -u -b -r1.20 layout.m
--- compiler/layout.m	26 May 2005 00:17:02 -0000	1.20
+++ compiler/layout.m	12 Oct 2005 08:16:20 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -152,9 +154,8 @@
 	--->	proc_layout_exec_trace(
 			call_label_layout	:: layout_name,
 			proc_body_bytes		:: list(int),
-						% The procedure body
-						% represented as a list of
-						% bytecodes.
+                                        % The procedure body represented as
+                                        % a list of bytecodes.
 
 			maybe_table_info	:: maybe(layout_name),
 			head_var_nums		:: list(int),
@@ -166,9 +167,8 @@
 						% procedure's arity.
 
 			var_names		:: list(int),
-						% Each variable name is an
-						% offset into the module's
-						% string table.
+                                        % Each variable name is an offset into
+                                        % the module's string table.
 
 			max_var_num		:: int,
 			max_r_num		:: int,
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.53
diff -u -b -r1.53 layout_out.m
--- compiler/layout_out.m	5 Oct 2005 06:33:39 -0000	1.53
+++ compiler/layout_out.m	12 Oct 2005 08:41:10 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -31,53 +33,60 @@
 
 	% Given a Mercury representation of a layout structure, output its
 	% definition in the appropriate C global variable.
+    %
 :- pred output_layout_data_defn(layout_data::in, decl_set::in, decl_set::out,
 	io::di, io::uo) is det.
 
 	% Given the name of a layout structure, output the declaration
 	% of the C global variable which will hold it.
+    %
 :- pred output_layout_name_decl(layout_name::in, io::di, io::uo) is det.
 
-	% Given the name of a layout structure, output the declaration
-	% of the C global variable which will hold it, if it has
-	% not already been declared.
+    % Given the name of a layout structure, output the declaration of the C
+    % global variable which will hold it, if it has not already been declared.
 :- pred output_maybe_layout_name_decl(layout_name::in,
 	decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 	% Given a Mercury representation of a layout structure, output the
 	% declaration of the C global variable which will hold it, if it has
 	% not already been declared.
+    %
 :- pred output_maybe_layout_data_decl(layout_data::in,
 	decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 	% Given a reference to a layout structure, output the storage class
 	% (e.g. static), type and name of the global variable that will
-	% hold it. The bool says whether the output is part of the definition
-	% of that variable (this influences e.g. whether we output "extern"
-	% or not).
+    % hold it. The bool says whether the output is part of the definition of
+    % that variable (this influences e.g. whether we output "extern" or not).
+    %
 :- pred output_layout_name_storage_type_name(layout_name::in, bool::in,
 	io::di, io::uo) is det.
 
 	% Given a reference to a layout structure, output the name of the
 	% global variable that will hold it.
+    %
 :- pred output_layout_name(layout_name::in, io::di, io::uo) is det.
 
 	% Given a reference to a layout structure, return a bool that is true
 	% iff the layout structure contains code addresses.
+    %
 :- func layout_name_would_include_code_addr(layout_name) = bool.
 
 	% Given a label, return a string giving the name of the global variable
-	% containing the label layout structure that would be associated with
-	% it. Make_label_layout_name does not guarantee that the label *has*
-	% an associated label layout structure.
+    % containing the label layout structure that would be associated with it.
+    % Make_label_layout_name does not guarantee that the label *has* an
+    % associated label layout structure.
+    %
 :- func make_label_layout_name(label) = string.
 
 	% For a given procedure label, return whether the procedure is
 	% user-defined or part of a compiler-generated unify, compare or index
 	% predicate.
+    %
 :- func proc_label_user_or_uci(proc_label) = proc_layout_user_or_uci.
 
 	% Output a value of C type MR_PredFunc corrresponding to the argument.
+    %
 :- pred output_pred_or_func(pred_or_func::in, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
@@ -95,6 +104,7 @@
 :- import_module libs__options.
 :- import_module libs__trace_params.
 :- import_module ll_backend__code_util.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_data.
 :- import_module parse_tree__prog_foreign.
 :- import_module parse_tree__prog_out.
@@ -212,8 +222,8 @@
 	% This code should be kept in sync with make_label_layout_name/1 above.
 	io__write_string(mercury_data_prefix, !IO),
 	io__write_string("_label_layout__", !IO),
-	io__write_string(label_to_c_string(internal(LabelNum, ProcLabel),
-		yes), !IO).
+    io__write_string(label_to_c_string(internal(LabelNum, ProcLabel), yes),
+        !IO).
 output_layout_name(proc_layout(RttiProcLabel, _), !IO) :-
 	io__write_string(mercury_data_prefix, !IO),
 	io__write_string("_proc_layout__", !IO),
@@ -323,8 +333,7 @@
 	output_proc_label(ProcLabel, no, !IO).
 
 output_layout_name_storage_type_name(
-		label_layout(ProcLabel, LabelNum, LabelVars),
-		_BeingDefined, !IO) :-
+        label_layout(ProcLabel, LabelNum, LabelVars), _BeingDefined, !IO) :-
 	io__write_string("static const ", !IO),
 	io__write_string(label_vars_to_type(LabelVars), !IO),
 	io__write_string(" ", !IO),
@@ -515,8 +524,8 @@
 	io::di, io::uo) is det.
 
 output_label_layout_data_defn(ProcLabel, LabelNum, ProcLayoutAddr, MaybePort,
-		MaybeIsHidden, LabelNumberInModule, MaybeGoalPath,
-		MaybeVarInfo, !DeclSet, !IO) :-
+        MaybeIsHidden, LabelNumberInModule, MaybeGoalPath, MaybeVarInfo,
+        !DeclSet, !IO) :-
 	output_layout_decl(ProcLayoutAddr, !DeclSet, !IO),
 	(
 		MaybeIsHidden = yes(yes),
@@ -531,18 +540,17 @@
 	),
 	(
 		MaybeVarInfo = yes(VarInfo0),
-		VarInfo0 = label_var_info(EncodedVarCount1,
-			LocnsTypes0, VarNums0, TypeParams0),
+        VarInfo0 = label_var_info(EncodedVarCount1, LocnsTypes0, VarNums0,
+            TypeParams0),
 		output_rval_decls(LocnsTypes0, !DeclSet, !IO),
 		output_rval_decls(VarNums0, !DeclSet, !IO),
 		output_rval_decls(TypeParams0, !DeclSet, !IO),
 		LabelVars = label_has_var_info,
 		globals__io_lookup_bool_option(split_c_files, Split, !IO),
 		(
-			% With --split-c-files, the names of common cells
-			% can't be of the form mercury_common_<n> (they have to
-			% be module qualified), which contradicts the
-			% assumptions of the CCC and CC0 variants of the
+            % With --split-c-files, the names of common cells can't be of the
+            % form mercury_common_<n> (they have to be module qualified), which
+            % contradicts the assumptions of the CCC and CC0 variants of the
 			% MR_DEF_LL macro.
 			Split = no,
 			LocnsTypes0 = const(data_addr_const(LTDataAddr, no)),
@@ -551,8 +559,7 @@
 			VNDataAddr = data_addr(_, common(VNCellNum, _))
 		->
 			(
-				TypeParams0 =
-					const(data_addr_const(TPDataAddr, no)),
+                TypeParams0 = const(data_addr_const(TPDataAddr, no)),
 				TPDataAddr = data_addr(_, common(TPCellNum, _))
 			->
 				CommonChars = "CCC",
@@ -579,8 +586,8 @@
 			TypeParams1 = rval(TypeParams0)
 		),
 		Macro = "MR_DEF_LL" ++ HiddenChars ++ CommonChars,
-		MaybeVarInfoTuple = yes({EncodedVarCount1,
-			LocnsTypes1, VarNums1, TypeParams1})
+        MaybeVarInfoTuple = yes({EncodedVarCount1, LocnsTypes1, VarNums1,
+            TypeParams1})
 	;
 		MaybeVarInfo = no,
 		LabelVars = label_has_no_var_info,
@@ -628,6 +635,7 @@
 
 	% Output the rval in a context in which it is immediately cast to an
 	% address.
+    %
 :- pred output_rval_as_addr(rval::in, io::di, io::uo) is det.
 
 output_rval_as_addr(Rval, !IO) :-
@@ -672,38 +680,37 @@
 	Kind = maybe_proc_layout_and_more_kind(MaybeRest, ProcLabel),
 	(
 		MaybeRest = no_proc_id,
-		output_proc_layout_data_defn_start(RttiProcLabel, Kind,
-			Traversal, !IO),
+        output_proc_layout_data_defn_start(RttiProcLabel, Kind, Traversal,
+            !IO),
 		output_layout_no_proc_id_group(!IO),
 		output_proc_layout_data_defn_end(!IO)
 	;
 		MaybeRest = proc_id(MaybeProcStatic, MaybeExecTrace),
 		(
 			MaybeProcStatic = yes(ProcStatic),
-			output_proc_static_data_defn(RttiProcLabel, ProcStatic,
-				!DeclSet, !IO)
+            output_proc_static_data_defn(RttiProcLabel, ProcStatic, !DeclSet,
+                !IO)
 		;
 			MaybeProcStatic = no
 		),
 		(
 			MaybeExecTrace = yes(ExecTrace),
 			HeadVarNums = ExecTrace ^ head_var_nums,
-			output_proc_layout_head_var_nums(RttiProcLabel,
-				HeadVarNums, !DeclSet, !IO),
+            output_proc_layout_head_var_nums(RttiProcLabel, HeadVarNums,
+                !DeclSet, !IO),
 			VarNames = ExecTrace ^ var_names,
 			MaxVarNum = ExecTrace ^ max_var_num,
-			output_proc_layout_var_names(RttiProcLabel, VarNames,
-				MaxVarNum, !DeclSet, !IO),
-			output_layout_exec_trace_decls(RttiProcLabel,
-				ExecTrace, !DeclSet, !IO),
-			output_layout_exec_trace(RttiProcLabel, ExecTrace,
-				!DeclSet, !IO)
+            output_proc_layout_var_names(RttiProcLabel, VarNames, MaxVarNum,
+                !DeclSet, !IO),
+            output_layout_exec_trace_decls(RttiProcLabel, ExecTrace,
+                !DeclSet, !IO),
+            output_layout_exec_trace(RttiProcLabel, ExecTrace, !DeclSet, !IO)
 		;
 			MaybeExecTrace = no
 		),
 
-		output_proc_layout_data_defn_start(RttiProcLabel, Kind,
-			Traversal, !IO),
+        output_proc_layout_data_defn_start(RttiProcLabel, Kind, Traversal,
+            !IO),
 		Origin = RttiProcLabel ^ pred_info_origin,
 		output_layout_proc_id_group(ProcLabel, Origin, !IO),
 		(
@@ -712,8 +719,7 @@
 		;
 			MaybeExecTrace = yes(_),
 			io__write_string("&", !IO),
-			output_layout_name(
-				proc_layout_exec_trace(RttiProcLabel), !IO),
+            output_layout_name(proc_layout_exec_trace(RttiProcLabel), !IO),
 			io__write_string(",\n", !IO)
 		),
 		(
@@ -727,8 +733,8 @@
 		),
 		output_proc_layout_data_defn_end(!IO)
 	),
-	decl_set_insert(data_addr(
-		layout_addr(proc_layout(RttiProcLabel, Kind))), !DeclSet).
+    decl_set_insert(data_addr(layout_addr(proc_layout(RttiProcLabel, Kind))),
+        !DeclSet).
 
 :- func maybe_proc_layout_and_more_kind(maybe_proc_id_and_more,
 	proc_label) = proc_layout_kind.
@@ -896,8 +902,7 @@
 	ExecTrace = proc_layout_exec_trace(CallLabelLayout, ProcBodyBytes,
 		MaybeTableInfo, HeadVarNums, _VarNames, MaxVarNum,
 		MaxRegNum, MaybeFromFullSlot, MaybeIoSeqSlot, MaybeTrailSlot,
-		MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot, EffTraceLevel,
-		Flags),
+        MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot, EffTraceLevel, Flags),
 	(
 		ProcBodyBytes = []
 	;
@@ -916,7 +921,7 @@
 	( CallLabelLayout = label_layout(CallProcLabel, CallLabelNum, _) ->
 		output_label(internal(CallLabelNum, CallProcLabel), no, !IO)
 	;
-		error("output_layout_exec_trace: bad call layout")
+        unexpected(this_file, "output_layout_exec_trace: bad call layout")
 	),
 	io__write_string("),\n(const MR_Module_Layout *) &", !IO),
 	ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
@@ -928,8 +933,7 @@
 		io__write_string("NULL", !IO)
 	;
 		ProcBodyBytes = [_ | _],
-		output_layout_name(proc_layout_body_bytecode(RttiProcLabel),
-			!IO)
+        output_layout_name(proc_layout_body_bytecode(RttiProcLabel), !IO)
 	),
 	io__write_string(",\n", !IO),
 	(
@@ -1031,13 +1035,13 @@
 
 output_proc_layout_head_var_nums(ProcLabel, HeadVarNums, !DeclSet, !IO) :-
 	io__write_string("\n", !IO),
-	output_layout_name_storage_type_name(
-		proc_layout_head_var_nums(ProcLabel), yes, !IO),
+    output_layout_name_storage_type_name(proc_layout_head_var_nums(ProcLabel),
+        yes, !IO),
 	io__write_string(" = {\n", !IO),
 	(
 		HeadVarNums = [],
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("0\n", !IO)
 	;
 		HeadVarNums = [_ | _],
@@ -1055,21 +1059,21 @@
 	require(unify(VarNameCount, MaxVarNum),
 		"output_proc_layout_var_names: VarNameCount != MaxVarNum"),
 	io__write_string("\n", !IO),
-	output_layout_name_storage_type_name(proc_layout_var_names(ProcLabel),
-		yes, !IO),
+    output_layout_name_storage_type_name(proc_layout_var_names(ProcLabel), yes,
+        !IO),
 	io__write_string(" = {\n", !IO),
 	(
 		VarNames = [],
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("0\n", !IO)
 	;
 		VarNames = [_ | _],
 		list__foldl(output_number_in_vector, VarNames, !IO)
 	),
 	io__write_string("};\n", !IO),
-	decl_set_insert(data_addr(
-		layout_addr(proc_layout_var_names(ProcLabel))), !DeclSet).
+    decl_set_insert(data_addr(layout_addr(proc_layout_var_names(ProcLabel))),
+        !DeclSet).
 
 %-----------------------------------------------------------------------------%
 
@@ -1104,10 +1108,8 @@
 		ProcLabel = proc(DefiningModule, PredOrFunc, DeclaringModule,
 			PredName0, Arity, Mode),
 		PredName = origin_name(Origin, PredName0),
-		mdbcomp__prim_data__sym_name_to_string(DefiningModule,
-			DefiningModuleStr),
-		mdbcomp__prim_data__sym_name_to_string(DeclaringModule,
-			DeclaringModuleStr),
+        sym_name_to_string(DefiningModule, DefiningModuleStr),
+        sym_name_to_string(DeclaringModule, DeclaringModuleStr),
 		output_pred_or_func(PredOrFunc, !IO),
 		io__write_string(",\n", !IO),
 		quote_and_write_string(DeclaringModuleStr, !IO),
@@ -1126,10 +1128,8 @@
 		TypeCtor = qualified(TypeModule, TypeName) - TypeArity,
 		PredName0 = special_pred_name(SpecialPredId, TypeCtor),
 		PredName = origin_name(Origin, PredName0),
-		mdbcomp__prim_data__sym_name_to_string(DefiningModule,
-			DefiningModuleStr),
-		mdbcomp__prim_data__sym_name_to_string(TypeModule, 
-			TypeModuleStr),
+        sym_name_to_string(DefiningModule, DefiningModuleStr),
+        sym_name_to_string(TypeModule, TypeModuleStr),
 		quote_and_write_string(TypeName, !IO),
 		io__write_string(",\n", !IO),
 		quote_and_write_string(TypeModuleStr, !IO),
@@ -1155,11 +1155,9 @@
 				SeqNo > 1
 			->
 				string__format("lambda%d_%s_%d",
-					[i(SeqNo), s(FileName), i(LineNum)], 
-					Name)
+                    [i(SeqNo), s(FileName), i(LineNum)], Name)
 			;
-				string__format("lambda_%s_%d",
-					[s(FileName), i(LineNum)], Name)
+                string__format("lambda_%s_%d", [s(FileName), i(LineNum)], Name)
 			)
 		;
 			% If the lambda pred has a meaningful name, use it.
@@ -1315,13 +1313,12 @@
 	io__write_string(" = {\n", !IO),
 	(
 		ProcLayoutNames = [],
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("NULL\n", !IO)
 	;
 		ProcLayoutNames = [_ | _],
-		list__foldl(output_proc_layout_name_in_vector, ProcLayoutNames,
-			!IO)
+        list__foldl(output_proc_layout_name_in_vector, ProcLayoutNames, !IO)
 	),
 	io__write_string("};\n", !IO),
 	decl_set_insert(data_addr(layout_addr(VectorName)), !DeclSet).
@@ -1336,14 +1333,15 @@
 		output_proc_label(ProcLabel, no, !IO),
 		io__write_string(")\n", !IO)
 	;
-		error("output_proc_layout_name_in_vector: not proc layout")
+        unexpected(this_file,
+            "output_proc_layout_name_in_vector: not proc layout")
 	).
 
 %-----------------------------------------------------------------------------%
 
 	% The string table cannot be zero size; it must contain at least an
 	% empty string.
-
+    %
 :- pred output_module_string_table(module_name::in,
 	int::in, string_with_0s::in, decl_set::in, decl_set::out,
 	io::di, io::uo) is det.
@@ -1364,7 +1362,7 @@
 	% recursive. The maximum observed size of the module string so far has
 	% been just short of 64 kilobytes; writing that out in 256 batches of
 	% 256 characters minimizes maximum total stack requirements.
-
+    %
 :- pred output_module_string_table_chars_driver(int::in, int::in,
 	string_with_0s::in, io::di, io::uo) is det.
 
@@ -1374,8 +1372,8 @@
 		SubMaxIndex = int__min(MaxIndex, CurIndex + 255),
 		output_module_string_table_chars(CurIndex, SubMaxIndex,
 			StringWithNulls, !IO),
-		output_module_string_table_chars_driver(SubMaxIndex + 1,
-			MaxIndex, StringWithNulls, !IO)
+        output_module_string_table_chars_driver(SubMaxIndex + 1, MaxIndex,
+            StringWithNulls, !IO)
 	;
 		true
 	).
@@ -1415,13 +1413,14 @@
 	io__write_string("\n", !IO),
 	output_layout_name_storage_type_name(VectorName, yes, !IO),
 	io__write_string(" = {\n", !IO),
-	( FileLayoutNames = [] ->
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+    (
+        FileLayoutNames = [],
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("NULL\n", !IO)
 	;
-		list__foldl(output_layout_name_in_vector("&"), FileLayoutNames,
-			!IO)
+        FileLayoutNames = [_ | _],
+        list__foldl(output_layout_name_in_vector("&"), FileLayoutNames, !IO)
 	),
 	io__write_string("};\n", !IO),
 	decl_set_insert(data_addr(layout_addr(VectorName)), !DeclSet).
@@ -1479,11 +1478,13 @@
 	io__write_string("\n", !IO),
 	output_layout_name_storage_type_name(LayoutName, yes, !IO),
 	io__write_string(" = {\n", !IO),
-	( LineNumbers = [] ->
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+    (
+        LineNumbers = [],
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("0\n", !IO)
 	;
+        LineNumbers = [_ | _],
 		list__foldl(output_number_in_vector, LineNumbers, !IO)
 	),
 	io__write_string("};\n", !IO),
@@ -1499,11 +1500,13 @@
 	io__write_string("\n", !IO),
 	output_layout_name_storage_type_name(LayoutName, yes, !IO),
 	io__write_string(" = {\n", !IO),
-	( LabelAddrs = [] ->
-			% ANSI/ISO C doesn't allow empty arrays, so
-			% place a dummy value in the array.
+    (
+        LabelAddrs = [],
+        % ANSI/ISO C doesn't allow empty arrays, so place a dummy value
+        % in the array.
 		io__write_string("NULL\n", !IO)
 	;
+        LabelAddrs = [_ | _],
 		list__map(project_label_layout, LabelAddrs, Labels),
 		output_label_layout_addrs_in_vector(Labels, !IO)
 	),
@@ -1519,7 +1522,7 @@
 	->
 		Label = internal(LabelNum, ProcLabel)
 	;
-		error("project_label_layout: not label layout")
+        unexpected(this_file, "project_label_layout: not label layout")
 	).
 
 :- pred output_label_layout_addrs_in_vector(list(label)::in, io::di, io::uo)
@@ -1677,8 +1680,7 @@
 	(
 		CallSiteStatic = normal_call(Callee, TypeSubst,
 			FileName, LineNumber, GoalPath),
-		io__write_string("MR_normal_call, (MR_Proc_Layout *)\n&",
-			!IO),
+        io__write_string("MR_normal_call, (MR_Proc_Layout *)\n&", !IO),
 		CalleeProcLabel = make_proc_label_from_rtti(Callee),
 		CalleeUserOrUci = proc_label_user_or_uci(CalleeProcLabel),
 		output_layout_name(proc_layout(Callee,
@@ -1691,12 +1693,10 @@
 			io__write_string(""", ", !IO)
 		)
 	;
-		CallSiteStatic = special_call(FileName, LineNumber,
-			GoalPath),
+        CallSiteStatic = special_call(FileName, LineNumber, GoalPath),
 		io__write_string("MR_special_call, NULL, NULL, ", !IO)
 	;
-		CallSiteStatic = higher_order_call(FileName, LineNumber,
-			GoalPath),
+        CallSiteStatic = higher_order_call(FileName, LineNumber, GoalPath),
 		io__write_string("MR_higher_order_call, NULL, NULL, ", !IO)
 	;
 		CallSiteStatic = method_call(FileName, LineNumber, GoalPath),
@@ -1723,8 +1723,7 @@
 		CalleeProcLabel = make_proc_label_from_rtti(Callee),
 		CalleeUserOrUci = proc_label_user_or_uci(CalleeProcLabel),
 		output_maybe_layout_name_decl(proc_layout(Callee,
-			proc_layout_proc_id(CalleeUserOrUci)),
-			!DeclSet, !IO)
+            proc_layout_proc_id(CalleeUserOrUci)), !DeclSet, !IO)
 	;
 		CallSiteStatic = special_call(_, _, _)
 	;
@@ -1906,5 +1905,11 @@
 		PredOrFunc = function,
 		io__write_string("MR_FUNCTION", !IO)
 	).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "layout_out.m".
 
 %-----------------------------------------------------------------------------%
Index: compiler/libs.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/libs.m,v
retrieving revision 1.5
diff -u -b -r1.5 libs.m
--- compiler/libs.m	19 Apr 2005 02:47:15 -0000	1.5
+++ compiler/libs.m	12 Oct 2005 08:13:13 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2003, 2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
Index: compiler/ll_backend.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ll_backend.m,v
retrieving revision 1.11
diff -u -b -r1.11 ll_backend.m
--- compiler/ll_backend.m	13 Sep 2005 04:56:06 -0000	1.11
+++ compiler/ll_backend.m	12 Oct 2005 08:25:28 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002,2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
Index: compiler/ll_pseudo_type_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ll_pseudo_type_info.m,v
retrieving revision 1.12
diff -u -b -r1.12 ll_pseudo_type_info.m
--- compiler/ll_pseudo_type_info.m	22 Mar 2005 06:40:04 -0000	1.12
+++ compiler/ll_pseudo_type_info.m	12 Oct 2005 08:27:19 -0000
@@ -1,4 +1,6 @@
 %---------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%---------------------------------------------------------------------------%
 % Copyright (C) 2000,2002-2003, 2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -27,8 +29,8 @@
 :- import_module ll_backend__llds.
 :- import_module parse_tree__prog_data.
 
-	% ll_pseudo_type_info__construct_typed_pseudo_type_info(Type,
-	% 	NumUnivQTvars, ExistQVars, Rval, LldsType)
+    % construct_typed_pseudo_type_info(Type, NumUnivQTvars, ExistQVars,
+    %   Rval, LldsType):
 	%
 	% Given a Mercury type (`Type'), this predicate returns an rval
 	% (`Rval') giving the pseudo type info for that type, plus the
@@ -40,17 +42,16 @@
 	% or is the special value -1, meaning that all variables in the type
 	% are universally quantified. ExistQVars is the list of existentially
 	% quantified type variables of the constructor in question.
-
-:- pred ll_pseudo_type_info__construct_typed_llds_pseudo_type_info((type)::in,
-	int::in, existq_tvars::in, static_cell_info::in, static_cell_info::out,
+    %
+:- pred construct_typed_llds_pseudo_type_info((type)::in, int::in,
+    existq_tvars::in, static_cell_info::in, static_cell_info::out,
 	rval::out, llds_type::out) is det.
 
 	% This is the same as the previous predicate, but does not return
 	% the LLDS type.
-
-:- pred ll_pseudo_type_info__construct_llds_pseudo_type_info((type)::in,
-	int::in, existq_tvars::in, static_cell_info::in, static_cell_info::out,
-	rval::out) is det.
+    %
+:- pred construct_llds_pseudo_type_info((type)::in, int::in, existq_tvars::in,
+    static_cell_info::in, static_cell_info::out, rval::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -64,13 +65,13 @@
 :- import_module list.
 :- import_module std_util.
 
-ll_pseudo_type_info__construct_llds_pseudo_type_info(Type, NumUnivQTvars,
-		ExistQTvars, !StaticCellInfo, Pseudo) :-
-	ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type,
+construct_llds_pseudo_type_info(Type, NumUnivQTvars, ExistQTvars,
+        !StaticCellInfo, Pseudo) :-
+    construct_typed_llds_pseudo_type_info(Type,
 		NumUnivQTvars, ExistQTvars, !StaticCellInfo, Pseudo, _LldsType).
 
-ll_pseudo_type_info__construct_typed_llds_pseudo_type_info(Type, NumUnivQTvars,
-		ExistQTvars, !StaticCellInfo, PseudoRval, LldsType) :-
+construct_typed_llds_pseudo_type_info(Type, NumUnivQTvars, ExistQTvars,
+        !StaticCellInfo, PseudoRval, LldsType) :-
 	pseudo_type_info__construct_pseudo_type_info(Type, NumUnivQTvars,
 			ExistQTvars, Pseudo),
 	convert_pseudo_type_info(Pseudo, !StaticCellInfo, PseudoRval, LldsType).
@@ -110,8 +111,7 @@
 convert_plain_type_info(TypeInfo, !StaticCellInfo, Rval, LldsType) :-
 	(
 		TypeInfo = plain_arity_zero_type_info(RttiTypeCtor),
-		DataAddr = rtti_addr(
-			ctor_rtti_id(RttiTypeCtor, type_info(TypeInfo))),
+        DataAddr = rtti_addr(ctor_rtti_id(RttiTypeCtor, type_info(TypeInfo))),
 		Rval = const(data_addr_const(DataAddr, no)),
 		LldsType = data_ptr
 	;
@@ -167,6 +167,6 @@
 		convert_plain_type_info(A, SCI0, SCI, AR, _LldsType)
 	), Args, ArgRvals1, !StaticCellInfo),
 	list__append(ArgRvals0, ArgRvals1, ArgRvals),
-	add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals],
-		DataAddr, !StaticCellInfo),
+    add_static_cell_natural_types([TypeCtorInfoRval | ArgRvals], DataAddr,
+        !StaticCellInfo),
 	Rval = const(data_addr_const(DataAddr, no)).
Index: compiler/lookup_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lookup_switch.m,v
retrieving revision 1.55
diff -u -b -r1.55 lookup_switch.m
--- compiler/lookup_switch.m	22 Mar 2005 06:40:05 -0000	1.55
+++ compiler/lookup_switch.m	12 Oct 2005 08:37:30 -0000
@@ -1,22 +1,25 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1996-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % lookup_switch.m
-
+% Author: conway.
+%
 % For switches on atomic types in which the cases contain only the construction
 % of constants, generate code which just assigns the values of the output
 % variables by indexing into an array of values for each output variable.
-
+%
 % For switches that can fail, the generated code does a range check on the
 % index, and then does a lookup in a bit-vector to see if there is a value
 % for the appropriate case. If there is, then it does a lookup (using the
 % field macro) in the array of results. The array is padded with "0"s for
 % cases that are not covered. This is fine, since we do the lookup after
 % we check the bit-vector for the appropriate case.
-
+%
 % The current implementation works out whether or not it can do a lookup
 % switch by generating code for each case and looking to see that no code
 % got generated (i.e. only the code generation state got modified) and that
@@ -24,17 +27,15 @@
 % quite inefficient because it does the work of generating code for the cases
 % and then may throw it away if a subsequent case generates actual code, or
 % non constant outputs.
-
+%
 % A potential improvement would be to make a single array for each switch,
 % since putting the values produced for each tag value side-by-side in
 % memory will tend to lead to fewer cache misses.
-
+%
 % The number of bits per word is taken from the bits_per_word option which
 % uses a flag in the mc script with a value from configuration. This is
 % used when generating bit-vectors.
-
-% Author: conway.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module ll_backend__lookup_switch.
@@ -59,15 +60,15 @@
 
 :- type rval_map == map(prog_var, list(pair(int, rval))).
 
-:- pred lookup_switch__is_lookup_switch(prog_var::in, cases_list::in,
+:- pred is_lookup_switch(prog_var::in, cases_list::in,
 	hlds_goal_info::in, can_fail::in, int::in, abs_store_map::in,
 	branch_end::in, branch_end::out, code_model::in, int::out, int::out,
 	can_fail::out, can_fail::out, list(prog_var)::out, case_consts::out,
 	maybe(set(prog_var))::out, code_info::in, code_info::out) is semidet.
 
 	% Generate code for a switch using a lookup table.
-
-:- pred lookup_switch__generate(prog_var::in, list(prog_var)::in,
+    %
+:- pred generate_lookup_switch(prog_var::in, list(prog_var)::in,
 	case_consts::in, int::in, int::in, can_fail::in, can_fail::in,
 	maybe(set(prog_var))::in, abs_store_map::in, branch_end::in,
 	code_tree::out, code_info::in, code_info::out) is det.
@@ -87,6 +88,7 @@
 :- import_module ll_backend__dense_switch.
 :- import_module ll_backend__exprn_aux.
 :- import_module ll_backend__global_data.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_data.
 
 :- import_module assoc_list.
@@ -96,28 +98,26 @@
 
 	% Most of this predicate is taken from dense_switch.m
 
-	% We need the code_info structure to generate code for the cases to
-	% get the constants (if they exist). We can't throw it away at the
-	% end because we may have allocated some new static ground term labels.
-lookup_switch__is_lookup_switch(CaseVar, TaggedCases, GoalInfo, SwitchCanFail,
+is_lookup_switch(CaseVar, TaggedCases, GoalInfo, SwitchCanFail,
 		ReqDensity, StoreMap, !MaybeEnd, CodeModel,
 		FirstVal, LastVal, NeedRangeCheck, NeedBitVecTest, OutVars,
 		CaseValues, MLiveness, !CI) :-
+    % We need the code_info structure to generate code for the cases to
+    % get the constants (if they exist). We can't throw it away at the
+    % end because we may have allocated some new static ground term labels.
 
-		% Since lookup switches rely on static ground terms to
-		% work efficiently, there is no point in using a lookup
-		% switch if static-ground-terms are not enabled. Well,
-		% actually, it is possible that they might be a win in
-		% some circumstances, but it would take a pretty complex
-		% heuristic to get it right, so, lets just use a simple
-		% one - no static ground terms, no lookup switch.
+    % Since lookup switches rely on static ground terms to work efficiently,
+    % there is no point in using a lookup switch if static-ground-terms are
+    % not enabled. Well, actually, it is possible that they might be a win in
+    % some circumstances, but it would take a pretty complex heuristic to get
+    % it right, so, lets just use a simple one - no static ground terms,
+    % no lookup switch.
 	code_info__get_globals(!.CI, Globals),
 	globals__lookup_bool_option(Globals, static_ground_terms, yes),
 
-	% We want to generate a lookup switch for any switch
-	% that is dense enough - we don't care how many cases
-	% it has. A memory lookup tends to be cheaper than
-	% a branch.
+    % We want to generate a lookup switch for any switch that is dense enough
+    % - we don't care how many cases it has. A memory lookup tends to be
+    % cheaper than a branch.
 	list__length(TaggedCases, NumCases),
 	TaggedCases = [FirstCase | _],
 	FirstCase = case(_, int_constant(FirstCaseVal), _, _),
@@ -128,9 +128,8 @@
 	dense_switch__calc_density(NumCases, Range, Density),
 	Density > ReqDensity,
 
-	% If there are going to be no gaps in the lookup
-	% table then we won't need a bitvector test to see
-	% if this switch has a value for this case.
+    % If there are going to be no gaps in the lookup table then we won't need
+    % a bitvector test to see if this switch has a value for this case.
 	( NumCases = Range ->
 		NeedBitVecTest0 = cannot_fail
 	;
@@ -138,20 +137,17 @@
 	),
 	(
 		SwitchCanFail = can_fail,
-		% For semidet switches, we normally need to check that
-		% the variable is in range before we index into the jump table.
-		% However, if the range of the type is sufficiently small,
-		% we can make the jump table large enough to hold all
-		% of the values for the type, but then we will need to do the
-		% bitvector test.
+        % For semidet switches, we normally need to check that the variable
+        % is in range before we index into the jump table. However, if the
+        % range of the type is sufficiently small, we can make the jump table
+        % large enough to hold all of the values for the type, but then we
+        % will need to do the bitvector test.
 		Type = code_info__variable_type(!.CI, CaseVar),
 		code_info__get_module_info(!.CI, ModuleInfo),
 		classify_type(ModuleInfo, Type) = TypeCategory,
 		(
-			dense_switch__type_range(!.CI, TypeCategory, Type,
-				TypeRange),
-			dense_switch__calc_density(NumCases, TypeRange,
-				DetDensity),
+            dense_switch__type_range(!.CI, TypeCategory, Type, TypeRange),
+            dense_switch__calc_density(NumCases, TypeRange, DetDensity),
 			DetDensity > ReqDensity
 		->
 			NeedRangeCheck = cannot_fail,
@@ -171,25 +167,23 @@
 		FirstVal = FirstCaseVal,
 		LastVal = LastCaseVal
 	),
-	lookup_switch__figure_out_output_vars(!.CI, GoalInfo, OutVars),
-	lookup_switch__generate_constants(TaggedCases, OutVars, StoreMap,
-		!MaybeEnd, CodeModel, CaseValues, MLiveness, !CI).
+    figure_out_output_vars(!.CI, GoalInfo, OutVars),
+    generate_constants(TaggedCases, OutVars, StoreMap, !MaybeEnd, CodeModel,
+        CaseValues, MLiveness, !CI).
 
 %---------------------------------------------------------------------------%
 
-:- pred lookup_switch__figure_out_output_vars(code_info::in,
-	hlds_goal_info::in, list(prog_var)::out) is det.
-
 	% Figure out which variables are bound in the switch.
 	% We do this by using the current instmap and the instmap delta in
 	% the goal info to work out which variables are [further] bound by
 	% the switch.
 
-lookup_switch__figure_out_output_vars(CI, GoalInfo, OutVars) :-
+:- pred figure_out_output_vars(code_info::in, hlds_goal_info::in,
+    list(prog_var)::out) is det.
+
+figure_out_output_vars(CI, GoalInfo, OutVars) :-
 	goal_info_get_instmap_delta(GoalInfo, InstMapDelta),
-	(
-		instmap_delta_is_unreachable(InstMapDelta)
-	->
+    ( instmap_delta_is_unreachable(InstMapDelta) ->
 		OutVars = []
 	;
 		code_info__get_instmap(CI, CurrentInstMap),
@@ -210,83 +204,84 @@
 
 %---------------------------------------------------------------------------%
 
-:- pred lookup_switch__generate_constants(cases_list::in, list(prog_var)::in,
+    % To figure out if the outputs are constants, we generate code for
+    % the cases, and check to see if each of the output vars is a constant,
+    % and that no actual code was generated for the goal.
+    %
+:- pred generate_constants(cases_list::in, list(prog_var)::in,
 	abs_store_map::in, branch_end::in, branch_end::out, code_model::in,
 	case_consts::out, maybe(set(prog_var))::out,
 	code_info::in, code_info::out) is semidet.
 
-	% To figure out if the outputs are constants, we generate code for
-	% the cases, and check to see if each of the output vars is a constant,
-	% and that no actual code was generated for the goal.
-lookup_switch__generate_constants([], _Vars, _StoreMap, !MaybeEnd,
-		_CodeModel, [], no, !CI).
-lookup_switch__generate_constants([Case | Cases], Vars, StoreMap,
-		!MaybeEnd, CodeModel, [CaseVal | Rest], yes(Liveness), !CI) :-
+generate_constants([], _Vars, _StoreMap, !MaybeEnd, _CodeModel, [], no, !CI).
+generate_constants([Case | Cases], Vars, StoreMap, !MaybeEnd, CodeModel,
+        [CaseVal | Rest], yes(Liveness), !CI) :-
 	Case = case(_, int_constant(CaseTag), _, Goal),
 	code_info__remember_position(!.CI, BranchStart),
 	code_gen__generate_goal(CodeModel, Goal, Code, !CI),
 	tree__tree_of_lists_is_empty(Code),
 	code_info__get_forward_live_vars(!.CI, Liveness),
-	lookup_switch__get_case_rvals(Vars, CaseRvals, !CI),
+    get_case_rvals(Vars, CaseRvals, !CI),
 	CaseVal = CaseTag - CaseRvals,
-		% EndCode code may contain instructions that place Vars
-		% in the locations dictated by StoreMap, and thus does not have
-		% to be empty. (The array lookup code will put those variables
-		% in those locations directly.)
+    % EndCode code may contain instructions that place Vars in the locations
+    % dictated by StoreMap, and thus does not have to be empty. (The array
+    % lookup code will put those variables in those locations directly.)
 	code_info__generate_branch_end(StoreMap, !MaybeEnd, _EndCode, !CI),
 	code_info__reset_to_position(BranchStart, !CI),
-	lookup_switch__generate_constants(Cases, Vars, StoreMap, !MaybeEnd,
+    generate_constants(Cases, Vars, StoreMap, !MaybeEnd,
 		CodeModel, Rest, _, !CI).
 
 %---------------------------------------------------------------------------%
 
-:- pred lookup_switch__get_case_rvals(list(prog_var)::in, list(rval)::out,
+:- pred get_case_rvals(list(prog_var)::in, list(rval)::out,
 	code_info::in, code_info::out) is semidet.
 
-lookup_switch__get_case_rvals([], [], !CI).
-lookup_switch__get_case_rvals([Var | Vars], [Rval | Rvals], !CI) :-
+get_case_rvals([], [], !CI).
+get_case_rvals([Var | Vars], [Rval | Rvals], !CI) :-
 	code_info__produce_variable(Var, Code, Rval, !CI),
 	tree__tree_of_lists_is_empty(Code),
 	code_info__get_globals(!.CI, Globals),
 	globals__get_options(Globals, Options),
 	exprn_aux__init_exprn_opts(Options, ExprnOpts),
-	lookup_switch__rval_is_constant(Rval, ExprnOpts),
-	lookup_switch__get_case_rvals(Vars, Rvals, !CI).
+    rval_is_constant(Rval, ExprnOpts),
+    get_case_rvals(Vars, Rvals, !CI).
 
 %---------------------------------------------------------------------------%
 
-	% lookup_switch__rval_is_constant(Rval, ExprnOpts) is
-	% true iff Rval is a constant. This depends on the options governing
-	% nonlocal gotos, asm labels enabled, and static ground terms, etc.
-:- pred lookup_switch__rval_is_constant(rval::in, exprn_opts::in) is semidet.
+    % rval_is_constant(Rval, ExprnOpts) is true iff Rval is a constant.
+    % This depends on the options governing nonlocal gotos, asm labels enabled
+    % and static ground terms, etc.
+    %
+:- pred rval_is_constant(rval::in, exprn_opts::in) is semidet.
 
-lookup_switch__rval_is_constant(const(Const), ExprnOpts) :-
+rval_is_constant(const(Const), ExprnOpts) :-
 	exprn_aux__const_is_constant(Const, ExprnOpts, yes).
-lookup_switch__rval_is_constant(unop(_, Exprn), ExprnOpts) :-
-	lookup_switch__rval_is_constant(Exprn, ExprnOpts).
-lookup_switch__rval_is_constant(binop(_, Exprn0, Exprn1), ExprnOpts) :-
-	lookup_switch__rval_is_constant(Exprn0, ExprnOpts),
-	lookup_switch__rval_is_constant(Exprn1, ExprnOpts).
-lookup_switch__rval_is_constant(mkword(_, Exprn0), ExprnOpts) :-
-	lookup_switch__rval_is_constant(Exprn0, ExprnOpts).
+rval_is_constant(unop(_, Exprn), ExprnOpts) :-
+    rval_is_constant(Exprn, ExprnOpts).
+rval_is_constant(binop(_, Exprn0, Exprn1), ExprnOpts) :-
+    rval_is_constant(Exprn0, ExprnOpts),
+    rval_is_constant(Exprn1, ExprnOpts).
+rval_is_constant(mkword(_, Exprn0), ExprnOpts) :-
+    rval_is_constant(Exprn0, ExprnOpts).
 
-:- pred lookup_switch__rvals_are_constant(list(maybe(rval))::in,
+:- pred rvals_are_constant(list(maybe(rval))::in,
 	exprn_opts::in) is semidet.
 
-lookup_switch__rvals_are_constant([], _).
-lookup_switch__rvals_are_constant([MRval | MRvals], ExprnOpts) :-
+rvals_are_constant([], _).
+rvals_are_constant([MRval | MRvals], ExprnOpts) :-
 	MRval = yes(Rval),
-	lookup_switch__rval_is_constant(Rval, ExprnOpts),
-	lookup_switch__rvals_are_constant(MRvals, ExprnOpts).
+    rval_is_constant(Rval, ExprnOpts),
+    rvals_are_constant(MRvals, ExprnOpts).
 
 %---------------------------------------------------------------------------%
 
-lookup_switch__generate(Var, OutVars, CaseValues,
-		StartVal, EndVal, NeedRangeCheck, NeedBitVecCheck,
-		MLiveness, StoreMap, MaybeEnd0, Code, !CI) :-
+generate_lookup_switch(Var, OutVars, CaseValues, StartVal, EndVal,
+        NeedRangeCheck, NeedBitVecCheck, MLiveness, StoreMap, MaybeEnd0,
+        Code, !CI) :-
 
 		% Evaluate the variable which we are going to be switching on.
 	code_info__produce_variable(Var, VarCode, Rval, !CI),
+
 		% If the case values start at some number other than 0,
 		% then subtract that number to give us a zero-based index.
 	( StartVal = 0 ->
@@ -294,9 +289,9 @@
 	;
 		Index = binop(-, Rval, const(int_const(StartVal)))
 	),
-		% If the switch is not locally deterministic, we need to
-		% check that the value of the variable lies within the
-		% appropriate range.
+
+    % If the switch is not locally deterministic, we need to check that
+    % the value of the variable lies within the appropriate range.
 	(
 		NeedRangeCheck = can_fail,
 		Difference = EndVal - StartVal,
@@ -309,61 +304,49 @@
 	),
 	(
 		NeedBitVecCheck = can_fail,
-		lookup_switch__generate_bitvec_test(Index, CaseValues,
-			StartVal, EndVal, CheckBitVec, !CI)
+        generate_bitvec_test(Index, CaseValues, StartVal, EndVal, CheckBitVec,
+            !CI)
 	;
 		NeedBitVecCheck = cannot_fail,
 		CheckBitVec = empty
 	),
-		% Now generate the terms into which we do the lookups
-	lookup_switch__generate_terms(Index, OutVars, CaseValues, StartVal,
-		!CI),
-		% We keep track of what variables are supposed to be
-		% live at the end of cases. We have to do this explicitly
-		% because generating a `fail' slot last would yield the
-		% wrong liveness.
+
+    % Now generate the terms into which we do the lookups.
+    generate_terms(Index, OutVars, CaseValues, StartVal, !CI),
+
+    % We keep track of what variables are supposed to be live at the end
+    % of cases. We have to do this explicitly because generating a `fail' slot
+    % last would yield the wrong liveness.
 	(
 		MLiveness = yes(Liveness),
 		code_info__set_forward_live_vars(Liveness, !CI)
 	;
 		MLiveness = no,
-		error("lookup_switch__generate: no liveness!")
+        unexpected(this_file, "generate_lookup_switch: no liveness!")
 	),
-	code_info__generate_branch_end(StoreMap, MaybeEnd0, _MaybeEnd,
-		LookupCode, !CI),
-		% Assemble to code together
+    code_info__generate_branch_end(StoreMap, MaybeEnd0, _MaybeEnd, LookupCode,
+        !CI),
 	Comment = node([comment("lookup switch") - ""]),
-	Code =
-		tree(Comment,
-		tree(VarCode,
-		tree(RangeCheck,
-		tree(CheckBitVec,
-		     LookupCode)))).
+    Code = tree_list([Comment, VarCode, RangeCheck, CheckBitVec, LookupCode]).
 
 %------------------------------------------------------------------------------%
 
-:- pred lookup_switch__generate_bitvec_test(rval::in, case_consts::in,
-	int::in, int::in, code_tree::out, code_info::in, code_info::out)
-	is det.
-
-	% The bitvector is an array of words (where we use the first
-	% 32 bits of each word). Each bit represents a tag value for
-	% the (range checked) input to the lookup switch. The bit is `1'
-	% iff we have a case for that tag value.
-lookup_switch__generate_bitvec_test(Index, CaseVals, Start, _End,
-		CheckCode, !CI) :-
-	lookup_switch__get_word_bits(!.CI, WordBits, Log2WordBits),
-	generate_bit_vec(CaseVals, Start, WordBits, BitVecArgs, BitVecRval,
-		!CI),
-
-		%
-		% Optimize the single-word case:
-		% if all the cases fit into a single word, then
-		% the word to use is always that word, and the index
-		% specifies which bit.  Otherwise, the high bits
-		% of the index specify which word to use and the
-		% low bits specify which bit.
+    % The bitvector is an array of words (where we use the first 32 bits
+    % of each word). Each bit represents a tag value for the (range checked)
+    % input to the lookup switch. The bit is `1' iff we have a case for that
+    % tag value.
 		%
+:- pred generate_bitvec_test(rval::in, case_consts::in, int::in, int::in,
+    code_tree::out, code_info::in, code_info::out) is det.
+
+generate_bitvec_test(Index, CaseVals, Start, _End, CheckCode, !CI) :-
+    get_word_bits(!.CI, WordBits, Log2WordBits),
+    generate_bit_vec(CaseVals, Start, WordBits, BitVecArgs, BitVecRval, !CI),
+
+    % Optimize the single-word case: if all the cases fit into a single word,
+    % then the word to use is always that word, and the index specifies which
+    % bit. Otherwise, the high bits of the index specify which word to use
+    % and the low bits specify which bit.
 	( BitVecArgs = [SingleWord] ->
 		Word = SingleWord,
 		BitNum = Index
@@ -380,22 +363,19 @@
 		% except that it can generate more efficient code.
 		BitNum = binop(&, Index, const(int_const(WordBits - 1)))
 	),
-	HasBit = binop((&),
-			binop((<<), const(int_const(1)), BitNum),
-			Word),
+    HasBit = binop((&), binop((<<), const(int_const(1)), BitNum), Word),
 	code_info__fail_if_rval_is_false(HasBit, CheckCode, !CI).
 
-:- pred lookup_switch__get_word_bits(code_info::in, int::out, int::out) is det.
-
-	% Prevent cross-compilation errors by making sure that
-	% the bitvector uses a number of bits that will fit both
-	% on this machine (so that we can correctly generate it),
-	% and on the target machine (so that it can be executed
-	% correctly).  Also make sure that the number of bits that
-	% we use is a power of 2, so that we implement division as
+    % Prevent cross-compilation errors by making sure that the bitvector
+    % uses a number of bits that will fit both on this machine (so that
+    % we can correctly generate it), and on the target machine (so that
+    % it can be executed correctly). Also make sure that the number of bits
+    % that we use is a power of 2, so that we implement division as
 	% right-shift (see above).
+    %
+:- pred get_word_bits(code_info::in, int::out, int::out) is det.
 
-lookup_switch__get_word_bits(CI, WordBits, Log2WordBits) :-
+get_word_bits(CI, WordBits, Log2WordBits) :-
 	int__bits_per_int(HostWordBits),
 	code_info__get_globals(CI, Globals),
 	globals__lookup_int_option(Globals, bits_per_word, TargetWordBits),
@@ -409,13 +389,13 @@
 log2_rounded_down(X) = Log :-
 	int__log2(X + 1, Log + 1).  % int__log2 rounds up
 
+    % We generate the bitvector by iterating through the cases marking the bit
+    % for each case. (We represent the bitvector here as a map from the word
+    % number in the vector to the bits for that word.
+    %
 :- pred generate_bit_vec(case_consts::in, int::in, int::in,
 	list(rval)::out, rval::out, code_info::in, code_info::out) is det.
 
-	% we generate the bitvector by iterating through the cases
-	% marking the bit for each case. (We represent the bitvector
-	% here as a map from the word number in the vector to the bits
-	% for that word.
 generate_bit_vec(CaseVals, Start, WordBits, Args, BitVec, !CI) :-
 	map__init(Empty),
 	generate_bit_vec_2(CaseVals, Start, WordBits, Empty, BitMap),
@@ -458,25 +438,24 @@
 
 %------------------------------------------------------------------------------%
 
-:- pred lookup_switch__generate_terms(rval::in, list(prog_var)::in,
-	case_consts::in, int::in, code_info::in, code_info::out) is det.
-
-	% Add an expression to the expression cache in the code_info
-	% structure for each of the output variables of the lookup
-	% switch. This is done by creating a `create' term for the
-	% array, and caching an expression for the variable to get the
-	% Index'th field of that term.
+    % Add an expression to the expression cache in the code_info structure
+    % for each of the output variables of the lookup switch. This is done by
+    % creating a `create' term for the array, and caching an expression
+    % for the variable to get the Index'th field of that term.
+    %
+:- pred generate_terms(rval::in, list(prog_var)::in, case_consts::in, int::in,
+    code_info::in, code_info::out) is det.
 
-lookup_switch__generate_terms(Index, OutVars, CaseVals, Start, !CI) :-
+generate_terms(Index, OutVars, CaseVals, Start, !CI) :-
 	map__init(Empty),
 	rearrange_vals(OutVars, CaseVals, Start, Empty, ValMap),
-	lookup_switch__generate_terms_2(Index, OutVars, ValMap, !CI).
+    generate_terms_2(Index, OutVars, ValMap, !CI).
 
-:- pred lookup_switch__generate_terms_2(rval::in, list(prog_var)::in,
+:- pred generate_terms_2(rval::in, list(prog_var)::in,
 	rval_map::in, code_info::in, code_info::out) is det.
 
-lookup_switch__generate_terms_2(_Index, [], _Map, !CI).
-lookup_switch__generate_terms_2(Index, [Var | Vars], Map, !CI) :-
+generate_terms_2(_Index, [], _Map, !CI).
+generate_terms_2(Index, [Var | Vars], Map, !CI) :-
 	map__lookup(Map, Var, Vals0),
 	list__sort(Vals0, Vals),
 	construct_args(Vals, 0, Args),
@@ -484,9 +463,8 @@
 	ArrayTerm = const(data_addr_const(DataAddr, no)),
 	LookupLval = field(yes(0), ArrayTerm, Index),
 	code_info__assign_lval_to_var(Var, LookupLval, Code, !CI),
-	require(tree__is_empty(Code),
-		"lookup_switch__generate_terms_2: nonempty code"),
-	lookup_switch__generate_terms_2(Index, Vars, Map, !CI).
+    require(tree__is_empty(Code), "generate_terms_2: nonempty code"),
+    generate_terms_2(Index, Vars, Map, !CI).
 
 :- pred construct_args(list(pair(int, rval))::in, int::in, list(rval)::out)
 	is det.
@@ -495,7 +473,7 @@
 construct_args([Index - Rval | Rest], Count0, [Arg | Args]) :-
 	( Count0 < Index ->
 		% If this argument (array element) is a place-holder and
-		% will never be referenced, just fill it in with a `0'
+        % will never be referenced, just fill it in with a `0'.
 		Arg = const(int_const(0)),
 		Remainder = [Index - Rval | Rest]
 	;
@@ -507,13 +485,13 @@
 
 %------------------------------------------------------------------------------%
 
+    % For the purpose of constructing the terms, the case_consts structure
+    % is a bit inconvenient, so we rearrange the data into a map from var
+    % to list of tag-value pairs.
+    %
 :- pred rearrange_vals(list(prog_var)::in, case_consts::in, int::in,
 	rval_map::in, rval_map::out) is det.
 
-	% For the purpose of constructing the terms, the case_consts
-	% structure is a bit inconvenient, so we rearrange the data
-	% into a map from var to list of tag-value pairs.
-
 rearrange_vals(_Vars, [], _Start, Map, Map).
 rearrange_vals(Vars, [Tag - Rvals | Rest], Start, Map0, Map) :-
 	assoc_list__from_corresponding_lists(Vars, Rvals, Pairs),
@@ -533,5 +511,11 @@
 	),
 	map__set(Map0, Var, Vals, Map1),
 	rearrange_vals_2(Rest, Tag, Map1, Map).
+
+%------------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "lookup_switch.m".
 
 %------------------------------------------------------------------------------%
Index: compiler/make.program_target.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make.program_target.m,v
retrieving revision 1.30
diff -u -b -r1.30 make.program_target.m
--- compiler/make.program_target.m	26 Apr 2005 04:32:48 -0000	1.30
+++ compiler/make.program_target.m	12 Oct 2005 08:49:19 -0000
@@ -1,12 +1,16 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
+%
 % File: make.program_target.m
 % Main author: stayl
 %
 % Build targets which relate to whole programs or libraries.
+%
 %-----------------------------------------------------------------------------%
 
 :- module make__program_target.
@@ -15,14 +19,14 @@
 
 %-----------------------------------------------------------------------------%
 
-	% make_linked_target(Target, Success, Info0, Info).
+    % make_linked_target(Target, Success, Info0, Info):
 	%
 	% Build a library or an executable.
 	%
 :- pred make_linked_target(linked_target_file::in, bool::out,
 	make_info::in, make_info::out, io::di, io::uo) is det.
 
-	% make_misc_target(Target, Success, Info0, Info).
+    % make_misc_target(Target, Success, Info0, Info):
 	%
 	% Handle miscellaneous target types, including clean-up, library
 	% installation, and building all files of a given type for all
@@ -65,10 +69,8 @@
 	;
 		get_object_code_type(FileType, PIC, !IO),
 
-		%
-		% Build the `.c' files first so that errors are
-		% reported as soon as possible.
-		%
+        % Build the `.c' files first so that errors are reported
+        % as soon as possible.
 		globals__io_get_target(CompilationTarget, !IO),
 		(
 			CompilationTarget = c,
@@ -85,14 +87,12 @@
 		;
 			CompilationTarget = java,
 			IntermediateTargetType = java_code,
-			% XXX Whoever finishes the Java backend
-			% can fill this in.
+            % XXX Whoever finishes the Java backend can fill this in.
 			ObjectTargetType = object_code(non_pic)
 		),
 
 		get_target_modules(IntermediateTargetType,
-			set__to_sorted_list(AllModules), ObjModules, !Info,
-			!IO),
+            set__to_sorted_list(AllModules), ObjModules, !Info, !IO),
 		IntermediateTargets = make_dependency_list(ObjModules,
 			IntermediateTargetType),
 		ObjTargets = make_dependency_list(ObjModules, ObjectTargetType),
@@ -102,34 +102,27 @@
 		ForeignObjTargets = list__condense(ForeignObjTargetsList),
 
 		foldl2_maybe_stop_at_error(KeepGoing,
-			foldl2_maybe_stop_at_error(KeepGoing,
-				make_module_target),
+            foldl2_maybe_stop_at_error(KeepGoing, make_module_target),
 			[IntermediateTargets, ObjTargets, ForeignObjTargets],
 			BuildDepsSucceeded, !Info, !IO),
 
-		linked_target_file_name(MainModuleName, FileType,
-			OutputFileName, !IO),
+        linked_target_file_name(MainModuleName, FileType, OutputFileName, !IO),
 		get_file_timestamp([dir__this_directory], OutputFileName,
 			MaybeTimestamp, !Info, !IO),
-		check_dependencies(OutputFileName, MaybeTimestamp,
-			BuildDepsSucceeded, ObjTargets, BuildDepsResult,
-			!Info, !IO),
-
+        check_dependencies(OutputFileName, MaybeTimestamp, BuildDepsSucceeded,
+            ObjTargets, BuildDepsResult, !Info, !IO),
 		(
 			DepsSuccess = yes,
 			BuildDepsResult \= error
 		->
 			build_with_check_for_interrupt(
 				build_with_output_redirect(MainModuleName,
-					build_linked_target(MainModuleName,
-						FileType, OutputFileName,
-						MaybeTimestamp, AllModules,
-						ObjModules, CompilationTarget,
-						PIC, DepsSuccess,
-						BuildDepsResult)
+                    build_linked_target(MainModuleName, FileType,
+                        OutputFileName, MaybeTimestamp, AllModules, ObjModules,
+                        CompilationTarget, PIC, DepsSuccess, BuildDepsResult)
 					),
-				linked_target_cleanup(MainModuleName, FileType,
-					OutputFileName, CompilationTarget),
+                linked_target_cleanup(MainModuleName, FileType, OutputFileName,
+                    CompilationTarget),
 				Succeeded, !Info, !IO)
 		;
 			Succeeded = no
@@ -180,10 +173,9 @@
 	io::di, io::uo) is det.
 
 get_foreign_object_targets(PIC, ModuleName, ObjectTargets, !Info, !IO) :-
-	%
 	% Find externally compiled foreign code files for
 	% `:- pragma foreign_proc' declarations.
-	%
+
 	globals__io_get_target(CompilationTarget, !IO),
 	get_module_dependencies(ModuleName, MaybeImports, !Info, !IO),
 	(
@@ -204,17 +196,14 @@
 		Imports ^ foreign_code = contains_foreign_code(Langs)
 	->
 		ForeignObjectTargets = list__map(
-			(func(L) =
-				target(ModuleName - foreign_il_asm(L))
+            (func(L) = target(ModuleName - foreign_il_asm(L))
 			), set__to_sorted_list(Langs))
 	;
 		ForeignObjectTargets = []
 	),
 
-	%
-	% Find out if any externally compiled foreign code files for fact
-	% tables exist.
-	%
+    % Find out if any externally compiled foreign code files for fact tables
+    % exist.
 	(
 		( CompilationTarget = c
 		; CompilationTarget = asm
@@ -222,8 +211,7 @@
 	->
 		FactObjectTargets = list__map(
 			(func(FactFile) =
-				target(ModuleName -
-					fact_table_object(PIC, FactFile))
+                target(ModuleName - fact_table_object(PIC, FactFile))
 			),
 			Imports ^ fact_table_deps),
 		ObjectTargets = FactObjectTargets ++ ForeignObjectTargets
@@ -231,13 +219,11 @@
 		ObjectTargets = ForeignObjectTargets
 	).
 
-
 :- pred build_linked_target(module_name::in, linked_target_type::in,
 	file_name::in, maybe_error(timestamp)::in, set(module_name)::in,
 	list(module_name)::in, compilation_target::in, pic::in,
 	bool::in, dependencies_result::in, io__output_stream::in,
-	bool::out, make_info::in, make_info::out,
-	io::di, io::uo) is det.
+    bool::out, make_info::in, make_info::out, io::di, io::uo) is det.
 
 build_linked_target(MainModuleName, FileType, OutputFileName, MaybeTimestamp,
 		AllModules, ObjModules, CompilationTarget, PIC, DepsSuccess,
@@ -248,8 +234,8 @@
 		MaybePreLinkCommand = yes(PreLinkCommand),
 		make_all_module_command(PreLinkCommand, MainModuleName,
 			to_sorted_list(AllModules), CommandString, !IO),
-		invoke_system_command(ErrorStream, verbose,
-			CommandString, PreLinkSucceeded, !IO)
+        invoke_system_command(ErrorStream, verbose, CommandString,
+            PreLinkSucceeded, !IO)
 	;
 		MaybePreLinkCommand = no,
 		PreLinkSucceeded = yes
@@ -257,10 +243,8 @@
 	(
 		PreLinkSucceeded = yes,
 		build_linked_target_2(MainModuleName, FileType, OutputFileName,
-			MaybeTimestamp, AllModules, ObjModules,
-			CompilationTarget, PIC, DepsSuccess,
-			BuildDepsResult, ErrorStream, Succeeded,
-			!Info, !IO)
+            MaybeTimestamp, AllModules, ObjModules, CompilationTarget, PIC,
+            DepsSuccess, BuildDepsResult, ErrorStream, Succeeded, !Info, !IO)
 	;
 		PreLinkSucceeded = no,
 		Succeeded = no
@@ -280,11 +264,9 @@
 	% Clear the option -- we'll pass the list of files directly.
 	globals__io_set_option(link_objects, accumulating([]), !IO),
 
-	%
 	% Remake the `_init.o' file.
 	% XXX We should probably make a `_init.o' file for shared
 	% libraries linked using dlopen().
-	%
 	AllModulesList = set__to_sorted_list(AllModules),
 	(
 		FileType = executable,
@@ -296,11 +278,9 @@
 			MainModuleName, AllModulesList, InitObjectResult, !IO),
 		(
 			InitObjectResult = yes(InitObject),
-				% We may need to update the timestamp
-				% of the `_init.o' file.
+            % We may need to update the timestamp of the `_init.o' file.
 			!:Info = !.Info ^ file_timestamps :=
-				map__delete(!.Info ^ file_timestamps,
-					InitObject),
+                map__delete(!.Info ^ file_timestamps, InitObject),
 			InitObjects = [InitObject],
 			DepsResult2 = BuildDepsResult
 		;
@@ -315,9 +295,7 @@
 
 	ObjectsToCheck = InitObjects ++ LinkObjects,
 
-	%
 	% Report errors if any of the extra objects aren't present.
-	%
 	list__map_foldl2(dependency_status,
 		list__map((func(F) = file(F, no)), ObjectsToCheck),
 		ExtraObjStatus, !Info, !IO),
@@ -342,20 +320,17 @@
 		Succeeded = no
 	;
 		DepsResult = up_to_date,
-		maybe_warn_up_to_date_target(
-			MainModuleName - linked_target(FileType), !Info, !IO),
+        maybe_warn_up_to_date_target(MainModuleName - linked_target(FileType),
+            !Info, !IO),
 		Succeeded = yes
 	;
 		DepsResult = out_of_date,
 		maybe_make_linked_target_message(OutputFileName, !IO),
 
-		%
-		% Find the extra object files for externally compiled
-		% foreign procedures and fact tables. We don't need
-		% to include these in the timestamp checking above --
-		% they will have been checked when the module's object
-		% file was built.
-		%
+        % Find the extra object files for externally compiled foreign
+        % procedures and fact tables. We don't need to include these in the
+        % timestamp checking above -- they will have been checked when the
+        % module's object file was built.
 		list__map_foldl2(
 		    (pred(ModuleName::in, ForeignFiles::out,
 		    	    MakeInfo0::in, MakeInfo::out, di, uo) is det -->
@@ -363,13 +338,11 @@
 				MakeInfo0, MakeInfo),
 			(
 			    { MaybeImports = yes(Imports) },
-			    external_foreign_code_files(PIC,
-			    	Imports, ForeignFiles)
+                external_foreign_code_files(PIC, Imports, ForeignFiles)
 			;
 			    { MaybeImports = no },
 			    % This error should have been detected earlier.
-			    { error(
-			    "build_linked_target: error in dependencies") }
+                { error("build_linked_target: error in dependencies") }
 			)
 		    ), AllModulesList, ExtraForeignFiles, !Info, !IO),
 		ForeignObjects = list__map(
@@ -385,12 +358,11 @@
 
 		% LinkObjects may contain `.a' files which must come
 		% after all the object files on the linker command line.
-		AllObjects = InitObjects ++ ObjList ++
-			ForeignObjects ++ LinkObjects,
+        AllObjects = InitObjects ++ ObjList ++ ForeignObjects ++ LinkObjects,
 		(
 			CompilationTarget = c,
-			% Run the link in a separate process so it can
-			% be killed if an interrupt is received.
+            % Run the link in a separate process so it can be killed
+            % if an interrupt is received.
 			call_in_forked_process(
 				compile_target_code__link(ErrorStream,
 					FileType, MainModuleName, AllObjects),
@@ -408,8 +380,7 @@
 			Succeeded = yes
 		;
 			CompilationTarget = java,
-			create_java_shell_script(MainModuleName, Succeeded,
-				!IO)
+            create_java_shell_script(MainModuleName, Succeeded, !IO)
 		),
 		!:Info = !.Info ^ command_line_targets :=
 			set__delete(!.Info ^ command_line_targets,
@@ -417,8 +388,7 @@
 		(
 			Succeeded = yes,
 			!:Info = !.Info ^ file_timestamps :=
-				map__delete(!.Info ^ file_timestamps,
-					OutputFileName)
+                map__delete(!.Info ^ file_timestamps, OutputFileName)
 		;
 			Succeeded = no,
 			file_error(OutputFileName, !IO)
@@ -431,15 +401,17 @@
 	% Appends the strings in the list `Strings' together into the
 	% string Result. Each string is prefixed by Prefix, suffixed by
 	% Suffix and separated by Separator.
-
+    %
 :- pred join_string_list(list(string)::in, string::in, string::in,
 	string::in, string::out) is det.
 
 join_string_list([], _Prefix, _Suffix, _Separator, "").
 join_string_list([String | Strings], Prefix, Suffix, Separator, Result) :-
-	( Strings = [] ->
+    (
+        Strings = [],
 		string__append_list([Prefix, String, Suffix], Result)
 	;
+        Strings = [_ | _],
 		join_string_list(Strings, Prefix, Suffix, Separator, Result0),
 		string__append_list([Prefix, String, Suffix, Separator,
 			Result0], Result)
@@ -467,8 +439,7 @@
 
 make_misc_target(MainModuleName - TargetType, Succeeded, !Info, !IO) :-
 	build_with_module_options(MainModuleName, [],
-		make_misc_target(MainModuleName - TargetType),
-		Succeeded, !Info, !IO).
+        make_misc_target(MainModuleName - TargetType), Succeeded, !Info, !IO).
 
 :- pred make_misc_target(pair(module_name, misc_target_type)::in,
 	list(string)::in, bool::out, make_info::in, make_info::out,
@@ -486,8 +457,8 @@
 	;
 		true
 	),
-	find_reachable_local_modules(MainModuleName, Succeeded0,
-		AllModulesSet, !Info, !IO),
+    find_reachable_local_modules(MainModuleName, Succeeded0, AllModulesSet,
+        !Info, !IO),
 	!:Info = !.Info ^ rebuild_dependencies := RebuildDeps,
 	AllModules = set__to_sorted_list(AllModulesSet),
 	(
@@ -510,8 +481,7 @@
 		;
 			foldl2_maybe_stop_at_error(KeepGoing,
 				make_module_target,
-				make_dependency_list(TargetModules,
-					ModuleTargetType),
+                make_dependency_list(TargetModules, ModuleTargetType),
 				Succeeded1, !Info, !IO),
 			Succeeded = Succeeded0 `and` Succeeded1
 		)
@@ -524,36 +494,30 @@
 			Intermod, !IO),
 		(
 			Intermod = yes,
-			OptFiles = make_dependency_list(AllModules,
-				intermodule_interface)
+            OptFiles = make_dependency_list(AllModules, intermodule_interface)
 		;
 			Intermod = no,
 			OptFiles = []
 		),
 		globals__io_lookup_bool_option(keep_going, KeepGoing, !IO),
 		foldl2_maybe_stop_at_error(KeepGoing,
-			foldl2_maybe_stop_at_error(KeepGoing,
-				make_module_target),
+            foldl2_maybe_stop_at_error(KeepGoing, make_module_target),
 			[ShortInts, LongInts, OptFiles],
 			IntSucceeded, !Info, !IO),
 		(
 			IntSucceeded = yes,
-				% Errors while making the `.init' file
-				% should be very rare.
+            % Errors while making the `.init' file should be very rare.
 			io__output_stream(ErrorStream, !IO),
-			compile_target_code__make_init_file(ErrorStream,
-				MainModuleName, AllModules, InitSucceeded,
-				!IO),
+            compile_target_code__make_init_file(ErrorStream, MainModuleName,
+                AllModules, InitSucceeded, !IO),
 			(
 				InitSucceeded = yes,
-				make_linked_target(MainModuleName -
-					static_library, StaticSucceeded,
-					!Info, !IO),
+                make_linked_target(MainModuleName - static_library,
+                    StaticSucceeded, !Info, !IO),
 				(
 					StaticSucceeded = yes,
-					make_linked_target(MainModuleName -
-						shared_library, Succeeded,
-						!Info, !IO)
+                    make_linked_target(MainModuleName - shared_library,
+                        Succeeded, !Info, !IO)
 				;
 					StaticSucceeded = no,
 					Succeeded = no
@@ -568,8 +532,8 @@
 		)
 	;
 		TargetType = install_library,
-		make_misc_target(MainModuleName - build_library,
-			LibSucceeded, !Info, !IO),
+        make_misc_target(MainModuleName - build_library, LibSucceeded,
+            !Info, !IO),
 		(
 			LibSucceeded = yes,
 			install_library(MainModuleName, Succeeded, !Info, !IO)
@@ -585,36 +549,36 @@
 	make_info::in, make_info::out, io::di, io::uo) is det.
 
 install_library(MainModuleName, Succeeded, !Info, !IO) :-
-	find_reachable_local_modules(MainModuleName, DepsSuccess,
-		AllModules0, !Info, !IO),
+    find_reachable_local_modules(MainModuleName, DepsSuccess, AllModules0,
+        !Info, !IO),
 	AllModules = set__to_sorted_list(AllModules0) ,
 	make_install_dirs(DirSucceeded, LinkSucceeded, !IO),
-	( DepsSuccess = yes, DirSucceeded = yes ->
+    (
+        DepsSuccess = yes,
+        DirSucceeded = yes
+    ->
 		globals__io_lookup_string_option(install_prefix, Prefix, !IO),
 
 		ModulesDir = Prefix/"lib"/"mercury"/"modules",
-		module_name_to_file_name(MainModuleName, ".init", no,
-			InitFileName, !IO),
+        module_name_to_file_name(MainModuleName, ".init", no, InitFileName,
+            !IO),
 		install_file(InitFileName, ModulesDir, InitSucceded, !IO),
 
-		list__map_foldl2(install_ints_and_headers(LinkSucceeded),
-			AllModules, IntsSucceeded, !Info, !IO),
+        list__map_foldl2(install_ints_and_headers(LinkSucceeded), AllModules,
+            IntsSucceeded, !Info, !IO),
 
 		globals__io_get_globals(Globals, !IO),
 		grade_directory_component(Globals, Grade),
-		install_library_grade_files(LinkSucceeded, Grade,
-			MainModuleName, AllModules, GradeSucceeded,
-			!Info, !IO),
+        install_library_grade_files(LinkSucceeded, Grade, MainModuleName,
+            AllModules, GradeSucceeded, !Info, !IO),
 		(
 			InitSucceded = yes,
 			bool__and_list(IntsSucceeded) = yes,
 			GradeSucceeded = yes
 		->
 			% XXX With Mmake, LIBGRADES is target-specific.
-			globals__io_lookup_accumulating_option(libgrades,
-				LibGrades0, !IO),
-			globals__io_lookup_bool_option(keep_going, KeepGoing,
-				!IO),
+            globals__io_lookup_accumulating_option(libgrades, LibGrades0, !IO),
+            globals__io_lookup_bool_option(keep_going, KeepGoing, !IO),
 			LibGrades = list__delete_all(LibGrades0, Grade),
 			foldl2_maybe_stop_at_error(KeepGoing,
 				install_library_grade(LinkSucceeded,
@@ -639,9 +603,11 @@
 			Intermod, !IO),
 		( Intermod = yes ->
 			% `.int0' files are imported by `.opt' files.
-			( Imports ^ children \= [] ->
+            (
+                Imports ^ children = [_ | _],
 				Exts = ["int0", "opt"]
 			;
+                Imports ^ children = [],
 				Exts = ["opt"]
 			)
 		;
@@ -651,8 +617,8 @@
 		globals__io_lookup_string_option(install_prefix, Prefix, !IO),
 		LibDir = Prefix/"lib"/"mercury",
 		list__map_foldl(
-			install_subdir_file(SubdirLinkSucceeded,
-				LibDir/"ints", ModuleName),
+            install_subdir_file(SubdirLinkSucceeded, LibDir/"ints",
+                ModuleName),
 			["int", "int2", "int3", "module_dep" | Exts],
 			Results, !IO),
 
@@ -661,16 +627,14 @@
 			% `.mh' files are only generated for modules containing
 			% `:- pragma export' declarations.
 			( Target = c ; Target = asm ),
-			Imports ^ contains_foreign_export =
-				contains_foreign_export
+            Imports ^ contains_foreign_export = contains_foreign_export
 		->
 			install_subdir_file(SubdirLinkSucceeded, LibDir/"inc",
 				ModuleName, "mh", HeaderSucceded1, !IO),
 
-			% This is needed so that the file will be
-			% found in Mmake's VPATH.
-			install_subdir_file(SubdirLinkSucceeded, LibDir/"ints",
-				ModuleName, "mh", HeaderSucceded2, !IO),
+            % This is needed so that the file will be found in Mmake's VPATH.
+            install_subdir_file(SubdirLinkSucceeded, LibDir/"ints", ModuleName,
+                "mh", HeaderSucceded2, !IO),
 
 			HeaderSucceded = HeaderSucceded1 `and` HeaderSucceded2
 		;
@@ -688,13 +652,12 @@
 
 install_library_grade(LinkSucceeded0, ModuleName, AllModules, Grade, Succeeded,
 		!Info, !IO) :-
-	%
-	% Building the library in the new grade is done in a separate
-	% process to make it easier to stop and clean up on an interrupt.
-	%
+    % Building the library in the new grade is done in a separate process
+    % to make it easier to stop and clean up on an interrupt.
+
 	Cleanup = make_grade_clean(ModuleName, AllModules),
 	build_with_check_for_interrupt(
-	    (pred(GradeSuccess::out, MInfo::in, MInfo::out, !.IO::di, !:IO::uo)
+        ( pred(GradeSuccess::out, MInfo::in, MInfo::out, !.IO::di, !:IO::uo)
 			is det :-
 		call_in_forked_process(
 		    (pred(GradeSuccess0::out, !.IO::di, !:IO::uo) is det :-
@@ -705,17 +668,14 @@
 	    ), Cleanup, Succeeded, !Info, !IO).
 
 :- pred install_library_grade_2(bool::in, string::in, module_name::in,
-	list(module_name)::in, make_info::in, bool::out, io::di, io::uo)
-	is det.
+    list(module_name)::in, make_info::in, bool::out, io::di, io::uo) is det.
 
 install_library_grade_2(LinkSucceeded0, Grade, ModuleName, AllModules,
 		Info0, Succeeded, !IO) :-
 	globals__io_get_globals(Globals, !IO),
 
-	%
 	% Set up so that grade-dependent files for the current grade
 	% don't overwrite the files for the default grade.
-	%
 	OptionArgs0 = Info0 ^ option_args,
 	OptionArgs = OptionArgs0 ++ ["--grade", Grade, "--use-grade-subdirs"],
 
@@ -729,8 +689,7 @@
 	lookup_mmc_options(Info0 ^ options_variables, MaybeMCFlags, !IO),
 	(
 		MaybeMCFlags = yes(MCFlags),
-		handle_options(MCFlags ++ OptionArgs, OptionsErrors, _, _, _,
-			!IO)
+        handle_options(MCFlags ++ OptionArgs, OptionsErrors, _, _, _, !IO)
 	;
 		MaybeMCFlags = no,
 		% Errors should have been caught before.
@@ -743,17 +702,15 @@
 		Succeeded = no
 	;
 		OptionsErrors = [],
-		%
+
 		% Remove the grade-dependent targets from the status map
 		% (we need to rebuild them in the new grade).
-		%
 		StatusMap0 = Info0 ^ dependency_status,
 		StatusMap = map__from_assoc_list(list__filter(
 			(pred((File - _)::in) is semidet :-
 				\+ (
 					File = target(_ - Target),
-					target_is_grade_or_arch_dependent(
-						Target)
+                    target_is_grade_or_arch_dependent(Target)
 				)
 			),
 			map__to_assoc_list(StatusMap0))),
@@ -763,11 +720,9 @@
 			Info1, Info2, !IO),
 		(
 			LibSucceeded = yes,
-			install_library_grade_files(LinkSucceeded0,
-				Grade, ModuleName, AllModules,
-				Succeeded, Info2, Info3, !IO),
-			make_grade_clean(ModuleName, AllModules,
-				Info3, _, !IO)
+            install_library_grade_files(LinkSucceeded0, Grade, ModuleName,
+                AllModules, Succeeded, Info2, Info3, !IO),
+            make_grade_clean(ModuleName, AllModules, Info3, _, !IO)
 		;
 			LibSucceeded = no,
 			Succeeded = no
@@ -788,35 +743,28 @@
 	LinkSucceeded = LinkSucceeded0 `and` LinkSucceeded1,
 	(
 		DirResult = yes,
-		linked_target_file_name(ModuleName, static_library,
-			LibFileName, !IO),
-		linked_target_file_name(ModuleName, shared_library,
-			SharedLibFileName, !IO),
-		linked_target_file_name(ModuleName, java_archive,
-			JarFileName, !IO),
+        linked_target_file_name(ModuleName, static_library, LibFileName, !IO),
+        linked_target_file_name(ModuleName, shared_library, SharedLibFileName,
+            !IO),
+        linked_target_file_name(ModuleName, java_archive, JarFileName, !IO),
 
 		globals__io_lookup_string_option(install_prefix, Prefix, !IO),
 		globals__io_lookup_string_option(fullarch, FullArch, !IO),
 
 		( Grade = "java" ->
 			GradeLibDir = Prefix/"lib"/"mercury"/"lib"/"java",
-			install_file(JarFileName, GradeLibDir, LibsSucceeded,
-				!IO)
+            install_file(JarFileName, GradeLibDir, LibsSucceeded, !IO)
 		;
-			GradeLibDir =
-				Prefix/"lib"/"mercury"/"lib"/Grade/FullArch,
-			install_file(LibFileName, GradeLibDir,
-				LibSuccess, !IO),
-			install_file(SharedLibFileName, GradeLibDir,
-				SharedLibSuccess, !IO),
+            GradeLibDir = Prefix/"lib"/"mercury"/"lib"/Grade/FullArch,
+            install_file(LibFileName, GradeLibDir, LibSuccess, !IO),
+            install_file(SharedLibFileName, GradeLibDir, SharedLibSuccess,
+                !IO),
 			LibsSucceeded = LibSuccess `and` SharedLibSuccess
 		),
 
-		list__map_foldl2(
-			install_grade_ints_and_headers(LinkSucceeded, Grade),
+        list__map_foldl2(install_grade_ints_and_headers(LinkSucceeded, Grade),
 			AllModules, IntsHeadersSucceeded, !Info, !IO),
-		Succeeded = bool__and_list(
-			[LibsSucceeded | IntsHeadersSucceeded])
+        Succeeded = bool__and_list([LibsSucceeded | IntsHeadersSucceeded])
 	;
 		DirResult = no,
 		Succeeded = no
@@ -837,40 +785,38 @@
 		LibDir = Prefix/"lib"/"mercury",
 
 		globals__io_get_target(Target, !IO),
-		globals__io_lookup_bool_option(highlevel_code, HighLevelCode,
-			!IO),
+        globals__io_lookup_bool_option(highlevel_code, HighLevelCode, !IO),
 		(
 			(
 				Target = c,
 				HighLevelCode = yes
 			;
 				Target = asm,
-				Imports ^ foreign_code =
-					contains_foreign_code(_)
+                Imports ^ foreign_code = contains_foreign_code(_)
 			)
 		->
 			GradeIncDir = LibDir/"lib"/Grade/FullArch/"inc",
-			install_subdir_file(LinkSucceeded, GradeIncDir,
-				ModuleName, "mih", HeaderSucceded1, !IO),
+            install_subdir_file(LinkSucceeded, GradeIncDir, ModuleName, "mih",
+                HeaderSucceded1, !IO),
 
 			% This is needed so that the file will be
 			% found in Mmake's VPATH.
 			IntDir = LibDir/"int",
-			install_subdir_file(LinkSucceeded, IntDir,
-				ModuleName, "mih", HeaderSucceded2, !IO),
+            install_subdir_file(LinkSucceeded, IntDir, ModuleName, "mih",
+                HeaderSucceded2, !IO),
 
 			HeaderSucceded = HeaderSucceded1 `and` HeaderSucceded2
 		;
 			HeaderSucceded = yes
 		),
 
-		globals__io_lookup_bool_option(intermodule_optimization,
-			Intermod, !IO),
+        globals__io_lookup_bool_option(intermodule_optimization, Intermod,
+            !IO),
 		(
 			Intermod = yes,
 			GradeIntDir = LibDir/"ints"/Grade,
-			install_subdir_file(LinkSucceeded, GradeIntDir,
-				ModuleName, "opt", OptSucceded, !IO)
+            install_subdir_file(LinkSucceeded, GradeIntDir, ModuleName, "opt",
+                OptSucceded, !IO)
 		;
 			Intermod = no,
 			OptSucceded = yes
@@ -881,9 +827,9 @@
 		Succeeded = no
 	).
 
-	% Install a file in the given directory, and in
-	% directory/Mercury/exts if the symlinks for the
-	% subdirectories couldn't be created (e.g. on Windows).
+    % Install a file in the given directory, and in directory/Mercury/exts
+    % if the symlinks for the subdirectories couldn't be created
+    % (e.g. on Windows).
 	%
 :- pred install_subdir_file(bool::in, dir_name::in, module_name::in,
 	string::in, bool::out, io::di, io::uo) is det.
@@ -894,8 +840,8 @@
 	install_file(FileName, InstallDir, Succeeded1, !IO),
 	(
 		SubdirLinkSucceeded = no,
-		install_file(FileName, InstallDir/"Mercury"/(Ext ++ "s"),
-			Succeeded2, !IO),
+        install_file(FileName, InstallDir/"Mercury"/(Ext ++ "s"), Succeeded2,
+            !IO),
 		Succeeded = Succeeded1 `and` Succeeded2
 	;
 		SubdirLinkSucceeded = yes,
@@ -943,10 +889,8 @@
 	;
 		LinkResult = no,
 		list__map_foldl(
-			(pred(Ext::in, MkDirResult::out, !.IO::di, !:IO::uo)
-					is det:-
-				make_directory(IntsSubdir/(Ext ++ "s"),
-					MkDirResult, !IO)
+            (pred(Ext::in, MkDirResult::out, !.IO::di, !:IO::uo) is det:-
+                make_directory(IntsSubdir/(Ext ++ "s"), MkDirResult, !IO)
 			), Subdirs, MkDirResults, !IO),
 		Results = Results0 ++ MkDirResults
 	),
@@ -972,13 +916,14 @@
 	list__map_foldl(make_install_symlink(GradeIntsSubdir),
 		["opt", "trans_opt"], LinkResults, !IO),
 	LinkResult = bool__and_list([LinkResult0 | LinkResults]),
-	( LinkResult = yes ->
+    (
+        LinkResult = yes,
 		Results = Results0
 	;
+        LinkResult = no,
 		make_directory(GradeIncSubdir/"mih", Result4, !IO),
 		make_directory(GradeIntsSubdir/"opts", Result5, !IO),
-		make_directory(GradeIntsSubdir/"trans_opts",
-			Result6, !IO),
+        make_directory(GradeIntsSubdir/"trans_opts", Result6, !IO),
 		Results = [Result4, Result5, Result6 | Results0]
 	),
 	print_mkdir_errors(Results, Result, !IO).
@@ -1024,17 +969,14 @@
 	linked_target_file_name(ModuleName, java_archive, JarFileName, !IO),
 
 	% Remove the symlinks created for `--use-grade-subdirs'.
-	globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs,
-		!IO),
+    globals__io_lookup_bool_option(use_grade_subdirs, UseGradeSubdirs, !IO),
 	globals__io_set_option(use_grade_subdirs, bool(no), !IO),
-	linked_target_file_name(ModuleName, executable, ThisDirExeFileName,
-		!IO),
+    linked_target_file_name(ModuleName, executable, ThisDirExeFileName, !IO),
 	linked_target_file_name(ModuleName, static_library,
 		ThisDirLibFileName, !IO),
 	linked_target_file_name(ModuleName, shared_library,
 		ThisDirSharedLibFileName, !IO),
-	linked_target_file_name(ModuleName, java_archive, ThisDirJarFileName,
-		!IO),
+    linked_target_file_name(ModuleName, java_archive, ThisDirJarFileName, !IO),
 	globals__io_set_option(use_grade_subdirs, bool(UseGradeSubdirs), !IO),
 
 	list__foldl2(remove_file,
@@ -1049,8 +991,7 @@
 	io::di, io::uo) is det.
 
 remove_init_files(ModuleName, !Info, !IO) :-
-	globals__io_lookup_string_option(object_file_extension, ObjExt,
-		!IO),
+    globals__io_lookup_string_option(object_file_extension, ObjExt, !IO),
 	globals__io_lookup_string_option(pic_object_file_extension, PicObjExt,
 		!IO),
 	globals__io_lookup_string_option(link_with_pic_object_file_extension,
@@ -1071,8 +1012,7 @@
 		[".used", ".prof", ".derived_schema", ".base_schema"],
 		!Info, !IO),
 
-	get_module_dependencies(ModuleName, MaybeImports,
-		!Info, !IO),
+    get_module_dependencies(ModuleName, MaybeImports, !Info, !IO),
 	(
 		MaybeImports = yes(Imports),
 		FactTableFiles = Imports ^ fact_table_deps
@@ -1082,8 +1022,7 @@
 	),
 
 	list__foldl2(
-		(pred(FactTableFile::in, !.Info::in, !:Info::out,
-				di, uo) is det -->
+        (pred(FactTableFile::in, !.Info::in, !:Info::out, di, uo) is det -->
 			fact_table_file_name(ModuleName, FactTableFile,
 				".c", no, FactTableCFile),
 			remove_file(FactTableCFile, !Info)
@@ -1092,36 +1031,28 @@
 	CCodeModule = foreign_language_module_name(ModuleName, c),
 	remove_target_file(CCodeModule, c_code, !Info, !IO),
 
-	%
 	% Remove object and assembler files.
-	%
 	list__foldl2(
-	    (pred(PIC::in, !.Info::in, !:Info::out, !.IO::di, !:IO::uo)
-			is det :-
+        (pred(PIC::in, !.Info::in, !:Info::out, !.IO::di, !:IO::uo) is det :-
 		remove_target_file(ModuleName, object_code(PIC), !Info, !IO),
 		remove_target_file(ModuleName, asm_code(PIC), !Info, !IO),
-		remove_target_file(ModuleName, foreign_object(PIC, c), !Info,
-			!IO),
+        remove_target_file(ModuleName, foreign_object(PIC, c), !Info, !IO),
 		list__foldl2(
 		    (pred(FactTableFile::in, !.Info::in, !:Info::out,
 				!.IO::di, !:IO::uo) is det :-
 			remove_target_file(ModuleName,
-				fact_table_object(PIC, FactTableFile), !Info,
-					!IO)
+                    fact_table_object(PIC, FactTableFile), !Info, !IO)
 		    ), FactTableFiles, !Info, !IO)
 	    ),
 	    [pic, link_with_pic, non_pic], !Info, !IO),
 
-	%
 	% Remove IL foreign code files.
-	%
 	CSharpModule = foreign_language_module_name(ModuleName, csharp),
 	remove_file(CSharpModule, foreign_language_file_extension(csharp),
 		!Info, !IO),
 	remove_target_file(CSharpModule, foreign_il_asm(csharp), !Info, !IO),
 
-	McppModule = foreign_language_module_name(ModuleName,
-		managed_cplusplus),
+    McppModule = foreign_language_module_name(ModuleName, managed_cplusplus),
 	remove_file(McppModule,
 		foreign_language_file_extension(managed_cplusplus),
 		!Info, !IO),
Index: compiler/make.util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make.util.m,v
retrieving revision 1.24
diff -u -b -r1.24 make.util.m
--- compiler/make.util.m	26 Apr 2005 04:32:49 -0000	1.24
+++ compiler/make.util.m	12 Oct 2005 09:07:06 -0000
@@ -1,12 +1,16 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
+%
 % File: make.util.m
 % Main author: stayl
 %
 % Assorted predicates used to implement `mmc --make'.
+%
 %-----------------------------------------------------------------------------%
 
 :- module make__util.
@@ -18,6 +22,7 @@
 % Versions of foldl which stop if the supplied predicate returns `no'
 % for any element of the list.
 %
+
 	% foldl2_pred_with_status(T, Succeeded, !Info).
 	%
 :- type foldl2_pred_with_status(T, Info, IO) ==
@@ -257,10 +262,10 @@
 
 %-----------------------------------------------------------------------------%
 
-foldl2_maybe_stop_at_error(KeepGoing, MakeTarget,
-		Targets, Success, !Info, !IO) :-
-	foldl2_maybe_stop_at_error_2(KeepGoing, MakeTarget, Targets,
-		yes, Success, !Info, !IO).
+foldl2_maybe_stop_at_error(KeepGoing, MakeTarget, Targets, Success,
+        !Info, !IO) :-
+    foldl2_maybe_stop_at_error_2(KeepGoing, MakeTarget, Targets, yes, Success,
+        !Info, !IO).
 
 :- pred foldl2_maybe_stop_at_error_2(bool::in,
 	foldl2_pred_with_status(T, Info, IO)::in(foldl2_pred_with_status),
@@ -276,8 +281,7 @@
 		)
 	->
 		!:Success = !.Success `and` NewSuccess,
-		foldl2_maybe_stop_at_error_2(KeepGoing, P, Ts,
-			!Success, !Info, !IO)
+        foldl2_maybe_stop_at_error_2(KeepGoing, P, Ts, !Success, !Info, !IO)
 	;
 		!:Success = no
 	).
@@ -301,8 +305,8 @@
 		)
 	->
 		!:Success = !.Success `and` NewSuccess,
-		foldl3_maybe_stop_at_error_2(KeepGoing, P, Ts,
-			!Success, !Acc, !Info, !IO)
+        foldl3_maybe_stop_at_error_2(KeepGoing, P, Ts, !Success, !Acc,
+            !Info, !IO)
 	;
 		!:Success = no
 	).
@@ -312,8 +316,7 @@
 build_with_module_options_and_output_redirect(ModuleName, ExtraOptions,
 		Build, Succeeded, !Info, !IO) :-
 	build_with_module_options(ModuleName, ExtraOptions,
-		build_with_module_options_and_output_redirect_2(ModuleName,
-			Build),
+        build_with_module_options_and_output_redirect_2(ModuleName, Build),
 		Succeeded, !Info, !IO).
 
 :- pred build_with_module_options_and_output_redirect_2(module_name::in,
@@ -323,8 +326,7 @@
 build_with_module_options_and_output_redirect_2(ModuleName, Build, AllOptions,
 		Succeeded, !Info, !IO) :-
 	build_with_output_redirect(ModuleName,
-		build_with_module_options_and_output_redirect_3(AllOptions,
-			Build),
+        build_with_module_options_and_output_redirect_3(AllOptions, Build),
 		Succeeded, !Info, !IO).
 
 :- pred build_with_module_options_and_output_redirect_3(list(string)::in,
@@ -369,10 +371,8 @@
 	bool::out, Info1::in, maybe(Info2)::out, io::di, io::uo) is det.
 
 build_with_module_options(InvokedByMmcMake, ModuleName, OptionVariables,
-		OptionArgs, ExtraOptions, Build, Succeeded, Info0, MaybeInfo,
-		!IO) :-
-	lookup_mmc_module_options(OptionVariables, ModuleName, OptionsResult,
-		!IO),
+        OptionArgs, ExtraOptions, Build, Succeeded, Info0, MaybeInfo, !IO) :-
+    lookup_mmc_module_options(OptionVariables, ModuleName, OptionsResult, !IO),
 	(
 		OptionsResult = no,
 		MaybeInfo = no,
@@ -397,9 +397,8 @@
 			InvokedByMake = []
 		),
 
-		AllOptionArgs = list__condense([InvokedByMake,
-			ModuleOptionArgs, OptionArgs,
-			ExtraOptions, UseSubdirs]),
+        AllOptionArgs = list__condense([InvokedByMake, ModuleOptionArgs,
+            OptionArgs, ExtraOptions, UseSubdirs]),
 		handle_options(AllOptionArgs, OptionsErrors, _, _, _, !IO),
 		(
 			OptionsErrors = [_ | _],
@@ -410,18 +409,15 @@
 			OptionsErrors = [],
 			Build(AllOptionArgs, Succeeded, Info0, Info, !IO),
 			MaybeInfo = yes(Info),
-			globals__io_set_globals(unsafe_promise_unique(Globals),
-				!IO)
+            globals__io_set_globals(unsafe_promise_unique(Globals), !IO)
 		)
 	).
 
 redirect_output(_ModuleName, MaybeErrorStream, !Info, !IO) :-
-	%
-	% Write the output to a temporary file first, so it's
-	% easy to just print the part of the error file
-	% that relates to the current command. It will
+    % Write the output to a temporary file first, so it's easy to just print
+    % the part of the error file that relates to the current command. It will
 	% be appended to the error file later.
-	%
+
 	io__make_temp(ErrorFileName, !IO),
 	io__open_output(ErrorFileName, ErrorFileRes, !IO),
 	(
@@ -445,8 +441,7 @@
 	io__open_input(TmpErrorFileName, TmpErrorInputRes, !IO),
 	(
 		TmpErrorInputRes = ok(TmpErrorInputStream),
-		module_name_to_file_name(ModuleName, ".err", yes,
-			ErrorFileName, !IO),
+        module_name_to_file_name(ModuleName, ".err", yes, ErrorFileName, !IO),
 		( set__member(ModuleName, !.Info ^ error_file_modules) ->
 			io__open_append(ErrorFileName, ErrorFileRes, !IO)
 		;
@@ -454,8 +449,8 @@
 		),
 		(
 			ErrorFileRes = ok(ErrorFileOutputStream),
-			globals__io_lookup_int_option(
-				output_compile_error_lines, LinesToWrite, !IO),
+            globals__io_lookup_int_option(output_compile_error_lines,
+                LinesToWrite, !IO),
 			io__output_stream(CurrentOutputStream, !IO),
 			io__input_stream_foldl2_io(TmpErrorInputStream,
 				write_error_char(ErrorFileOutputStream,
@@ -468,17 +463,14 @@
 				io__write_string("Error reading `", !IO),
 				io__write_string(TmpErrorFileName, !IO),
 				io__write_string("': ", !IO),
-				io__write_string(
-					io__error_message(TmpFileInputError),
-					!IO),
+                io__write_string(io__error_message(TmpFileInputError), !IO),
 				io__nl(!IO)
 			),
 
 			io__close_output(ErrorFileOutputStream, !IO),
 
 			!:Info = !.Info ^ error_file_modules :=
-				set__insert(!.Info ^ error_file_modules,
-					ModuleName)
+                set__insert(!.Info ^ error_file_modules, ModuleName)
 		;
 			ErrorFileRes = error(Error),
 			io__write_string("Error opening `", !IO),
@@ -517,15 +509,13 @@
 
 %-----------------------------------------------------------------------------%
 
-get_timestamp_file_timestamp(ModuleName - FileType,
-		MaybeTimestamp, !Info, !IO) :-
+get_timestamp_file_timestamp(ModuleName - FileType, MaybeTimestamp,
+        !Info, !IO) :-
 	globals__io_get_globals(Globals, !IO),
 	( TimestampExt = timestamp_extension(Globals, FileType) ->
-		module_name_to_file_name(ModuleName, TimestampExt, no,
-			FileName, !IO)
+        module_name_to_file_name(ModuleName, TimestampExt, no, FileName, !IO)
 	;
-		module_target_to_file_name(ModuleName, FileType, no,
-			FileName, !IO)
+        module_target_to_file_name(ModuleName, FileType, no, FileName, !IO)
 	),
 
 	% We should only ever look for timestamp files
@@ -576,19 +566,18 @@
 		MaybeTimestamp0 = error(_),
 		FileType = intermodule_interface
 	->
-		%
 		% If a `.opt' file in another directory doesn't exist,
 		% it just means that a library wasn't compiled with
 		% `--intermodule-optimization'.
-		%
+
 		get_module_dependencies(ModuleName, MaybeImports, !Info, !IO),
 		(
 			MaybeImports = yes(Imports),
 			Imports ^ module_dir \= dir__this_directory
 		->
 			MaybeTimestamp = ok(oldest_timestamp),
-			!:Info = !.Info ^ file_timestamps
-				^ elem(FileName) := MaybeTimestamp
+            !:Info = !.Info ^ file_timestamps ^ elem(FileName)
+                := MaybeTimestamp
 		;
 			MaybeTimestamp = MaybeTimestamp0
 		)
@@ -598,11 +587,9 @@
 
 get_file_name(Search, ModuleName - FileType, FileName, !Info, !IO) :-
 	( FileType = source ->
-		%
-		% In some cases the module name won't match the file
-		% name (module mdb.parse might be in parse.m or mdb.m),
-		% so we need to look up the file name here.
-		%
+        % In some cases the module name won't match the file name
+        % (module mdb.parse might be in parse.m or mdb.m), so we need to
+        % look up the file name here.
 		get_module_dependencies(ModuleName, MaybeImports, !Info, !IO),
 		(
 			MaybeImports = yes(Imports),
@@ -612,8 +599,7 @@
 
 			% Something has gone wrong generating the dependencies,
 			% so just take a punt (which probably won't work).
-			module_name_to_file_name(ModuleName, ".m",
-				no, FileName, !IO)
+            module_name_to_file_name(ModuleName, ".m", no, FileName, !IO)
 		)
 	;
 		globals__io_get_globals(Globals, !IO),
@@ -622,17 +608,15 @@
 			MaybeExt = yes(Ext),
 			(
 				Search = yes,
-				module_name_to_search_file_name(ModuleName,
-					Ext, FileName, !IO)
+                module_name_to_search_file_name(ModuleName, Ext, FileName, !IO)
 			;
 				Search = no,
-				module_name_to_file_name(ModuleName,
-					Ext, no, FileName, !IO)
+                module_name_to_file_name(ModuleName, Ext, no, FileName, !IO)
 			)
 		;
 			MaybeExt = no,
-			module_target_to_file_name(ModuleName, FileType,
-				no, Search, FileName, !IO)
+            module_target_to_file_name(ModuleName, FileType, no, Search,
+                FileName, !IO)
 		)
 	).
 
@@ -646,22 +630,19 @@
 			io__input_stream_name(FullFileName, !IO),
 			io__set_input_stream(OldInputStream, FileStream, !IO),
 			io__close_input(FileStream, !IO),
-			io__file_modification_time(FullFileName, TimeTResult,
-				!IO),
+            io__file_modification_time(FullFileName, TimeTResult, !IO),
 			(
 				TimeTResult = ok(TimeT),
 				Timestamp = time_t_to_timestamp(TimeT),
 				MaybeTimestamp = ok(Timestamp)
 			;
 				TimeTResult = error(Error),
-				MaybeTimestamp = error(
-					io__error_message(Error))
+                MaybeTimestamp = error(io__error_message(Error))
 			),
-			!:Info = !.Info ^ file_timestamps
-				^ elem(FileName) := MaybeTimestamp
+            !:Info = !.Info ^ file_timestamps ^ elem(FileName)
+                := MaybeTimestamp
 		;
-			MaybeTimestamp = error("file `" ++ FileName
-				++ "' not found")
+            MaybeTimestamp = error("file `" ++ FileName ++ "' not found")
 		)
 	).
 
@@ -672,8 +653,7 @@
 	MaybeOpt = search_for_file_type(FileType),
 	(
 		MaybeOpt = yes(SearchDirOpt),
-		globals__io_lookup_accumulating_option(SearchDirOpt,
-			SearchDirs0, !IO),
+        globals__io_lookup_accumulating_option(SearchDirOpt, SearchDirs0, !IO),
 		% Make sure the current directory is searched
 		% for C headers and libraries.
 		SearchDirs =
@@ -777,8 +757,7 @@
 	module_target_type::in, file_name::out, io::di, io::uo) is det.
 
 module_target_to_search_file_name(ModuleName, TargetType, FileName, !IO) :-
-	module_target_to_file_name(ModuleName, TargetType, no, yes, FileName,
-		!IO).
+    module_target_to_file_name(ModuleName, TargetType, no, yes, FileName, !IO).
 
 :- pred module_target_to_file_name(module_name::in, module_target_type::in,
 	bool::in, bool::in, file_name::out, io::di, io::uo) is det.
@@ -791,48 +770,42 @@
 		MaybeExt = yes(Ext),
 		(
 			Search = yes,
-			module_name_to_search_file_name(ModuleName, Ext,
-				FileName, !IO)
+            module_name_to_search_file_name(ModuleName, Ext, FileName, !IO)
 		;
 			Search = no,
-			module_name_to_file_name(ModuleName, Ext,
-				MkDir, FileName, !IO)
+            module_name_to_file_name(ModuleName, Ext, MkDir, FileName, !IO)
 		)
 	;
 		MaybeExt = no,
 		( TargetType = foreign_object(PIC, Lang) ->
 			(
 				ForeignModuleName =
-					foreign_language_module_name(
-						ModuleName, Lang)
+                    foreign_language_module_name(ModuleName, Lang)
 			->
-				module_target_to_file_name(ForeignModuleName,
-					object_code(PIC), MkDir, Search,
-					FileName, !IO)
+                module_target_to_file_name(ForeignModuleName, object_code(PIC),
+                    MkDir, Search, FileName, !IO)
 			;
 				error("module_target_to_file_name_2")
 			)
 		; TargetType = foreign_il_asm(Lang) ->
 			(
 				ForeignModuleName =
-					foreign_language_module_name(
-						ModuleName, Lang)
+                    foreign_language_module_name(ModuleName, Lang)
 			->
-				module_target_to_file_name(ForeignModuleName,
-					il_asm, MkDir, Search, FileName, !IO)
+                module_target_to_file_name(ForeignModuleName, il_asm, MkDir,
+                    Search, FileName, !IO)
 			;
 				error("module_target_to_file_name_2")
 			)
 		; TargetType = fact_table_object(PIC, FactFile) ->
 			maybe_pic_object_file_extension(PIC, Ext, !IO),
-			fact_table_file_name(ModuleName, FactFile, Ext,
-				MkDir, FileName, !IO)
+            fact_table_file_name(ModuleName, FactFile, Ext, MkDir, FileName,
+                !IO)
 		;
 			error("module_target_to_file_name_2")
 		)
 	).
 
-
 	% Note that we need a timestamp file for `.err' files because
 	% errors are written to the `.err' file even when writing interfaces.
 	% The timestamp is only updated when compiling to target code.
@@ -980,17 +953,15 @@
 			io__write_string("** Nothing to be done for `", !IO),
 			(
 				FileType = module_target(ModuleTargetType),
-				write_target_file(ModuleName -
-					ModuleTargetType, !IO)
+                write_target_file(ModuleName - ModuleTargetType, !IO)
 			;
 				FileType = linked_target(LinkedTargetType),
-				linked_target_file_name(ModuleName,
-					LinkedTargetType, FileName, !IO),
+                linked_target_file_name(ModuleName, LinkedTargetType, FileName,
+                    !IO),
 				io__write_string(FileName, !IO)
 			;
 				FileType = misc_target(_),
-				error("maybe_warn_up_to_date_target: " ++
-					"misc_target")
+                error("maybe_warn_up_to_date_target: misc_target")
 			),
 			io__write_string("'.\n", !IO)
 		;
Index: compiler/matching.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/matching.m,v
retrieving revision 1.4
diff -u -b -r1.4 matching.m
--- compiler/matching.m	22 Mar 2005 06:40:07 -0000	1.4
+++ compiler/matching.m	12 Oct 2005 09:32:14 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2001-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -54,9 +56,12 @@
 			include_all_candidates	:: bool
 		).
 
+:- type benefit_node.
+:- type cost_node.
+
 	% find_via_cell_vars(CellVar, CandidateFieldVars, CellVarFlushedLater,
 	%	BeforeFlush, AfterFlush, MatchingParams,
-	%	RealizedBenefitNodes, RealizedCostNodes, ViaCellVars)
+    %   RealizedBenefitNodes, RealizedCostNodes, ViaCellVars):
 	%
 	% CellVar gives a variable that corresponds to a memory cell, while
 	% CandidateArgVars gives a subset of the variables that are the fields
@@ -69,10 +74,7 @@
 	% should be accesed via CellVar. The outputs RealizedBenefitNodes
 	% and RealizedCostNodes give the benefit and cost nodes realized
 	% by this choice.
-
-:- type benefit_node.
-:- type cost_node.
-
+    %
 :- pred find_via_cell_vars(prog_var::in, set(prog_var)::in, bool::in,
 	set(prog_var)::in, list(set(prog_var))::in, matching_params::in,
 	set(benefit_node)::out, set(cost_node)::out, set(prog_var)::out)
@@ -94,17 +96,18 @@
 :- import_module std_util.
 :- import_module string.
 :- import_module term.
+:- import_module svmap.
+:- import_module svqueue.
 
-% The stack optimization graph is a bipartite graph, whose two node types
-% are cost nodes and benefit nodes. Each node represents a copy of an
-% operation, a load or a store. We have LoadCost copies of each load operation
-% and StoreCost copies of each store operation, where LoadCost and StoreCost
-% are parameters of find_via_cell_vars.
-%
-% We represent the stack optimization graph in the usual manner: as two maps,
-% with each map one kind of node to the set of nodes of the other types to
-% which it is adjacent.
-
+    % The stack optimization graph is a bipartite graph, whose two node types
+    % are cost nodes and benefit nodes. Each node represents a copy of an
+    % operation, a load or a store. We have LoadCost copies of each load
+    % operation and StoreCost copies of each store operation, where LoadCost
+    % and StoreCost are parameters of find_via_cell_vars.
+    %
+    % We represent the stack optimization graph in the usual manner:
+    % as two maps, with each map one kind of node to the set of nodes
+    % of the other types to which it is adjacent.
 :- type stack_slot_graph
 	--->	stack_slot_graph(
 			map(cost_node, set(benefit_node)),
@@ -123,10 +126,9 @@
 :- type cost_node --->		cost_node(cost_operation, int).
 :- type benefit_node --->	benefit_node(benefit_operation, int).
 
-% The field_costs_benefits structure records, for a given field variable,
-% the nodes of the cost we incur and the benefits we gain if we access that
-% field variable via the cell instead of via the stack.
-
+    % The field_costs_benefits structure records, for a given field variable,
+    % the nodes of the cost we incur and the benefits we gain if we access that
+    % field variable via the cell instead of via the stack.
 :- type	field_costs_benefits
 	--->	field_costs_benefits(
 			prog_var,
@@ -134,11 +136,11 @@
 			set(benefit_node)
 		).
 
-% Matchings are sets of edges, in which each node in the graph can occur at
-% most once. We represent the matching by mapping each node that is an endpoint
-% of an edge in the matching to the node at the other end of the edge.
-% If a node is not in the matching, it will not occur in the relevant map.
-
+    % Matchings are sets of edges, in which each node in the graph can occur at
+    % most once. We represent the matching by mapping each node that is an
+    % endpoint of an edge in the matching to the node at the other end of the
+    % edge. If a node is not in the matching, it will not occur in the relevant
+    % map.
 :- type matching
 	--->	matching(
 			map(cost_node, benefit_node),
@@ -168,8 +170,7 @@
 	),
 	set__to_sorted_list(OccurringCandidateFieldVars,
 		OccurringCandidateFieldVarList),
-	list__filter_map(
-		simplify_segment(CellVar, OccurringCandidateFieldVars),
+    list__filter_map(simplify_segment(CellVar, OccurringCandidateFieldVars),
 		AfterFlush, FilteredAfterFlush),
 	NumberedAfterFlush = number_segments(2, FilteredAfterFlush),
 	CostsBenefits = list__map(
@@ -195,10 +196,8 @@
 		set__init, RealizedBenefitNodes),
 	list__foldl(gather_costs, RealizedCostsBenefits,
 		set__init, RealizedCostNodes),
-	RealizedBenefitOps =
-		set__map(project_benefit_op, RealizedBenefitNodes),
-	RealizedCostOps =
-		set__map(project_cost_op, RealizedCostNodes),
+    RealizedBenefitOps = set__map(project_benefit_op, RealizedBenefitNodes),
+    RealizedCostOps = set__map(project_cost_op, RealizedCostNodes),
 	set__to_sorted_list(RealizedBenefitNodes, RealizedBenefitNodeList),
 	set__to_sorted_list(RealizedCostNodes, RealizedCostNodeList),
 	set__to_sorted_list(RealizedBenefitOps, RealizedBenefitOpList),
@@ -210,10 +209,8 @@
 	OpRatio = MatchingParams ^ one_path_op_ratio,
 	NodeRatio = MatchingParams ^ one_path_node_ratio,
 	(
-		RealizedBenefitOpCount * 100 >=
-			RealizedCostOpCount * OpRatio,
-		RealizedBenefitNodeCount * 100 >=
-			RealizedCostNodeCount * NodeRatio
+        RealizedBenefitOpCount * 100 >= RealizedCostOpCount * OpRatio,
+        RealizedBenefitNodeCount * 100 >= RealizedCostNodeCount * NodeRatio
 	->
 		ViaCellOccurringVars = ViaCellOccurringVars0
 		% Uncomment if you want to dump performance information into
@@ -237,12 +234,12 @@
 
 %-----------------------------------------------------------------------------%
 
-% Simplify_segment fails if the CellVar is in the SegmentVars since the cost
-% of executing such segments doesn't depend on whether we access field vars
-% via the cell var or via the stack. If CellVar is not in SegmentVars,
-% them simplify_segment succeeds after removing the non-candidate variables
-% from SegmentVars0.
-
+    % Simplify_segment fails if the CellVar is in the SegmentVars since the
+    % cost of executing such segments doesn't depend on whether we access
+    % field vars via the cell var or via the stack. If CellVar is not in
+    % SegmentVars, them simplify_segment succeeds after removing the
+    % non-candidate variables from SegmentVars0.
+    %
 :- pred simplify_segment(prog_var::in, set(prog_var)::in, set(prog_var)::in,
 	set(prog_var)::out) is semidet.
 
@@ -259,9 +256,9 @@
 
 %-----------------------------------------------------------------------------%
 
-% find_costs_benefits computes the costs and benefits of accessing the given
-% field variable FieldVar via the cell variable CellVar.
-
+    % Find_costs_benefits computes the costs and benefits of accessing the
+    % given field variable FieldVar via the cell variable CellVar.
+    %
 :- func find_costs_benefits(prog_var, set(prog_var),
 	assoc_list(int, set(prog_var)), bool, matching_params, prog_var)
 	= field_costs_benefits.
@@ -301,8 +298,7 @@
 		CostNodeSet, BenefitNodeSet).
 
 :- pred find_cell_var_loads_for_field(assoc_list(int, set(prog_var))::in,
-	prog_var::in, list(cost_operation)::in, list(cost_operation)::out)
-	is det.
+    prog_var::in, list(cost_operation)::in, list(cost_operation)::out) is det.
 
 find_cell_var_loads_for_field([], _, !CostOps).
 find_cell_var_loads_for_field([SegmentNum - SegmentVars | AfterFlush],
@@ -350,16 +346,16 @@
 
 %-----------------------------------------------------------------------------%
 
-% Accumulate all the benefit nodes.
-
+    % Accumulate all the benefit nodes.
+    %
 :- pred gather_benefits(field_costs_benefits::in, set(benefit_node)::in,
 	set(benefit_node)::out) is det.
 
 gather_benefits(field_costs_benefits(_, _, FieldBenefits), !Benefits) :-
 	set__union(FieldBenefits, !Benefits).
 
-% Accumulate all the cost nodes.
-
+    % Accumulate all the cost nodes.
+    %
 :- pred gather_costs(field_costs_benefits::in, set(cost_node)::in,
 	set(cost_node)::out) is det.
 
@@ -368,8 +364,8 @@
 
 %-----------------------------------------------------------------------------%
 
-% Create the stack slot optimization graph described in the paper.
-
+    % Create the stack slot optimization graph described in the paper.
+    %
 :- func create_graph(list(field_costs_benefits)) = stack_slot_graph.
 
 create_graph(CostsBenefits) = Graph :-
@@ -397,11 +393,9 @@
 add_cost_benefit_links(Benefits, Cost, !CostToBenefitsMap) :-
 	( map__search(!.CostToBenefitsMap, Cost, CostBenefits0) ->
 		set__union(CostBenefits0, Benefits, CostBenefits),
-		map__det_update(!.CostToBenefitsMap, Cost, CostBenefits,
-			!:CostToBenefitsMap)
+        svmap__det_update(Cost, CostBenefits, !CostToBenefitsMap)
 	;
-		map__det_insert(!.CostToBenefitsMap, Cost, Benefits,
-			!:CostToBenefitsMap)
+        svmap__det_insert(Cost, Benefits, !CostToBenefitsMap)
 	).
 
 :- pred add_benefit_cost_links(set(cost_node)::in, benefit_node::in,
@@ -411,17 +405,15 @@
 add_benefit_cost_links(Costs, Benefit, !BenefitToCostsMap) :-
 	( map__search(!.BenefitToCostsMap, Benefit, BenefitCosts0) ->
 		set__union(BenefitCosts0, Costs, BenefitCosts),
-		map__det_update(!.BenefitToCostsMap, Benefit, BenefitCosts,
-			!:BenefitToCostsMap)
+        svmap__det_update(Benefit, BenefitCosts, !BenefitToCostsMap)
 	;
-		map__det_insert(!.BenefitToCostsMap, Benefit, Costs,
-			!:BenefitToCostsMap)
+        svmap__det_insert(Benefit, Costs, !BenefitToCostsMap)
 	).
 
 %-----------------------------------------------------------------------------%
 
-% Find a maximal matching in the given graph.
-
+    % Find a maximal matching in the given graph.
+    %
 :- func maximal_matching(list(benefit_node), stack_slot_graph) = matching.
 
 maximal_matching(BenefitNodes, Graph) = Matching :-
@@ -460,17 +452,17 @@
 
 %-----------------------------------------------------------------------------%
 
-% Breadth-first search for an augmenting path.
-
-% Build an initial queue of all the unmatched benefit nodes, with empty paths.
-% Take the first element of the queue and see what nodes are reachable
-% from there. If one is unmatched return the path, otherwise add these nodes
-% to the queue if they haven't been visited before.
-
 :- type edge_list == assoc_list(benefit_node, cost_node).
 
 :- type benefit_node_and_edge_list == pair(benefit_node, edge_list).
 
+    % Breadth-first search for an augmenting path.
+
+    % Build an initial queue of all the unmatched benefit nodes, with empty
+    % paths. Take the first element of the queue and see what nodes are
+    % reachable from there. If one is unmatched return the path, otherwise add
+    % these nodes to the queue if they haven't been visited before.
+    %
 :- func find_first_path_bf(list(benefit_node), stack_slot_graph, matching)
 	= edge_list is semidet.
 
@@ -515,12 +507,12 @@
 		Unmatched = find_unmatched_cost(Matches)
 	).
 
-% For each node CostNode adjacent to BenefitNode, we have determined whether
-% they are matched (that information is in MaybeAdjBenefitNode).
-% If AdjBenefitNode has not been visited before (it is not in Seen0),
-% we add it to the queue with the path extended by the last arc
-% (BenefitNode - CostNode)
-
+    % For each node CostNode adjacent to BenefitNode, we have determined
+    % whether they are matched (that information is in MaybeAdjBenefitNode).
+    % If AdjBenefitNode has not been visited before (it is not in Seen0),
+    % we add it to the queue with the path extended by the last arc
+    % (BenefitNode - CostNode).
+    %
 :- pred add_alternates(assoc_list(cost_node, maybe(benefit_node))::in,
 	list(benefit_node)::in, list(benefit_node)::out, benefit_node::in,
 	edge_list::in, queue(benefit_node_and_edge_list)::in,
@@ -534,8 +526,7 @@
 		not list__member(AdjBenefitNode, !.Seen)
 	->
 		!:Seen = [AdjBenefitNode | !.Seen],
-		!:Queue = queue__put(!.Queue,
-			AdjBenefitNode - [BenefitNode - CostNode | Path])
+        svqueue__put(AdjBenefitNode - [BenefitNode - CostNode | Path], !Queue)
 	;
 		true
 	),
@@ -543,16 +534,16 @@
 
 %-----------------------------------------------------------------------------%
 
-% Find all the benefit nodes reachable from the cost nodes in the first
-% argument via alternating paths. The SelectedCostNodes are not matched,
-% so first we look for matched benefit nodes adjacent to them, since those
-% nodes are reachable. We then look at the cost nodes matched to those benefit
-% nodes, since the benefit nodes reachable from there are also reachable from
-% the original cost nodes.
-%
-% To ensure termination, we follow the matched link from a benefit node
-% only when that benefit node is first put into the reachable set.
-
+    % Find all the benefit nodes reachable from the cost nodes in the first
+    % argument via alternating paths. The SelectedCostNodes are not matched,
+    % so first we look for matched benefit nodes adjacent to them, since those
+    % nodes are reachable. We then look at the cost nodes matched to those
+    % benefit nodes, since the benefit nodes reachable from there are also
+    % reachable from the original cost nodes.
+    %
+    % To ensure termination, we follow the matched link from a benefit node
+    % only when that benefit node is first put into the reachable set.
+    %
 :- func reachable_by_alternating_path(list(cost_node), stack_slot_graph,
 	matching) = set(benefit_node).
 
@@ -567,14 +558,14 @@
 
 reachable_by_alternating_path(SelectedCostNodes, Graph, Matching,
 		!BenefitNodes) :-
-	( SelectedCostNodes = [] ->
-		true
+    (
+        SelectedCostNodes = []
 	;
+        SelectedCostNodes = [_ | _],
 		Graph = stack_slot_graph(CostToBenefitsMap, _),
 		list__foldl(adjacents(CostToBenefitsMap), SelectedCostNodes,
 			set__init, AdjBenefitNodes),
-		set__difference(!.BenefitNodes, AdjBenefitNodes,
-			NewBenefitNodes),
+        set__difference(!.BenefitNodes, AdjBenefitNodes, NewBenefitNodes),
 		set__union(AdjBenefitNodes, !BenefitNodes),
 		set__to_sorted_list(NewBenefitNodes, NewBenefitNodeList),
 		Matching = matching(_, BenefitToCostMap),
@@ -593,10 +584,10 @@
 
 %-----------------------------------------------------------------------------%
 
-% Given a list of cost nodes adjacent to a benefit node, find out for each of
-% those cost nodes whether it is linked to a benefit node by the given
-% matching, and if yes, to which one.
-
+    % Given a list of cost nodes adjacent to a benefit node, find out
+    % for each of those cost nodes whether it is linked to a benefit node
+    % by the given matching, and if yes, to which one.
+    %
 :- func map_adjs_to_matched_cost(list(cost_node), map(cost_node, benefit_node))
 	= assoc_list(cost_node, maybe(benefit_node)).
 
@@ -622,8 +613,7 @@
 compute_via_cell_vars([], _MarkedBenefits) = set__init.
 compute_via_cell_vars([FieldCostsBenefits | FieldsCostsBenefits],
 		MarkedBenefits) = ViaCellVars :-
-	ViaCellVars1 = compute_via_cell_vars(FieldsCostsBenefits,
-		MarkedBenefits),
+    ViaCellVars1 = compute_via_cell_vars(FieldsCostsBenefits, MarkedBenefits),
 	FieldCostsBenefits = field_costs_benefits(FieldVar, _, FieldBenefits),
 	set__intersect(FieldBenefits, MarkedBenefits, MarkedFieldBenefits),
 	( set__empty(MarkedFieldBenefits) ->
@@ -637,9 +627,9 @@
 
 %-----------------------------------------------------------------------------%
 
-% Get the set of benefit nodes in the first argument that are not matched
-% by a cost node in the given matching.
-
+    % Get the set of benefit nodes in the first argument that are not matched
+    % by a cost node in the given matching.
+    %
 :- func get_unmatched_benefit_nodes(list(benefit_node),
 	map(benefit_node, cost_node)) = list(benefit_node).
 
@@ -652,9 +642,9 @@
 		UnmatchedNodes = [Node | UnmatchedNodes1]
 	).
 
-% Get the set of cost nodes in the first argument that are not matched
-% by a benefit node in the given matching.
-
+    % Get the set of cost nodes in the first argument that are not matched
+    % by a benefit node in the given matching.
+    %
 :- func get_unmatched_cost_nodes(list(cost_node),
 	map(cost_node, benefit_node)) = list(cost_node).
 
@@ -669,12 +659,12 @@
 
 %-----------------------------------------------------------------------------%
 
-% Dump the results of the matching process to standard output to assist in
-% tracking down any correctness and performance problems with this module.
-% Using this predicate requires uncommenting the import of module unsafe,
-% the call to dump_results, and two lines computing one of the arguments of
-% that call.
-
+    % Dump the results of the matching process to standard output to assist in
+    % tracking down any correctness and performance problems with this module.
+    % Using this predicate requires uncommenting the import of module unsafe,
+    % the call to dump_results, and two lines computing one of the arguments of
+    % that call.
+    %
 :- pred dump_results(prog_var::in, set(prog_var)::in, list(prog_var)::in,
 	set(prog_var)::in, bool::in, set(prog_var)::in,
 	assoc_list(int, set(prog_var))::in,
Index: compiler/mmc_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mmc_analysis.m,v
retrieving revision 1.7
diff -u -b -r1.7 mmc_analysis.m
--- compiler/mmc_analysis.m	8 Aug 2005 02:33:10 -0000	1.7
+++ compiler/mmc_analysis.m	12 Oct 2005 09:52:22 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2003-2005 University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -26,8 +28,8 @@
 :- func module_name_to_module_id(module_name) = module_id.
 :- func module_id_to_module_name(module_id) = module_name.
 
-:- func pred_or_func_name_arity_to_func_id(pred_or_func,
-	string, arity, proc_id) = func_id.
+:- func pred_or_func_name_arity_to_func_id(pred_or_func, string, arity,
+    proc_id) = func_id.
 
 :- implementation.
 
Index: compiler/name_mangle.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/name_mangle.m,v
retrieving revision 1.12
diff -u -b -r1.12 name_mangle.m
--- compiler/name_mangle.m	22 Mar 2005 06:40:15 -0000	1.12
+++ compiler/name_mangle.m	12 Oct 2005 09:55:12 -0000
@@ -1,24 +1,26 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % File: name_mangle.m
-
+%
 % This module defines routines for generating and/or outputing identifiers
 % for modules, predicates/functions, and procedures in forms that are
 % syntactically acceptable in all our target languages, meaning C, Java
 % and MSIL.
-
+%
 % NOTE: some parts of the name mangling routines are defined in 
 % prog_foreign.m because they are required by the frontend of the compiler,
 % for generating makefile fragments etc.
-
+%
 % Warning: any changes to the name mangling algorithms implemented in this
 % module may also require changes to extras/dynamic_linking/name_mangle.m,
 % profiler/demangle.m, util/mdemangle.c and compiler/prog_foreign.m.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module backend_libs__name_mangle.
@@ -133,18 +135,18 @@
 	%
 proc_label_to_c_string(special_proc(Module, SpecialPredId, TypeModule,
 		TypeName, TypeArity, ModeInt), AddPrefix) = ProcLabelString :-
-	% figure out the LabelName
+    % Figure out the LabelName.
 	DummyArity = -1,	% not used by make_pred_or_func_name.
 	TypeCtor = qualified(TypeModule, TypeName) - TypeArity,
 	PredName = special_pred_name(SpecialPredId, TypeCtor),
 	LabelName = make_pred_or_func_name(unqualified(""), predicate,
 		unqualified(""), PredName, DummyArity, AddPrefix),
 
-	% figure out the ModeNumString
+    % Figure out the ModeNumString.
 	string__int_to_string(TypeArity, TypeArityString),
 	string__int_to_string(ModeInt, ModeNumString),
 
-	% mangle all the relevent names
+    % Mangle all the relevent names.
 	MangledModule = sym_name_mangle(Module),
 	MangledTypeModule = sym_name_mangle(TypeModule),
 	MangledTypeName = name_mangle(TypeName),
@@ -159,7 +161,7 @@
 	FullyQualifiedMangledTypeName = maybe_qualify_name(MangledModule,
 		QualifiedMangledTypeName),
 
-	% join it all together
+    % Join it all together.
 	string__append_list([LabelName, "_", FullyQualifiedMangledTypeName,
 		"_", TypeArityString, "_", ModeNumString],
 		ProcLabelString).
@@ -168,17 +170,16 @@
 	% defining module, predicate or function indicator, declaring module,
 	% predicate name, arity, and whether or not to add the
 	% mercury_label_prefix.
-
+    %
 :- func make_pred_or_func_name(module_name, pred_or_func, module_name, string,
 	arity, bool) = string.
 
-%
-% Warning: any changes to the name mangling algorithm here may also
-% require changes to extras/dynamic_linking/name_mangle.m, profiler/demangle.m,
-% util/mdemangle.c and compiler/prog_foreign.m.
-%
 make_pred_or_func_name(DefiningModule, PredOrFunc, DeclaringModule,
 		Name0, Arity, AddPrefix) = LabelName :-
+    % WARNING: any changes to the name mangling algorithm here may also
+    % require changes to extras/dynamic_linking/name_mangle.m,
+    % profiler/demangle.m, util/mdemangle.c and compiler/prog_foreign.m.
+
 	DeclaringModuleName = sym_name_mangle(DeclaringModule),
 	DefiningModuleName = sym_name_mangle(DefiningModule),
 	( dont_module_qualify_name(Name0, Arity) ->
@@ -189,27 +190,29 @@
 	% If this is a specialized version of a predicate defined
 	% in some other module, then it needs both module prefixes.
 	( DefiningModule \= DeclaringModule ->
-		string__append_list([DefiningModuleName, "__", LabelName0],
-			LabelName1)
+        LabelName1 = DefiningModuleName ++ "__" ++ LabelName0
 	;
 		LabelName1 = LabelName0
 	),
 	LabelName2 = name_mangle(LabelName1),
 	(
 		PredOrFunc = function,
-		string__append("fn__", LabelName2, LabelName3)
+        LabelName3 = "fn__" ++ LabelName2
 	;
 		PredOrFunc = predicate,
 		LabelName3 = LabelName2
 	),
-	( AddPrefix = yes ->
-		string__append(mercury_label_prefix, LabelName3, LabelName)
+    (
+        AddPrefix = yes,
+        LabelName = mercury_label_prefix ++ LabelName3
 	;
+        AddPrefix = no,
 		LabelName = LabelName3
 	).
 
 	% Define the conditions for which labels are printed
 	% without module qualification.
+    %
 :- pred dont_module_qualify_name(string::in, arity::in) is semidet.
 
 dont_module_qualify_name(Name, Arity) :-
@@ -220,11 +223,6 @@
 		string__prefix(Name, "__")
 	).
 
-	% Convert a Mercury predicate name into something that can form
-	% part of a C identifier.  This predicate is necessary because
-	% quoted names such as 'name with embedded spaces' are valid
-	% predicate names in Mercury.
-
 name_doesnt_need_mangling(Name) :-
 	string__is_alnum_or_underscore(Name),
 	\+ string__append("f_", _Suffix, Name).
@@ -237,7 +235,7 @@
 
 	% Produces a string of the form Module__Name, unless Module__
 	% is already a prefix of Name.
-
+    %
 :- func maybe_qualify_name(string, string) = string.
 
 maybe_qualify_name(Module0, Name0) = Name :-
Index: compiler/par_conj_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/par_conj_gen.m,v
retrieving revision 1.18
diff -u -b -r1.18 par_conj_gen.m
--- compiler/par_conj_gen.m	22 Mar 2005 06:40:16 -0000	1.18
+++ compiler/par_conj_gen.m	12 Oct 2005 09:58:45 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1998-2000,2002-2005 University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -19,6 +21,7 @@
 % declarative semantics as normal conjunction, but it has different (stricter)
 % rules for mode-correctness and determinism-correctness, and it has different
 % operational semantics.
+%
 %	[Operational semantics]
 %	- `,'/2 gives some operational guarantees that `&'/2 does not:
 %	  if `--no-reorder-conj' is set, there is an implied ordering
@@ -31,6 +34,7 @@
 %	  coroutining (not currently implemented) is being used, then the
 %	  data dependancies between the two goals will constrain the order
 %	  of execution at runtime.
+%
 %	[Mode correctness]
 %	- `,'/2 has a *sequential* behaviour `A, B' proves `A' *then*
 %	  proves `B'. Mode analysis only allows unidirectional data-
@@ -62,7 +66,7 @@
 % conjunct are distinct from those bound by the other conjuncts, the
 % unification of the instmaps is guarenteed to succeed.
 %
-% In principal, the determinism of a parallel conjunction is derived from
+% In principle, the determinism of a parallel conjunction is derived from
 % its conjuncts in the same way as the determinism of a conjunction but
 % because the current runtime implementation only allows model_det parallel
 % conjunction, determinism analysis works by inferring the determinism of
@@ -103,9 +107,8 @@
 
 :- import_module list.
 
-:- pred par_conj_gen__generate_par_conj(list(hlds_goal)::in,
-	hlds_goal_info::in, code_model::in, code_tree::out,
-	code_info::in, code_info::out) is det.
+:- pred generate_par_conj(list(hlds_goal)::in, hlds_goal_info::in,
+    code_model::in, code_tree::out, code_info::in, code_info::out) is det.
 
 %---------------------------------------------------------------------------%
 
@@ -135,7 +138,7 @@
 
 %---------------------------------------------------------------------------%
 
-par_conj_gen__generate_par_conj(Goals, GoalInfo, CodeModel, Code, !CI) :-
+generate_par_conj(Goals, GoalInfo, CodeModel, Code, !CI) :-
 	(
 		CodeModel = model_det
 	;
@@ -155,8 +158,7 @@
 	goal_info_get_instmap_delta(GoalInfo, Delta),
 	instmap__apply_instmap_delta(Initial, Delta, Final),
 	code_info__get_module_info(!.CI, ModuleInfo),
-	par_conj_gen__find_outputs(Variables, Initial, Final, ModuleInfo,
-		[], Outputs),
+    find_outputs(Variables, Initial, Final, ModuleInfo, [], Outputs),
 	list__length(Goals, NumGoals),
 	code_info__acquire_reg(r, RegLval, !CI),
 	code_info__acquire_temp_slot(sync_term, SyncSlot, !CI),
@@ -174,21 +176,19 @@
 	]),
 	code_info__release_reg(RegLval, !CI),
 	code_info__clear_all_registers(no, !CI),
-	par_conj_gen__generate_det_par_conj_2(Goals, 0, SyncSlot, SpSlot,
-		Initial, no, GoalCode, !CI),
+    generate_det_par_conj_2(Goals, 0, SyncSlot, SpSlot, Initial, no,
+        GoalCode, !CI),
 	code_info__release_temp_slot(SyncSlot, !CI),
 	Code = tree(tree(SaveCode, MakeTerm), GoalCode),
 	code_info__clear_all_registers(no, !CI),
-	par_conj_gen__place_all_outputs(Outputs, !CI).
+    place_all_outputs(Outputs, !CI).
 
-:- pred par_conj_gen__generate_det_par_conj_2(list(hlds_goal), int, lval, lval,
-		instmap, branch_end, code_tree, code_info, code_info).
-:- mode par_conj_gen__generate_det_par_conj_2(in, in, in, in,
-		in, in, out, in, out) is det.
-
-par_conj_gen__generate_det_par_conj_2([], _N, _SyncTerm, _SpSlot, _Initial,
-		_, empty, !CI).
-par_conj_gen__generate_det_par_conj_2([Goal | Goals], N, SyncTerm, SpSlot,
+:- pred generate_det_par_conj_2(list(hlds_goal)::in, int::in,
+    lval::in, lval::in, instmap::in, branch_end::in, code_tree::out,
+    code_info::in, code_info::out) is det.
+
+generate_det_par_conj_2([], _N, _SyncTerm, _SpSlot, _Initial, _, empty, !CI).
+generate_det_par_conj_2([Goal | Goals], N, SyncTerm, SpSlot,
 		Initial, MaybeEnd0, Code, !CI) :-
 	code_info__remember_position(!.CI, StartPos),
 	code_info__get_next_label(ThisConjunct, !CI),
@@ -205,12 +205,10 @@
 	goal_info_get_instmap_delta(GoalInfo, Delta),
 	instmap__apply_instmap_delta(Initial, Delta, Final),
 	code_info__get_module_info(!.CI, ModuleInfo),
-	par_conj_gen__find_outputs(Variables, Initial, Final, ModuleInfo,
-			[], TheseOutputs),
-	par_conj_gen__copy_outputs(!.CI, TheseOutputs, SpSlot, CopyCode),
+    find_outputs(Variables, Initial, Final, ModuleInfo, [], TheseOutputs),
+    copy_outputs(!.CI, TheseOutputs, SpSlot, CopyCode),
 	(
-		Goals = [_ | _]
-	->
+        Goals = [_ | _],
 		code_info__reset_to_position(StartPos, !CI),
 		code_info__get_total_stackslot_count(!.CI, NumSlots),
 		ForkCode = node([
@@ -226,6 +224,7 @@
 				- "start of the next conjunct"
 		])
 	;
+        Goals = [],
 		code_info__get_next_label(ContLab, !CI),
 		ForkCode = empty,
 		JoinCode = node([
@@ -235,22 +234,18 @@
 				- "end of parallel conjunction"
 		])
 	),
-	ThisCode = tree(
-		ForkCode,
-		tree(ThisGoalCode, tree(tree(SaveCode, CopyCode), JoinCode))
-	),
+    ThisCode = tree_list([ForkCode, ThisGoalCode, SaveCode, CopyCode,
+        JoinCode]),
 	N1 = N + 1,
-	par_conj_gen__generate_det_par_conj_2(Goals, N1, SyncTerm, SpSlot,
-		Initial, MaybeEnd, RestCode, !CI),
+    generate_det_par_conj_2(Goals, N1, SyncTerm, SpSlot, Initial, MaybeEnd,
+        RestCode, !CI),
 	Code = tree(ThisCode, RestCode).
 
-:- pred par_conj_gen__find_outputs(list(prog_var)::in,
-	instmap::in, instmap::in, module_info::in,
-	list(prog_var)::in, list(prog_var)::out) is det.
-
-par_conj_gen__find_outputs([], _Initial, _Final, _ModuleInfo, !Outputs).
-par_conj_gen__find_outputs([Var | Vars],  Initial, Final, ModuleInfo,
-		!Outputs) :-
+:- pred find_outputs(list(prog_var)::in, instmap::in, instmap::in,
+    module_info::in, list(prog_var)::in, list(prog_var)::out) is det.
+
+find_outputs([], _Initial, _Final, _ModuleInfo, !Outputs).
+find_outputs([Var | Vars],  Initial, Final, ModuleInfo, !Outputs) :-
 	instmap__lookup_var(Initial, Var, InitialInst),
 	instmap__lookup_var(Final, Var, FinalInst),
 	( mode_is_output(ModuleInfo, (InitialInst -> FinalInst)) ->
@@ -258,20 +253,17 @@
 	;
 		!:Outputs = !.Outputs
 	),
-	par_conj_gen__find_outputs(Vars, Initial, Final, ModuleInfo, !Outputs).
+    find_outputs(Vars, Initial, Final, ModuleInfo, !Outputs).
 
-:- pred par_conj_gen__copy_outputs(code_info::in, list(prog_var)::in, lval::in,
+:- pred copy_outputs(code_info::in, list(prog_var)::in, lval::in,
 	code_tree::out) is det.
 
-par_conj_gen__copy_outputs(_, [], _, empty).
-par_conj_gen__copy_outputs(CI, [Var | Vars], SpSlot, Code) :-
+copy_outputs(_, [], _, empty).
+copy_outputs(CI, [Var | Vars], SpSlot, Code) :-
 	code_info__get_variable_slot(CI, Var, SrcSlot),
-	(
-		SrcSlot = stackvar(SlotNum)
-	->
+    ( SrcSlot = stackvar(SlotNum) ->
 		NegSlotNum = (- SlotNum),
-		DestSlot = field(yes(0), lval(SpSlot),
-			const(int_const(NegSlotNum)))
+        DestSlot = field(yes(0), lval(SpSlot), const(int_const(NegSlotNum)))
 	;
 		error("par conj in model non procedure!")
 	),
@@ -280,13 +272,13 @@
 			- "copy result to parent stackframe"
 	]),
 	Code = tree(ThisCode, RestCode),
-	par_conj_gen__copy_outputs(CI, Vars, SpSlot, RestCode).
+    copy_outputs(CI, Vars, SpSlot, RestCode).
 
-:- pred par_conj_gen__place_all_outputs(list(prog_var)::in,
-	code_info::in, code_info::out) is det.
+:- pred place_all_outputs(list(prog_var)::in, code_info::in, code_info::out)
+    is det.
 
-par_conj_gen__place_all_outputs([], !CI).
-par_conj_gen__place_all_outputs([Var | Vars], !CI) :-
+place_all_outputs([], !CI).
+place_all_outputs([Var | Vars], !CI) :-
 	code_info__variable_locations(!.CI, VarLocations),
 	code_info__get_variable_slot(!.CI, Var, Slot),
 	(
@@ -297,4 +289,4 @@
 	;
 		code_info__set_var_location(Var, Slot, !CI)
 	),
-	par_conj_gen__place_all_outputs(Vars, !CI).
+    place_all_outputs(Vars, !CI).
Index: compiler/parse_tree.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/parse_tree.m,v
retrieving revision 1.11
diff -u -b -r1.11 parse_tree.m
--- compiler/parse_tree.m	15 Sep 2005 07:38:44 -0000	1.11
+++ compiler/parse_tree.m	12 Oct 2005 09:55:54 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
Index: compiler/pd_cost.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_cost.m,v
retrieving revision 1.23
diff -u -b -r1.23 pd_cost.m
--- compiler/pd_cost.m	24 Mar 2005 05:34:11 -0000	1.23
+++ compiler/pd_cost.m	12 Oct 2005 09:59:51 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1998-2005 University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -99,8 +101,7 @@
 	goal_info_get_nonlocals(GoalInfo, NonLocals),
 	pd_cost__unify(NonLocals, Unification, Cost).
 
-pd_cost__goal(foreign_proc(Attributes, _, _, Args, _, _) - _,
-		Cost) :-
+pd_cost__goal(foreign_proc(Attributes, _, _, Args, _, _) - _, Cost) :-
 	( may_call_mercury(Attributes) = will_not_call_mercury ->
 		Cost1 = 0
 	;
@@ -137,9 +138,11 @@
 	).
 
 pd_cost__unify(NonLocals, deconstruct(_, _, Args, _, CanFail, _), Cost) :-
-	( CanFail = can_fail ->
+    (
+        CanFail = can_fail,
 		pd_cost__simple_test(Cost0)
 	;
+        CanFail = cannot_fail,
 		Cost0 = 0
 	),
 	list__filter((pred(X::in) is semidet :-
Index: compiler/pd_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_debug.m,v
retrieving revision 1.14
diff -u -b -r1.14 pd_debug.m
--- compiler/pd_debug.m	30 Aug 2005 04:11:56 -0000	1.14
+++ compiler/pd_debug.m	12 Oct 2005 10:00:01 -0000
@@ -5,10 +5,12 @@
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
+%
 % File: pd_debug.m
 % Main author: stayl.
 %
 % Debugging routines for partial deduction.
+%
 %-----------------------------------------------------------------------------%
 
 :- module transform_hlds__pd_debug.
Index: compiler/pd_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_info.m,v
retrieving revision 1.20
diff -u -b -r1.20 pd_info.m
--- compiler/pd_info.m	30 Sep 2005 08:08:29 -0000	1.20
+++ compiler/pd_info.m	12 Oct 2005 10:03:04 -0000
@@ -1,12 +1,16 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1998-2001, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
+%
 % File: pd_info.m
 % Main author: stayl
 %
 % Types for deforestation.
+%
 %-----------------------------------------------------------------------------%
 
 :- module transform_hlds__pd_info.
@@ -28,8 +32,8 @@
 :- import_module set.
 :- import_module std_util.
 
-:- type pd_info --->
-	pd_info(
+:- type pd_info
+    --->    pd_info(
 		module_info		:: module_info,
 		maybe_unfold_info	:: maybe(unfold_info),
 		goal_version_index	:: goal_version_index,
@@ -43,13 +47,13 @@
 		useless_versions	:: useless_versions
 	).
 
-		% map from list of called preds in the
-		% conjunctions to the specialised versions.
+    % Map from list of called preds in the conjunctions
+    % to the specialised versions.
 :- type goal_version_index == map(list(pred_proc_id), list(pred_proc_id)).
 
 :- type useless_versions == set(pair(pred_proc_id)).
 
-		% map from version id to the info about the version.
+    % Map from version id to the info about the version.
 :- type version_index == map(pred_proc_id, version_info).
 
 :- pred pd_info_init(module_info::in, pd_arg_info::in, pd_info::out) is det.
@@ -226,7 +230,8 @@
 			parents		:: set(pred_proc_id),
 			pred_proc_id	:: pred_proc_id,
 					% current pred_proc_id
-			changed		:: bool,% has anything changed
+                changed		    :: bool,
+                                % has anything changed
 			size_delta	:: int,
 					% increase in size measured while
 					% processing this procedure
@@ -377,24 +382,29 @@
 
 	% Find the deforestation procedure which most closely
 	% matches the given goal.
+    %
 :- pred pd_info__search_version(pd_info::in, hlds_goal::in, maybe_version::out,
 	io::di, io::uo) is det.
 
 	% Create a new predicate for the input goal, returning a
 	% goal which calls the new predicate.
+    %
 :- pred pd_info__define_new_pred(pred_origin::in, hlds_goal::in,
 	pred_proc_id::out, hlds_goal::out, pd_info::in, pd_info::out) is det.
 
 	% Add a version to the table.
+    %
 :- pred pd_info__register_version(pred_proc_id::in, version_info::in,
 	pd_info::in, pd_info::out, io::di, io::uo) is det.
 
 	% Remove a version and make sure it is never recreated.
+    %
 :- pred pd_info__invalidate_version(pred_proc_id::in,
 	pd_info::in, pd_info::out) is det.
 
 	% Remove a version, but allow it to be recreated if it
 	% is used elsewhere.
+    %
 :- pred pd_info__remove_version(pred_proc_id::in,
 	pd_info::in, pd_info::out) is det.
 
@@ -415,8 +425,8 @@
 	--->	exact
 	;	more_general.
 
-:- type version_info --->
-	version_info(
+:- type version_info
+    --->    version_info(
 		version_orig_goal	:: hlds_goal,
 					% goal before unfolding.
 		version_deforest_calls	:: list(pred_proc_id),
@@ -475,16 +485,14 @@
 	Version = version_info(OldGoal, _, OldArgs, OldArgTypes,
 		OldInstMap, _, _, _, _),
 	(
-		pd_info__goal_is_more_general(ModuleInfo,
-			OldGoal, OldInstMap, OldArgs, OldArgTypes,
-			ThisGoal, ThisInstMap, VarTypes, VersionId, Version,
+		pd_info__goal_is_more_general(ModuleInfo, OldGoal, OldInstMap, OldArgs,
+            OldArgTypes, ThisGoal, ThisInstMap, VarTypes, VersionId, Version,
 			MaybeVersion1)
 	->
 		(
 			MaybeVersion1 = no_version,
-			pd_info__get_matching_version(ModuleInfo,
-				ThisGoal, ThisInstMap, VarTypes, VersionIds,
-				Versions, MaybeVersion)
+			pd_info__get_matching_version(ModuleInfo, ThisGoal, ThisInstMap,
+                VarTypes, VersionIds, Versions, MaybeVersion)
 		;
 			MaybeVersion1 = version(exact, _, _, _, _),
 			MaybeVersion = MaybeVersion1
@@ -495,18 +503,17 @@
 				ThisInstMap, VarTypes, VersionIds,
 				Versions, MaybeVersion2),
 			pd_info__pick_version(ModuleInfo, PredProcId, Renaming,
-				TypeSubn, MoreGeneralVersion, MaybeVersion2,
-				MaybeVersion)
+				TypeSubn, MoreGeneralVersion, MaybeVersion2, MaybeVersion)
 		)
 	;
-		pd_info__get_matching_version(ModuleInfo, ThisGoal,
-			ThisInstMap, VarTypes, VersionIds,
-			Versions, MaybeVersion)
+		pd_info__get_matching_version(ModuleInfo, ThisGoal, ThisInstMap,
+            VarTypes, VersionIds, Versions, MaybeVersion)
 	).
 
 %-----------------------------------------------------------------------------%
 
 	% Choose between two versions.
+    %
 :- pred pd_info__pick_version(module_info::in, pred_proc_id::in,
 	map(prog_var, prog_var)::in, tsubst::in, version_info::in,
 	maybe_version::in, maybe_version::out) is det.
@@ -571,6 +578,7 @@
 
 	% Check that all the insts in the old version are at least as
 	% general as the insts in the new version.
+    %
 :- pred pd_info__check_insts(module_info::in, list(prog_var)::in,
 	map(prog_var, prog_var)::in, instmap::in, instmap::in, vartypes::in,
 	version_is_exact::in, version_is_exact::out) is semidet.
@@ -671,8 +679,8 @@
 		Calls = [FirstCall | _],
 		list__last(Calls, LastCall)
 	->
-			% Make sure we never create another version to
-			% deforest this pair of calls.
+        % Make sure we never create another version to deforest
+        % this pair of calls.
 		pd_info_get_useless_versions(!.PDInfo, Useless0),
 		set__insert(Useless0, FirstCall - LastCall, Useless),
 		pd_info_set_useless_versions(Useless, !PDInfo)
Index: compiler/pd_term.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/pd_term.m,v
retrieving revision 1.10
diff -u -b -r1.10 pd_term.m
--- compiler/pd_term.m	22 Mar 2005 06:40:17 -0000	1.10
+++ compiler/pd_term.m	12 Oct 2005 10:05:23 -0000
@@ -1,14 +1,18 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1998-2001, 2003-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
+%
 % File: pd_term.m
 % Main author: stayl
 %
 % Termination checking for the deforestation process.
 % There are two places where care must be taken to ensure
 % termination of the process:
+%
 % - when unfolding a call to a recursive procedure
 % - when creating a new version, to avoid creating an infinite sequence of
 % 	new versions for which folding never occurs.
@@ -24,6 +28,7 @@
 % the check succeeds and the new argument sizes are recorded.
 %
 % There are many possible improvements to this:
+%
 % - Partition on subterms of arguments rather than whole arguments - useful
 % 	when partially instantiated structures are present.
 % - Use homeomorphic embedding instead of term sizes as suggested in
@@ -46,11 +51,12 @@
 :- import_module std_util.
 
 	% pd_term__global_check(Module, CallGoal1, BetweenGoals, CallGoal2,
-	% 	InstMap, Versions, Info0, Info, Result)
+    %   InstMap, Versions, Info0, Info, Result):
 	%
 	% Check whether a new version can be created for the conjunction
 	% (CallGoal1, BetweenGoals, CallGoal2) without the deforestation
 	% process looping.
+    %
 :- pred pd_term__global_check(module_info::in, hlds_goal::in,
 	list(hlds_goal)::in, maybe(hlds_goal)::in, instmap::in,
 	version_index::in, global_term_info::in,
@@ -69,6 +75,7 @@
 
 	% Check whether a call can be unfolded without the
 	% unfolding process looping.
+    %
 :- pred pd_term__local_check(module_info::in, hlds_goal::in, instmap::in,
 	local_term_info::in, local_term_info::out) is semidet.
 
@@ -79,8 +86,9 @@
 :- pred pd_term__get_proc_term_info(local_term_info::in, pred_proc_id::in,
 	pd_proc_term_info::out) is semidet.
 
-	% Update the global termination information when we find
-	% out the pred_proc_id that has been assigned to a version.
+    % Update the global termination information when we find out the
+    % pred_proc_id that has been assigned to a version.
+    %
 :- pred pd_term__update_global_term_info(proc_pair::in, pred_proc_id::in,
 	int::in, global_term_info::in,global_term_info::out) is det.
 
@@ -104,8 +112,8 @@
 :- import_module require.
 :- import_module set.
 
-:- type global_term_info --->
-	global_term_info(
+:- type global_term_info
+    --->    global_term_info(
 		single_covering_goals,
 		multiple_covering_goals
 	).
@@ -148,13 +156,11 @@
 		Hd = (pred(List::in, Head::out) is semidet :-
 			List = [Head | _]
 		),
-		expand_calls(Hd, Versions, proc(PredId1, ProcId1),
-			FirstPredProcId),
+        expand_calls(Hd, Versions, proc(PredId1, ProcId1), FirstPredProcId),
 		(
-			MaybeLaterGoal = yes(
-				call(PredId2, ProcId2, _, _, _, _) - _),
-			expand_calls(list__last, Versions,
-				proc(PredId2, ProcId2), LastPredProcId),
+            MaybeLaterGoal = yes(call(PredId2, ProcId2, _, _, _, _) - _),
+            expand_calls(list__last, Versions, proc(PredId2, ProcId2),
+                LastPredProcId),
 			MaybeLastPredProcId = yes(LastPredProcId)
 		;
 			MaybeLaterGoal = no,
@@ -171,35 +177,29 @@
 				Length < MaxLength
 			->
 				Result = ok(ProcPair, Length),
-					% set the maybe(pred_proc_id)
-					% when we create the new predicate
+                % Set the maybe(pred_proc_id) when we create the new predicate.
 				map__set(MultipleGoalCover0, ProcPair,
 					Length - no, MultipleGoalCover)
 			;
 				Length = MaxLength,
-				MaybeCoveringPredProcId =
-					yes(CoveringPredProcId)
+                MaybeCoveringPredProcId = yes(CoveringPredProcId)
 			->
-				% If the goals match, check that the
-				% argument insts decrease.
-				% If not, we may need to do a
-				% generalisation step.
-				Result = possible_loop(ProcPair, Length,
-						CoveringPredProcId),
+                % If the goals match, check that the argument insts decrease.
+                 %If not, we may need to do a generalisation step.
+                Result = possible_loop(ProcPair, Length, CoveringPredProcId),
 				MultipleGoalCover = MultipleGoalCover0
 			;
 				Result = loop,
 				MultipleGoalCover = MultipleGoalCover0
 			)
 		;
-			% We haven't seen this pair before, so it must
-			% be okay to specialise.
+            % We haven't seen this pair before, so it must be okay
+            % to specialise.
 			Result = ok(ProcPair, Length),
 
-			% set the maybe(pred_proc_id)
-			% when we create the new predicate
-			map__set(MultipleGoalCover0, ProcPair,
-				Length - no, MultipleGoalCover)
+            % Set the maybe(pred_proc_id) when we create the new predicate.
+            map__set(MultipleGoalCover0, ProcPair, Length - no,
+                MultipleGoalCover)
 		),
 		SingleGoalCover = SingleGoalCover0
 	;
@@ -216,6 +216,7 @@
 	% 	new3 ......... pred1
 	% Instead, we expand to predicates from the original program,
 	% which must contain a finite number of pairs of pred_proc_ids.
+    %
 :- pred expand_calls(pred(list(pred_proc_id), pred_proc_id)::
 	in(pred(in, out) is semidet), version_index::in,
 	pred_proc_id::in, pred_proc_id::out) is semidet.
@@ -236,8 +237,7 @@
 	( map__search(!.Cover, proc(PredId, ProcId), CoveringInstSizes0) ->
 		pd_term__do_local_check(ModuleInfo, InstMap, Args,
 			CoveringInstSizes0, CoveringInstSizes),
-		map__set(!.Cover, proc(PredId, ProcId), CoveringInstSizes,
-			!:Cover)
+        map__set(!.Cover, proc(PredId, ProcId), CoveringInstSizes, !:Cover)
 	;
 		pd_term__initial_sizes(ModuleInfo, InstMap,
 			Args, 1, ArgInstSizes),
@@ -254,8 +254,7 @@
 	( NewTotal < OldTotal ->
 		NewSizes = NewSizes1
 	;
-		pd_term__split_out_non_increasing(OldSizes, NewSizes1,
-			yes, NewSizes)
+        pd_term__split_out_non_increasing(OldSizes, NewSizes1, yes, NewSizes)
 	).
 
 %-----------------------------------------------------------------------------%
@@ -299,8 +298,7 @@
 %-----------------------------------------------------------------------------%
 
 :- pred pd_term__split_out_non_increasing(assoc_list(int, int)::in,
-	assoc_list(int, int)::in, bool::out, assoc_list(int, int)::out)
-	is semidet.
+    assoc_list(int, int)::in, bool::out, assoc_list(int, int)::out) is semidet.
 
 pd_term__split_out_non_increasing([], [], no, []).
 pd_term__split_out_non_increasing([_|_], [], _, _) :-
Index: compiler/process_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/process_util.m,v
retrieving revision 1.15
diff -u -b -r1.15 process_util.m
--- compiler/process_util.m	26 Apr 2005 04:32:49 -0000	1.15
+++ compiler/process_util.m	12 Oct 2005 10:08:11 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2002-2005 University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -24,8 +26,7 @@
 :- type post_signal_cleanup(Info) == pred(Info, Info, io, io).
 :- inst post_signal_cleanup == (pred(in, out, di, uo) is det).
 
-	% build_with_check_for_interrupt(Build, Cleanup,
-	%	Succeeded, Info0, Info)
+    % build_with_check_for_interrupt(Build, Cleanup, Succeeded, !Info):
 	%
 	% Apply `Build' with signal handlers installed to check for
 	% signals which would normally kill the process. If a signal
@@ -56,7 +57,7 @@
 	%
 :- pred can_fork is semidet.
 
-	% call_in_forked_process(P, AltP, Succeeded)
+    % call_in_forked_process(P, AltP, Succeeded):
 	%
 	% Execute `P' in a separate process.
 	%
@@ -96,12 +97,13 @@
 	( Signalled = 1 ->
 		Succeeded = no,
 		globals__io_lookup_bool_option(verbose_make, Verbose, !IO),
-		( Verbose = yes ->
+        (
+            Verbose = yes,
 			io__write_string("** Received signal ", !IO),
 			io__write_int(Signal, !IO),
 			io__write_string(", cleaning up.\n", !IO)
 		;
-			true
+            Verbose = no
 		),
 		Cleanup(!Info, !IO),
 
@@ -216,9 +218,9 @@
 #endif
 }").
 
-	% Restore all signal handlers to default values in the child
-	% so that the child will be killed by the signals the parent
-	% is catching.
+    % Restore all signal handlers to default values in the child so that
+    % the child will be killed by the signals the parent is catching.
+    %
 :- pred setup_child_signal_handlers(io::di, io::uo) is det.
 
 setup_child_signal_handlers(!IO) :-
@@ -275,8 +277,7 @@
 		( ForkStatus = 1 ->
 			Success = no
 		;
-			Status = io__handle_system_command_exit_status(
-				CallStatus),
+            Status = io__handle_system_command_exit_status(CallStatus),
 			Success = (Status = ok(exited(0)) -> yes ; no)
 		)
 	;
@@ -303,8 +304,8 @@
 	error("call_in_forked_process_2").
 
 :- pragma foreign_proc("C",
-	call_in_forked_process_2(Pred::in(io_pred),
-		ForkStatus::out, Status::out, IO0::di, IO::uo),
+    call_in_forked_process_2(Pred::in(io_pred), ForkStatus::out, Status::out,
+        IO0::di, IO::uo),
 	[may_call_mercury, promise_pure, tabled_for_io],
 "{
 #ifdef MC_CAN_FORK
@@ -392,8 +393,10 @@
 }").
 
 	% call_child_process_io_pred(P, ExitStatus).
+    %
 :- pred call_child_process_io_pred(io_pred::in(io_pred), int::out,
 	io::di, io::uo) is det.
+
 :- pragma export(call_child_process_io_pred(in(io_pred), out, di, uo),
 	"MC_call_child_process_io_pred").
 
Index: compiler/string_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/string_switch.m,v
retrieving revision 1.47
diff -u -b -r1.47 string_switch.m
--- compiler/string_switch.m	22 Mar 2005 06:40:26 -0000	1.47
+++ compiler/string_switch.m	12 Oct 2005 09:00:58 -0000
@@ -1,16 +1,18 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1994-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %-----------------------------------------------------------------------------%
-
+%
 % string_switch.m
-
+%
 % For switches on strings, we generate a hash table using open addressing
 % to resolve hash conflicts.
-
+%
 % Author: fjh.
-
+%
 %-----------------------------------------------------------------------------%
 
 :- module ll_backend__string_switch.
@@ -25,7 +27,7 @@
 :- import_module ll_backend__llds.
 :- import_module parse_tree__prog_data.
 
-:- pred string_switch__generate(cases_list::in, prog_var::in, code_model::in,
+:- pred generate_string_switch(cases_list::in, prog_var::in, code_model::in,
 	can_fail::in, hlds_goal_info::in, label::in,
 	branch_end::in, branch_end::out, code_tree::out,
 	code_info::in, code_info::out) is det.
@@ -50,7 +52,7 @@
 :- import_module std_util.
 :- import_module string.
 
-string_switch__generate(Cases, Var, CodeModel, _CanFail, SwitchGoalInfo,
+generate_string_switch(Cases, Var, CodeModel, _CanFail, SwitchGoalInfo,
 		EndLabel, !MaybeEnd, Code, !CI) :-
 	code_info__produce_variable(Var, VarCode, VarRval, !CI),
 	code_info__acquire_reg(r, SlotReg, !CI),
@@ -59,169 +61,137 @@
 	code_info__get_next_label(FailLabel, !CI),
 	code_info__get_next_label(JumpLabel, !CI),
 
-	% Determine how big to make the hash table.
-	% Currently we round the number of cases up to the nearest
-	% power of two, and then double it.  This should hopefully
-	% ensure that we don't get too many hash collisions.
-	%
+    % Determine how big to make the hash table. Currently we round the number
+    % of cases up to the nearest power of two, and then double it.
+    % This should hopefully ensure that we don't get too many hash collisions.
+
 	list__length(Cases, NumCases),
 	int__log2(NumCases, LogNumCases),
 	int__pow(2, LogNumCases, RoundedNumCases),
 	TableSize = 2 * RoundedNumCases,
 	HashMask = TableSize - 1,
 
-	% Compute the hash table
-	%
+    % Compute the hash table.
 	switch_util__string_hash_cases(Cases, HashMask, HashValsMap),
 	map__to_assoc_list(HashValsMap, HashValsList),
-	switch_util__calc_hash_slots(HashValsList, HashValsMap,
-		HashSlotsMap),
+    switch_util__calc_hash_slots(HashValsList, HashValsMap, HashSlotsMap),
+
+    % Note that it is safe to release the registers now, even though we haven't
+    % yet generated all the code which uses them, because that code will be
+    % executed before the code for the cases (which might reuse those
+    % registers), and because that code is generated manually (below)
+    % so we don't need the reg info to be valid when we generate it.
 
-		% Note that it is safe to release the registers now,
-		% even though we haven't yet generated all the code
-		% which uses them, because that code will be executed
-		% before the code for the cases (which might reuse those
-		% registers), and because that code is generated manually
-		% (below) so we don't need the reg info to be valid when
-		% we generate it.
 	code_info__release_reg(SlotReg, !CI),
 	code_info__release_reg(StringReg, !CI),
 
-		% Generate the code for when the hash lookup fails.
-		% This must be done before gen_hash_slots, since
-		% we want to use the exprn_info corresponding to
-		% the start of the switch, not to the end of the last case.
+    % Generate the code for when the hash lookup fails. This must be done
+    % before gen_hash_slots, since we want to use the exprn_info corresponding
+    % to the start of the switch, not to the end of the last case.
 	code_info__generate_failure(FailCode, !CI),
 
-		% Generate the code etc. for the hash table
-		%
-	string_switch__gen_hash_slots(0, TableSize, HashSlotsMap, CodeModel,
-		SwitchGoalInfo, FailLabel, EndLabel, !MaybeEnd,
-		Strings, Labels, NextSlots, SlotsCode, !CI),
+    % Generate the code etc. for the hash table.
+    gen_hash_slots(0, TableSize, HashSlotsMap, CodeModel, SwitchGoalInfo,
+        FailLabel, EndLabel, !MaybeEnd, Strings, Labels, NextSlots,
+        SlotsCode, !CI),
 
 		% Generate code which does the hash table lookup
 	(
-		add_static_cell_natural_types(NextSlots, NextSlotsTableAddr,
-			!CI),
-		NextSlotsTable = const(
-			data_addr_const(NextSlotsTableAddr, no)),
+        add_static_cell_natural_types(NextSlots, NextSlotsTableAddr, !CI),
+        NextSlotsTable = const(data_addr_const(NextSlotsTableAddr, no)),
 		add_static_cell_natural_types(Strings, StringTableAddr, !CI),
 		StringTable = const(data_addr_const(StringTableAddr, no)),
 		HashLookupCode = node([
-			comment("hashed string switch") -
-			  "",
-			assign(SlotReg, binop(&, unop(hash_string, VarRval),
-						const(int_const(HashMask)))) -
-			  "compute the hash value of the input string",
-			label(LoopLabel) -
-			  "begin hash chain loop",
-			assign(StringReg, binop(array_index(elem_type_string),
-					StringTable, lval(SlotReg))) -
-			  "lookup the string for this hash slot",
+            comment("hashed string switch") - "",
+            assign(SlotReg,
+                binop(&, unop(hash_string, VarRval),
+                    const(int_const(HashMask))))
+                - "compute the hash value of the input string",
+            label(LoopLabel) - "begin hash chain loop",
+            assign(StringReg,
+                binop(array_index(elem_type_string),
+                    StringTable, lval(SlotReg)))
+                - "lookup the string for this hash slot",
 			if_val(binop(and, lval(StringReg),
-				binop(str_eq, lval(StringReg), VarRval)),
-					label(JumpLabel)) -
-			  "did we find a match?",
-			assign(SlotReg, binop(array_index(elem_type_int),
-					NextSlotsTable, lval(SlotReg))) -
-			  "not yet, so get next slot in hash chain",
+                binop(str_eq, lval(StringReg), VarRval)), label(JumpLabel))
+                - "did we find a match?",
+            assign(SlotReg,
+                binop(array_index(elem_type_int),
+                    NextSlotsTable, lval(SlotReg)))
+                - "not yet, so get next slot in hash chain",
 			if_val(binop(>=, lval(SlotReg), const(int_const(0))),
-				label(LoopLabel)) -
-			  "keep searching until we reach the end of the chain",
-			label(FailLabel) -
-			  "no match, so fail"
+                label(LoopLabel))
+                - "keep searching until we reach the end of the chain",
+            label(FailLabel) - "no match, so fail"
 		])
 	),
 	JumpCode = node([
-		label(JumpLabel) -
-			"we found a match",
-		computed_goto(lval(SlotReg), Labels) -
-			"jump to the corresponding code"
+        label(JumpLabel) - "we found a match",
+        computed_goto(lval(SlotReg), Labels) - "jump to the corresponding code"
 	]),
-		% Collect all the generated code fragments together
-	Code =
-		tree(VarCode,
-		tree(HashLookupCode,
-		tree(FailCode,
-		tree(JumpCode,
-		     SlotsCode)))).
+    Code = tree_list([VarCode, HashLookupCode, FailCode, JumpCode, SlotsCode]).
 
-:- pred string_switch__gen_hash_slots(int::in, int::in,
+:- pred gen_hash_slots(int::in, int::in,
 	map(int, hash_slot)::in, code_model::in, hlds_goal_info::in, label::in,
 	label::in, branch_end::in, branch_end::out,
 	list(rval)::out, list(label)::out, list(rval)::out, code_tree::out,
 	code_info::in, code_info::out) is det.
 
-string_switch__gen_hash_slots(Slot, TableSize, HashSlotMap, CodeModel,
-		SwitchGoalInfo, FailLabel, EndLabel, !MaybeEnd,
-		Strings, Labels, NextSlots, Code, !CI) :-
+gen_hash_slots(Slot, TableSize, HashSlotMap, CodeModel, SwitchGoalInfo,
+        FailLabel, EndLabel, !MaybeEnd, Strings, Labels, NextSlots,
+        Code, !CI) :-
 	( Slot = TableSize ->
 		Strings = [],
 		Labels = [],
 		NextSlots = [],
-		Code = node([
-			label(EndLabel) - "end of hashed string switch"
-		])
+        Code = node([label(EndLabel) - "end of hashed string switch"])
 	;
-		string_switch__gen_hash_slot(Slot, TableSize, HashSlotMap,
-			CodeModel, SwitchGoalInfo, FailLabel, EndLabel,
-			!MaybeEnd, String, Label, NextSlot, SlotCode, !CI),
+        gen_hash_slot(Slot, TableSize, HashSlotMap, CodeModel, SwitchGoalInfo,
+            FailLabel, EndLabel, !MaybeEnd, String, Label, NextSlot,
+            SlotCode, !CI),
 		Slot1 = Slot + 1,
-		string_switch__gen_hash_slots(Slot1, TableSize, HashSlotMap,
-			CodeModel, SwitchGoalInfo, FailLabel, EndLabel,
-			!MaybeEnd, Strings0, Labels0, NextSlots0, Code0, !CI),
+        gen_hash_slots(Slot1, TableSize, HashSlotMap, CodeModel,
+            SwitchGoalInfo, FailLabel, EndLabel, !MaybeEnd, Strings0, Labels0,
+            NextSlots0, Code0, !CI),
 		Strings = [String | Strings0],
 		Labels = [Label | Labels0],
 		NextSlots = [NextSlot | NextSlots0],
 		Code = tree(SlotCode, Code0)
 	).
 
-:- pred string_switch__gen_hash_slot(int::in, int::in, map(int, hash_slot)::in,
+:- pred gen_hash_slot(int::in, int::in, map(int, hash_slot)::in,
 	code_model::in, hlds_goal_info::in, label::in, label::in,
 	branch_end::in, branch_end::out, rval::out, label::out, rval::out,
 	code_tree::out, code_info::in, code_info::out) is det.
 
-string_switch__gen_hash_slot(Slot, TblSize, HashSlotMap, CodeModel,
-		SwitchGoalInfo, FailLabel, EndLabel, !MaybeEnd,
-		StringRval, Label, NextSlotRval, Code, !CI) :-
+gen_hash_slot(Slot, TblSize, HashSlotMap, CodeModel, SwitchGoalInfo, FailLabel,
+        EndLabel, !MaybeEnd, StringRval, Label, NextSlotRval, Code, !CI) :-
 	( map__search(HashSlotMap, Slot, hash_slot(Case, Next)) ->
 		NextSlotRval = const(int_const(Next)),
 		Case = case(_, ConsTag, _, Goal),
 		( ConsTag = string_constant(String0) ->
 			String = String0
 		;
-			error("string_switch__gen_hash_slots: string expected")
+            error("gen_hash_slots: string expected")
 		),
 		StringRval = const(string_const(String)),
 		code_info__get_next_label(Label, !CI),
 		string__append_list(["case """, String, """"], Comment),
-		LabelCode = node([
-			label(Label) - Comment
-		]),
+        LabelCode = node([label(Label) - Comment]),
 		code_info__remember_position(!.CI, BranchStart),
 		trace__maybe_generate_internal_event_code(Goal, SwitchGoalInfo,
 			TraceCode, !CI),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode, !CI),
 		goal_info_get_store_map(SwitchGoalInfo, StoreMap),
-		code_info__generate_branch_end(StoreMap, !MaybeEnd,
-			SaveCode, !CI),
-		(
-			string_switch__this_is_last_case(Slot, TblSize,
-				HashSlotMap)
-		->
+        code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode, !CI),
+        ( this_is_last_case(Slot, TblSize, HashSlotMap) ->
 			true
 		;
 			code_info__reset_to_position(BranchStart, !CI)
 		),
-		FinishCode = node([
-			goto(label(EndLabel)) - "jump to end of switch"
-		]),
-		Code =
-			tree(LabelCode,
-			tree(TraceCode,
-			tree(GoalCode,
-			tree(SaveCode,
-			     FinishCode))))
+        FinishCode = node([goto(label(EndLabel)) - "jump to end of switch"]),
+        Code = tree_list([LabelCode, TraceCode, GoalCode, SaveCode,
+             FinishCode])
 	;
 		StringRval = const(int_const(0)),
 		Label = FailLabel,
@@ -229,16 +199,16 @@
 		Code = empty
 	).
 
-:- pred string_switch__this_is_last_case(int::in, int::in,
-	map(int, hash_slot)::in) is semidet.
+:- pred this_is_last_case(int::in, int::in, map(int, hash_slot)::in)
+    is semidet.
 
-string_switch__this_is_last_case(Slot, TableSize, Table) :-
+this_is_last_case(Slot, TableSize, Table) :-
 	Slot1 = Slot + 1,
 	( Slot1 >= TableSize ->
 		true
 	;
 		\+ map__contains(Table, Slot1),
-		string_switch__this_is_last_case(Slot1, TableSize, Table)
+        this_is_last_case(Slot1, TableSize, Table)
 	).
 
 %-----------------------------------------------------------------------------%
Index: compiler/switch_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/switch_gen.m,v
retrieving revision 1.87
diff -u -b -r1.87 switch_gen.m
--- compiler/switch_gen.m	13 Sep 2005 04:56:12 -0000	1.87
+++ compiler/switch_gen.m	12 Oct 2005 08:55:10 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1994-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -33,11 +35,11 @@
 %	in the form of a try-me-else chain, a try chain, a dense jump table
 %	or a binary search.
 %
-%	For switches on strings, we lookup the address to jump to in a
-%	hash table, using open addressing to resolve hash collisions.
+% For switches on strings, we lookup the address to jump to in a hash table,
+% using open addressing to resolve hash collisions.
 %
-%	For all other cases (or if the --smart-indexing option was
-%	disabled), we just generate a chain of if-then-elses.
+% For all other cases (or if the --smart-indexing option was disabled),
+% we just generate a chain of if-then-elses.
 %
 %---------------------------------------------------------------------------%
 
@@ -54,7 +56,7 @@
 
 :- import_module list.
 
-:- pred switch_gen__generate_switch(code_model::in, prog_var::in, can_fail::in,
+:- pred generate_switch(code_model::in, prog_var::in, can_fail::in,
 	list(case)::in, hlds_goal_info::in, code_tree::out,
 	code_info::in, code_info::out) is det.
 
@@ -89,19 +91,18 @@
 	% Choose which method to use to generate the switch.
 	% CanFail says whether the switch covers all cases.
 
-switch_gen__generate_switch(CodeModel, CaseVar, CanFail, Cases, GoalInfo,
+generate_switch(CodeModel, CaseVar, CanFail, Cases, GoalInfo,
 		Code, !CI) :-
 	goal_info_get_store_map(GoalInfo, StoreMap),
-	SwitchCategory = switch_gen__determine_category(!.CI, CaseVar),
+    SwitchCategory = determine_category(!.CI, CaseVar),
 	code_info__get_next_label(EndLabel, !CI),
-	switch_gen__lookup_tags(!.CI, Cases, CaseVar, TaggedCases0),
+    lookup_tags(!.CI, Cases, CaseVar, TaggedCases0),
 	list__sort_and_remove_dups(TaggedCases0, TaggedCases),
 	code_info__get_globals(!.CI, Globals),
-	globals__lookup_bool_option(Globals, smart_indexing,
-		Indexing),
+    globals__lookup_bool_option(Globals, smart_indexing, Indexing),
 	(
 		% Check for a switch on a type whose representation
-		% uses reserved addresses
+        % uses reserved addresses.
 		list__member(Case, TaggedCases),
 		Case = case(_Priority, Tag, _ConsId, _Goal),
 		(
@@ -111,84 +112,73 @@
 		)
 	->
 		% XXX This may be be inefficient in some cases.
-		switch_gen__generate_all_cases(TaggedCases, CaseVar, CodeModel,
-			CanFail, GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
+        generate_all_cases(TaggedCases, CaseVar, CodeModel, CanFail, GoalInfo,
+            EndLabel, no, MaybeEnd, Code, !CI)
 	;
 		Indexing = yes,
 		SwitchCategory = atomic_switch,
 		code_info__get_maybe_trace_info(!.CI, MaybeTraceInfo),
 		MaybeTraceInfo = no,
 		list__length(TaggedCases, NumCases),
-		globals__lookup_int_option(Globals, lookup_switch_size,
-			LookupSize),
+        globals__lookup_int_option(Globals, lookup_switch_size, LookupSize),
 		NumCases >= LookupSize,
 		globals__lookup_int_option(Globals, lookup_switch_req_density,
 			ReqDensity),
-		lookup_switch__is_lookup_switch(CaseVar, TaggedCases,
-			GoalInfo, CanFail, ReqDensity, StoreMap, no,
-			MaybeEndPrime, CodeModel, FirstVal, LastVal,
-			NeedRangeCheck, NeedBitVecCheck, OutVars, CaseVals,
-			MLiveness, !CI)
+        is_lookup_switch(CaseVar, TaggedCases, GoalInfo, CanFail, ReqDensity,
+            StoreMap, no, MaybeEndPrime, CodeModel, FirstVal, LastVal,
+            NeedRangeCheck, NeedBitVecCheck, OutVars, CaseVals, MLiveness, !CI)
 	->
 		MaybeEnd = MaybeEndPrime,
-		lookup_switch__generate(CaseVar, OutVars, CaseVals,
-			FirstVal, LastVal, NeedRangeCheck, NeedBitVecCheck,
-			MLiveness, StoreMap, no, Code, !CI)
+        generate_lookup_switch(CaseVar, OutVars, CaseVals, FirstVal, LastVal,
+            NeedRangeCheck, NeedBitVecCheck, MLiveness, StoreMap, no,
+            Code, !CI)
 	;
 		Indexing = yes,
 		SwitchCategory = atomic_switch,
 		list__length(TaggedCases, NumCases),
-		globals__lookup_int_option(Globals, dense_switch_size,
-			DenseSize),
+        globals__lookup_int_option(Globals, dense_switch_size, DenseSize),
 		NumCases >= DenseSize,
 		globals__lookup_int_option(Globals, dense_switch_req_density,
 			ReqDensity),
 		dense_switch__is_dense_switch(!.CI, CaseVar, TaggedCases,
 			CanFail, ReqDensity, FirstVal, LastVal, CanFail1)
 	->
-		dense_switch__generate(TaggedCases,
-			FirstVal, LastVal, CaseVar, CodeModel, CanFail1,
-			GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
+        generate_dense_switch(TaggedCases, FirstVal, LastVal, CaseVar,
+            CodeModel, CanFail1, GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
 	;
 		Indexing = yes,
 		SwitchCategory = string_switch,
 		list__length(TaggedCases, NumCases),
-		globals__lookup_int_option(Globals, string_switch_size,
-			StringSize),
+        globals__lookup_int_option(Globals, string_switch_size, StringSize),
 		NumCases >= StringSize
 	->
-		string_switch__generate(TaggedCases, CaseVar, CodeModel,
-			CanFail, GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
+        generate_string_switch(TaggedCases, CaseVar, CodeModel, CanFail,
+            GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
 	;
 		Indexing = yes,
 		SwitchCategory = tag_switch,
 		list__length(TaggedCases, NumCases),
-		globals__lookup_int_option(Globals, tag_switch_size,
-			TagSize),
+        globals__lookup_int_option(Globals, tag_switch_size, TagSize),
 		NumCases >= TagSize
 	->
-		tag_switch__generate(TaggedCases, CaseVar, CodeModel, CanFail,
+        generate_tag_switch(TaggedCases, CaseVar, CodeModel, CanFail,
 			GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
 	;
-		% To generate a switch, first we flush the
-		% variable on whose tag we are going to switch, then we
-		% generate the cases for the switch.
-
-		switch_gen__generate_all_cases(TaggedCases, CaseVar,
-			CodeModel, CanFail, GoalInfo, EndLabel, no, MaybeEnd,
-			Code, !CI)
+        % To generate a switch, first we flush the variable on whose tag
+        % we are going to switch, then we generate the cases for the switch.
+        generate_all_cases(TaggedCases, CaseVar, CodeModel, CanFail, GoalInfo,
+            EndLabel, no, MaybeEnd, Code, !CI)
 	),
 	code_info__after_all_branches(StoreMap, MaybeEnd, !CI).
 
 %---------------------------------------------------------------------------%
 
-	% We categorize switches according to whether the value
-	% being switched on is an atomic type, a string, or
-	% something more complicated.
-
-:- func switch_gen__determine_category(code_info, prog_var) = switch_category.
+    % We categorize switches according to whether the value being switched on
+    % is an atomic type, a string, or something more complicated.
+    %
+:- func determine_category(code_info, prog_var) = switch_category.
 
-switch_gen__determine_category(CI, CaseVar) = SwitchCategory :-
+determine_category(CI, CaseVar) = SwitchCategory :-
 	Type = code_info__variable_type(CI, CaseVar),
 	code_info__get_module_info(CI, ModuleInfo),
 	classify_type(ModuleInfo, Type) = TypeCategory,
@@ -196,16 +186,16 @@
 
 %---------------------------------------------------------------------------%
 
-:- pred switch_gen__lookup_tags(code_info::in, list(case)::in, prog_var::in,
+:- pred lookup_tags(code_info::in, list(case)::in, prog_var::in,
 	cases_list::out) is det.
 
-switch_gen__lookup_tags(_, [], _, []).
-switch_gen__lookup_tags(CI, [Case | Cases], Var, [TaggedCase | TaggedCases]) :-
+lookup_tags(_, [], _, []).
+lookup_tags(CI, [Case | Cases], Var, [TaggedCase | TaggedCases]) :-
 	Case = case(ConsId, Goal),
 	Tag = code_info__cons_id_to_tag(CI, Var, ConsId),
 	Priority = switch_util__switch_priority(Tag),
 	TaggedCase = case(Priority, Tag, ConsId, Goal),
-	switch_gen__lookup_tags(CI, Cases, Var, TaggedCases).
+    lookup_tags(CI, Cases, Var, TaggedCases).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
@@ -235,14 +225,14 @@
 	% we try to find out which case will be executed more frequently,
 	% and put that one first. This minimizes the number of pipeline
 	% breaks caused by taken branches.
-
-:- pred switch_gen__generate_all_cases(list(extended_case)::in, prog_var::in,
+    %
+:- pred generate_all_cases(list(extended_case)::in, prog_var::in,
 	code_model::in, can_fail::in, hlds_goal_info::in, label::in,
 	branch_end::in, branch_end::out, code_tree::out,
 	code_info::in, code_info::out) is det.
 
-switch_gen__generate_all_cases(Cases0, Var, CodeModel, CanFail, GoalInfo,
-		EndLabel, !MaybeEnd, Code, !CI) :-
+generate_all_cases(Cases0, Var, CodeModel, CanFail, GoalInfo, EndLabel,
+        !MaybeEnd, Code, !CI) :-
 	code_info__produce_variable(Var, VarCode, _Rval, !CI),
 	(
 		CodeModel = model_det,
@@ -271,73 +261,60 @@
 	;
 		Cases = Cases0
 	),
-	switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
-		GoalInfo, EndLabel, !MaybeEnd, CasesCode, !CI),
+    generate_cases(Cases, Var, CodeModel, CanFail, GoalInfo, EndLabel,
+        !MaybeEnd, CasesCode, !CI),
 	Code = tree(VarCode, CasesCode).
 
-:- pred switch_gen__generate_cases(list(extended_case)::in, prog_var::in,
+:- pred generate_cases(list(extended_case)::in, prog_var::in,
 	code_model::in, can_fail::in, hlds_goal_info::in, label::in,
 	branch_end::in, branch_end::out, code_tree::out,
 	code_info::in, code_info::out) is det.
 
-	% At the end of a locally semidet switch, we fail because we
-	% came across a tag which was not covered by one of the cases.
-	% It is followed by the end of switch label to which the cases
-	% branch.
-switch_gen__generate_cases([], _Var, _CodeModel, CanFail, _GoalInfo,
-		EndLabel, !MaybeEnd, Code, !CI) :-
-	( CanFail = can_fail ->
+generate_cases([], _Var, _CodeModel, CanFail, _GoalInfo, EndLabel, !MaybeEnd,
+        Code, !CI) :-
+    (
+        CanFail = can_fail,
+        % At the end of a locally semidet switch, we fail because we came
+        % across a tag which was not covered by one of the cases. It is
+        % followed by the end of switch label to which the cases branch.
 		code_info__generate_failure(FailCode, !CI)
 	;
+        CanFail = cannot_fail,
 		FailCode = empty
 	),
-	EndCode = node([
-		label(EndLabel) -
-			"end of switch"
-	]),
+    EndCode = node([label(EndLabel) - "end of switch"]),
 	Code = tree(FailCode, EndCode).
 
-switch_gen__generate_cases([case(_, _, Cons, Goal) | Cases], Var, CodeModel,
-		CanFail, SwitchGoalInfo, EndLabel, !MaybeEnd, CasesCode,
-		!CI) :-
+generate_cases([case(_, _, Cons, Goal) | Cases], Var, CodeModel, CanFail,
+        SwitchGoalInfo, EndLabel, !MaybeEnd, CasesCode, !CI) :-
 	code_info__remember_position(!.CI, BranchStart),
 	goal_info_get_store_map(SwitchGoalInfo, StoreMap),
 	(
-		( Cases = [_|_] ; CanFail = can_fail )
+        ( Cases = [_|_]
+        ; CanFail = can_fail
+        )
 	->
-		unify_gen__generate_tag_test(Var, Cons, branch_on_failure,
-			NextLabel, TestCode, !CI),
+        unify_gen__generate_tag_test(Var, Cons, branch_on_failure, NextLabel,
+            TestCode, !CI),
 		trace__maybe_generate_internal_event_code(Goal, SwitchGoalInfo,
 			TraceCode, !CI),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode, !CI),
-		code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode,
-			!CI),
+        code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode, !CI),
 		ElseCode = node([
-			goto(label(EndLabel)) -
-				"skip to the end of the switch",
-			label(NextLabel) -
-				"next case"
+            goto(label(EndLabel)) - "skip to the end of the switch",
+            label(NextLabel) - "next case"
 		]),
-		ThisCaseCode =
-			tree(TestCode,
-			tree(TraceCode,
-			tree(GoalCode,
-			tree(SaveCode,
-			     ElseCode))))
+        ThisCaseCode = tree_list([TestCode, TraceCode, GoalCode, SaveCode,
+             ElseCode])
 	;
 		trace__maybe_generate_internal_event_code(Goal, SwitchGoalInfo,
 			TraceCode, !CI),
 		code_gen__generate_goal(CodeModel, Goal, GoalCode, !CI),
-		code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode,
-			!CI),
-		ThisCaseCode =
-			tree(TraceCode,
-			tree(GoalCode,
-			     SaveCode))
+        code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode, !CI),
+        ThisCaseCode = tree_list([TraceCode, GoalCode, SaveCode])
 	),
 	code_info__reset_to_position(BranchStart, !CI),
-		% generate the rest of the cases.
-	switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
+    generate_cases(Cases, Var, CodeModel, CanFail,
 		SwitchGoalInfo, EndLabel, !MaybeEnd, OtherCasesCode, !CI),
 	CasesCode = tree(ThisCaseCode, OtherCasesCode).
 
Index: compiler/tag_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tag_switch.m,v
retrieving revision 1.63
diff -u -b -r1.63 tag_switch.m
--- compiler/tag_switch.m	25 Aug 2005 03:19:48 -0000	1.63
+++ compiler/tag_switch.m	12 Oct 2005 09:01:11 -0000
@@ -28,7 +28,7 @@
 
     % Generate intelligent indexing code for tag based switches.
     %
-:- pred tag_switch__generate(list(extended_case)::in, prog_var::in,
+:- pred generate_tag_switch(list(extended_case)::in, prog_var::in,
     code_model::in, can_fail::in, hlds_goal_info::in, label::in,
     branch_end::in, branch_end::out, code_tree::out,
     code_info::in, code_info::out) is det.
@@ -188,8 +188,8 @@
     ;       jump_table
     ;       binary_search.
 
-generate(Cases, Var, CodeModel, CanFail, SwitchGoalInfo, EndLabel, !MaybeEnd,
-        Code, !CI) :-
+generate_tag_switch(Cases, Var, CodeModel, CanFail, SwitchGoalInfo, EndLabel,
+        !MaybeEnd, Code, !CI) :-
     % Group the cases based on primary tag value and find out how many
     % constructors share each primary tag value.
 
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing debian/patches
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/aditi
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/stream
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
cvs diff: Diffing util
cvs diff: Diffing vim
cvs diff: Diffing vim/after
cvs diff: Diffing vim/ftplugin
cvs diff: Diffing vim/syntax
--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list