[m-rev.] diff: shorten long lines

Zoltan Somogyi zs at unimelb.edu.au
Wed Oct 24 16:50:42 AEDT 2012


compiler/*.m:
	Shorten lines longer than 79 characters.

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/extra
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/extra
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/libatomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops/doc
cvs diff: Diffing boehm_gc/libatomic_ops/pkgconfig
cvs diff: Diffing boehm_gc/libatomic_ops/src
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/armcc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/gcc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/hpc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/ibmc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/icc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/msftc
cvs diff: Diffing boehm_gc/libatomic_ops/src/atomic_ops/sysdeps/sunc
cvs diff: Diffing boehm_gc/libatomic_ops/tests
cvs diff: Diffing boehm_gc/libatomic_ops-1.2
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/doc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/tests
cvs diff: Diffing boehm_gc/m4
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/abstract_mode_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/abstract_mode_constraints.m,v
retrieving revision 1.13
diff -u -b -r1.13 abstract_mode_constraints.m
--- compiler/abstract_mode_constraints.m	30 Mar 2010 23:57:25 -0000	1.13
+++ compiler/abstract_mode_constraints.m	24 Oct 2012 05:48:13 -0000
@@ -181,7 +181,8 @@
     %   !PredPCConstraints):
     %
     % Add the constraint given by Constraint to the constraint system in
-    % PredPCConstraints, and associate it specifically with the given procedure.
+    % PredPCConstraints, and associate it specifically with the given
+    % procedure.
     %
 :- pred add_proc_specific_constraint(mc_varset::in, prog_context::in,
     proc_id::in, mc_constraint::in,
Index: compiler/analysis.file.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/analysis.file.m,v
retrieving revision 1.17
diff -u -b -r1.17 analysis.file.m
--- compiler/analysis.file.m	14 Dec 2011 04:55:16 -0000	1.17
+++ compiler/analysis.file.m	24 Oct 2012 05:48:13 -0000
@@ -299,7 +299,8 @@
                     io.nl(!IO),
                     read_module_analysis_results_2(Compiler, AnalysisFileName,
                         ModuleResults, !IO),
-                    write_analysis_cache_file(CacheFileName, ModuleResults, !IO)
+                    write_analysis_cache_file(CacheFileName, ModuleResults,
+                        !IO)
                 )
             ;
                 read_module_analysis_results_2(Compiler, AnalysisFileName,
Index: compiler/analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/analysis.m,v
retrieving revision 1.13
diff -u -b -r1.13 analysis.m
--- compiler/analysis.m	23 May 2011 05:08:00 -0000	1.13
+++ compiler/analysis.m	24 Oct 2012 05:48:13 -0000
@@ -488,7 +488,8 @@
 
 lookup_results(Info, ModuleName, FuncId, ResultList) :-
     AllowInvalidModules = no,
-    lookup_results_1(Info, ModuleName, FuncId, AllowInvalidModules, ResultList).
+    lookup_results_1(Info, ModuleName, FuncId, AllowInvalidModules,
+        ResultList).
 
 :- pred lookup_results_1(analysis_info::in, module_name::in, func_id::in,
     bool::in, list(analysis_result(Call, Answer))::out) is det
@@ -543,7 +544,8 @@
         ResultList = []
     ).
 
-lookup_matching_results(Info, ModuleName, FuncId, FuncInfo, Call, ResultList) :-
+lookup_matching_results(Info, ModuleName, FuncId, FuncInfo, Call,
+        ResultList) :-
     lookup_results(Info, ModuleName, FuncId, AllResultsList),
     ResultList = list.filter(
         (pred(Result::in) is semidet :-
@@ -553,7 +555,8 @@
             )
         ), AllResultsList).
 
-lookup_best_result(Info, ModuleName, FuncId, FuncInfo, Call, MaybeBestResult) :-
+lookup_best_result(Info, ModuleName, FuncId, FuncInfo, Call,
+        MaybeBestResult) :-
     trace [io(!IO)] (
         debug_msg((pred(!.IO::di, !:IO::uo) is det :-
             io.write_string("% Looking up best analysis result for ", !IO),
@@ -855,7 +858,8 @@
 
 update_analysis_registry_3(ModuleInfo, ModuleName, AnalysisName, FuncMap,
         !Info, !IO) :-
-    map.foldl2(update_analysis_registry_4(ModuleInfo, ModuleName, AnalysisName),
+    map.foldl2(
+        update_analysis_registry_4(ModuleInfo, ModuleName, AnalysisName),
         FuncMap, !Info, !IO).
 
 :- pred update_analysis_registry_4(module_info::in, module_name::in,
@@ -866,8 +870,10 @@
         NewResults, !Info, !IO) :-
     % XXX Currently we do not prevent there being more than one recorded result
     % for a given call pattern.
-    list.foldl2(update_analysis_registry_5(ModuleInfo, ModuleName, AnalysisName,
-        FuncId), NewResults, !Info, !IO).
+    list.foldl2(
+        update_analysis_registry_5(ModuleInfo, ModuleName, AnalysisName,
+            FuncId),
+        NewResults, !Info, !IO).
 
 :- pred update_analysis_registry_5(module_info::in, module_name::in,
     analysis_name::in, func_id::in, some_analysis_result::in,
Index: compiler/bytecode.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/bytecode.m,v
retrieving revision 1.80
diff -u -b -r1.80 bytecode.m
--- compiler/bytecode.m	6 Sep 2011 05:20:41 -0000	1.80
+++ compiler/bytecode.m	24 Oct 2012 05:48:13 -0000
@@ -769,14 +769,16 @@
 output_cons_id(byte_float_const(FloatVal), !IO) :-
     output_byte(3, !IO),
     output_float(FloatVal, !IO).
-output_cons_id(byte_pred_const(ModuleId, PredId, Arity, IsFunc, ProcId), !IO) :-
+output_cons_id(byte_pred_const(ModuleId, PredId, Arity, IsFunc, ProcId),
+        !IO) :-
     output_byte(4, !IO),
     output_module_id(ModuleId, !IO),
     output_pred_id(PredId, !IO),
     output_length(Arity, !IO),
     output_is_func(IsFunc, !IO),
     output_proc_id(ProcId, !IO).
-output_cons_id(byte_type_ctor_info_const(ModuleId, TypeName, TypeArity), !IO) :-
+output_cons_id(byte_type_ctor_info_const(ModuleId, TypeName, TypeArity),
+        !IO) :-
     output_byte(6, !IO),
     output_module_id(ModuleId, !IO),
     output_string(TypeName, !IO),
Index: compiler/bytecode_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/bytecode_gen.m,v
retrieving revision 1.135
diff -u -b -r1.135 bytecode_gen.m
--- compiler/bytecode_gen.m	2 Jul 2012 01:16:32 -0000	1.135
+++ compiler/bytecode_gen.m	24 Oct 2012 05:48:13 -0000
@@ -366,7 +366,8 @@
     determinism_to_code_model(Detism, CodeModel),
     get_module_info(ByteInfo, ModuleInfo),
     list.map(get_var_type(ByteInfo), ArgVars, ArgTypes),
-    make_standard_arg_infos(ArgTypes, ArgModes, CodeModel, ModuleInfo, ArgInfo),
+    make_standard_arg_infos(ArgTypes, ArgModes, CodeModel, ModuleInfo,
+        ArgInfo),
     assoc_list.from_corresponding_lists(ArgVars, ArgInfo, ArgVarsInfos),
 
     arg_info.partition_args(ArgVarsInfos, InVars, OutVars),
@@ -779,7 +780,8 @@
         sorry($module, $pred, "bytecode doesn't implement type_info_const")
     ;
         ConsId = typeclass_info_const(_),
-        sorry($module, $pred, "bytecode doesn't implement typeclass_info_const")
+        sorry($module, $pred,
+            "bytecode doesn't implement typeclass_info_const")
     ;
         ConsId = ground_term_const(_, _),
         sorry($module, $pred, "bytecode doesn't implement ground_term_const")
Index: compiler/c_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/c_util.m,v
retrieving revision 1.54
diff -u -b -r1.54 c_util.m
--- compiler/c_util.m	19 Jun 2012 07:21:23 -0000	1.54
+++ compiler/c_util.m	24 Oct 2012 05:48:13 -0000
@@ -82,7 +82,8 @@
 :- pred output_quoted_string_lang(literal_language, string, io, io).
 :- mode output_quoted_string_lang(in(bound(literal_c)), in, di, uo) is det.
 :- mode output_quoted_string_lang(in(bound(literal_java)), in, di, uo) is det.
-:- mode output_quoted_string_lang(in(bound(literal_csharp)), in, di, uo) is det.
+:- mode output_quoted_string_lang(in(bound(literal_csharp)), in, di, uo)
+    is det.
 :- mode output_quoted_string_lang(in, in, di, uo) is det.
 
     % output_quoted_multi_string is like list.foldl(output_quoted_string)
Index: compiler/call_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/call_gen.m,v
retrieving revision 1.208
diff -u -b -r1.208 call_gen.m
--- compiler/call_gen.m	2 Jul 2012 01:16:32 -0000	1.208
+++ compiler/call_gen.m	24 Oct 2012 05:48:13 -0000
@@ -227,8 +227,8 @@
         OutArgsInfosR),
     give_vars_consecutive_arg_infos(OutVarsF, reg_f, FirstOutputF, top_out,
         OutArgsInfosF),
-    ArgInfos = list.condense([SpecifierArgInfos, InVarArgInfosR, InVarArgInfosF,
-        OutArgsInfosR, OutArgsInfosF]),
+    ArgInfos = list.condense([SpecifierArgInfos,
+        InVarArgInfosR, InVarArgInfosF, OutArgsInfosR, OutArgsInfosF]),
 
     % Save the necessary vars on the stack and move the input args defined
     % by variables to their registers.
@@ -427,7 +427,8 @@
     % constants.
     %
 :- pred generic_call_nonvar_setup(generic_call::in, known_call_variant::in,
-    list(prog_var)::in, list(prog_var)::in, list(prog_var)::in, list(prog_var)::in,
+    list(prog_var)::in, list(prog_var)::in,
+    list(prog_var)::in, list(prog_var)::in,
     llds_code::out, code_info::in, code_info::out) is det.
 
 generic_call_nonvar_setup(higher_order(_, _, _, _), HoCallVariant,
@@ -697,13 +698,16 @@
             Code = ArgCode ++ TestCode
         ;
             SimpleCode = assign(_, _),
-            unexpected($module, $pred, "malformed model_semi builtin predicate")
+            unexpected($module, $pred,
+                "malformed model_semi builtin predicate")
         ;
             SimpleCode = ref_assign(_, _),
-            unexpected($module, $pred, "malformed model_semi builtin predicate")
+            unexpected($module, $pred,
+                "malformed model_semi builtin predicate")
         ;
             SimpleCode = noop(_),
-            unexpected($module, $pred, "malformed model_semi builtin predicate")
+            unexpected($module, $pred,
+                "malformed model_semi builtin predicate")
         )
     ;
         CodeModel = model_non,
Index: compiler/check_typeclass.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/check_typeclass.m,v
retrieving revision 1.143
diff -u -b -r1.143 check_typeclass.m
--- compiler/check_typeclass.m	10 Sep 2012 17:08:56 -0000	1.143
+++ compiler/check_typeclass.m	24 Oct 2012 05:48:13 -0000
@@ -1176,7 +1176,8 @@
         constraint_list_to_string(ClassVarSet, UnprovenConstraints,
             ConstraintsString),
         Pieces = [words("In instance declaration for"),
-            words("`" ++ ClassNameString ++ "(" ++ InstanceTypesString ++ ")'"),
+            words("`" ++ ClassNameString ++
+                "(" ++ InstanceTypesString ++ ")'"),
             words(choose_number(UnprovenConstraintsTail,
                 "superclass constraint", "superclass constraints")),
             words("not satisfied:"), words(ConstraintsString), suffix("."),
@@ -2199,16 +2200,14 @@
 :- pred report_bogus_instance_methods(class_id::in, instance_methods::in,
     prog_context::in, list(error_spec)::in, list(error_spec)::out) is det.
 
-report_bogus_instance_methods(ClassId, BogusInstanceMethods, Context, !Specs) :-
+report_bogus_instance_methods(ClassId, BogusInstanceMethods, Context,
+        !Specs) :-
     % There were one or more bogus methods.
     % Construct an appropriate error message.
     ClassId = class_id(ClassName, ClassArity),
-    ErrorMsgStart =  [
-        words("In instance declaration for"),
-        sym_name_and_arity(ClassName / ClassArity),
-        suffix(":"),
-        words("incorrect method name(s):")
-    ],
+    ErrorMsgStart =  [words("In instance declaration for"),
+        sym_name_and_arity(ClassName / ClassArity), suffix(":"),
+        words("incorrect method name(s):")],
     ErrorMsgBody0 = list.map(format_method_name, BogusInstanceMethods),
     ErrorMsgBody1 = list.condense(ErrorMsgBody0),
     ErrorMsgBody = list.append(ErrorMsgBody1, [suffix(".")]),
Index: compiler/closure_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/closure_analysis.m,v
retrieving revision 1.28
diff -u -b -r1.28 closure_analysis.m
--- compiler/closure_analysis.m	2 Jul 2012 01:16:32 -0000	1.28
+++ compiler/closure_analysis.m	24 Oct 2012 05:48:13 -0000
@@ -331,7 +331,8 @@
         ),
         DisjunctsAndInfos = list.map(ProcessDisjunct, Goals0),
         assoc_list.keys_and_values(DisjunctsAndInfos, Goals, DisjunctsInfo),
-        list.foldl(merge_closure_infos, DisjunctsInfo, map.init, !:ClosureInfo),
+        list.foldl(merge_closure_infos, DisjunctsInfo,
+            map.init, !:ClosureInfo),
         GoalExpr = disj(Goals),
         Goal = hlds_goal(GoalExpr, GoalInfo0)
     ;
Index: compiler/code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_util.m,v
retrieving revision 1.193
diff -u -b -r1.193 code_util.m
--- compiler/code_util.m	13 Feb 2012 00:11:34 -0000	1.193
+++ compiler/code_util.m	24 Oct 2012 05:48:13 -0000
@@ -579,7 +579,8 @@
     list(rval)::out, list(lval)::out) is det.
 
 foreign_proc_components_get_rvals_and_lvals([], [], []).
-foreign_proc_components_get_rvals_and_lvals([Comp | Comps], !:Rvals, !:Lvals) :-
+foreign_proc_components_get_rvals_and_lvals([Comp | Comps],
+        !:Rvals, !:Lvals) :-
     foreign_proc_components_get_rvals_and_lvals(Comps, !:Rvals, !:Lvals),
     foreign_proc_component_get_rvals_and_lvals(Comp, !Rvals, !Lvals).
 
Index: compiler/compile_target_code.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/compile_target_code.m,v
retrieving revision 1.190
diff -u -b -r1.190 compile_target_code.m
--- compiler/compile_target_code.m	19 Jul 2012 11:44:12 -0000	1.190
+++ compiler/compile_target_code.m	24 Oct 2012 05:48:13 -0000
@@ -2501,7 +2501,8 @@
 :- pred get_restricted_command_line_link_opts(globals::in,
     linked_target_type::in, string::out) is det.
 
-get_restricted_command_line_link_opts(Globals, LinkTargetType, ResCmdLinkOpts) :-
+get_restricted_command_line_link_opts(Globals, LinkTargetType,
+        ResCmdLinkOpts) :-
     globals.lookup_bool_option(Globals, restricted_command_line,
         RestrictedCommandLine),
     (
@@ -2588,9 +2589,9 @@
             % Remove the target of the symlink/copy in case it already exists.
             io.remove_file_recursively(UserDirFileName, _, !IO),
 
-            % Erlang "archives" are just directories of .beam files, so we need
-            % to copy them as directories rather than files (on systems on which
-            % symbolic links are not available).
+            % Erlang "archives" are just directories of .beam files,
+            % so we need to copy them as directories rather than files
+            % (on systems on which symbolic links are not available).
             ( if LinkTargetType = erlang_archive then
                 make_symlink_or_copy_dir(Globals, OutputFileName,
                     UserDirFileName, Succeeded, !IO)
@@ -2799,12 +2800,11 @@
     ).
 
 :- pred create_csharp_exe_or_lib(globals::in, io.output_stream::in,
-    linked_target_type::in, module_name::in, file_name::in, list(file_name)::in,
-    bool::out, io::di, io::uo) is det.
+    linked_target_type::in, module_name::in, file_name::in,
+    list(file_name)::in, bool::out, io::di, io::uo) is det.
 
 create_csharp_exe_or_lib(Globals, ErrorStream, LinkTargetType, MainModuleName,
         OutputFileName0, SourceList0, Succeeded, !IO) :-
-
     get_host_env_type(Globals, EnvType),
     get_csharp_compiler_type(Globals, CSharpCompilerType),
 
@@ -2818,7 +2818,7 @@
         % If we output line numbers the mono C# compiler outputs lots of
         % spurious warnings about unused variables and unreachable code,
         % so disable these warnings.  It also confuses #pragma warning
-        % which is why we make the options global
+        % which is why we make the options global.
         LineNumbers = yes,
         NoWarnLineNumberOpt = "-nowarn:162,219 "
     ;
@@ -2924,7 +2924,8 @@
     % This is because the MS C# compiler only allows \ as the path separator,
     % so we convert all / into \ when using the MC C# compiler.
     %
-:- func csharp_file_name(env_type, csharp_compiler_type, file_name) = file_name.
+:- func csharp_file_name(env_type, csharp_compiler_type, file_name)
+    = file_name.
 
 csharp_file_name(env_type_posix, csharp_microsoft, _FileName) =
     unexpected($module, $pred, "microsoft c# compiler in posix env").
@@ -3269,8 +3270,8 @@
 % Standalone interfaces
 %
 
-% NOTE: the following code is similar to that of make_init_obj/7.  Any
-% changes here may need to be reflected there.
+% NOTE: the following code is similar to that of make_init_obj/7.
+% Any changes here may need to be reflected there.
 
 make_standalone_interface(Globals, Basename, !IO) :-
     make_standalone_int_header(Basename, HdrSucceeded, !IO),
Index: compiler/ctgc.selector.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ctgc.selector.m,v
retrieving revision 1.36
diff -u -b -r1.36 ctgc.selector.m
--- compiler/ctgc.selector.m	11 Jun 2012 03:13:20 -0000	1.36
+++ compiler/ctgc.selector.m	24 Oct 2012 05:48:13 -0000
@@ -202,9 +202,11 @@
                 % of a type variable.  This is probably a hack.
                 Extension = []
             ;
-                % If both selectors begin with term selectors, clearly they must
-                % agree on the node to select for the selectors to be comparable.
-                SubType = det_select_subtype(ModuleInfo, Type, ConsIdA, IndexA),
+                % If both selectors begin with term selectors, clearly
+                % they must agree on the node to select for the selectors
+                % to be comparable.
+                SubType = det_select_subtype(ModuleInfo, Type, ConsIdA,
+                    IndexA),
                 selector_subsumed_by_2(ModuleInfo, AT, BT, SubType, Extension)
             )
         ;
Index: compiler/dep_par_conj.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dep_par_conj.m,v
retrieving revision 1.64
diff -u -b -r1.64 dep_par_conj.m
--- compiler/dep_par_conj.m	19 Jul 2012 13:41:10 -0000	1.64
+++ compiler/dep_par_conj.m	24 Oct 2012 05:48:13 -0000
@@ -1090,8 +1090,9 @@
         FirstWaitedOnAllSuccessPaths, Goal0, Goal, !VarSet, !VarTypes),
     Case = case(MainConsId, OtherConsIds, Goal),
     join_branches(FirstWaitedOnAllSuccessPaths, !WaitedOnAllSuccessPaths),
-    insert_wait_in_cases(ModuleInfo, AllowSomePathsOnly, FutureMap, ConsumedVar,
-        !WaitedOnAllSuccessPaths, Cases0, Cases, !VarSet, !VarTypes).
+    insert_wait_in_cases(ModuleInfo, AllowSomePathsOnly, FutureMap,
+        ConsumedVar, !WaitedOnAllSuccessPaths, Cases0, Cases,
+        !VarSet, !VarTypes).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/det_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/det_report.m,v
retrieving revision 1.161
diff -u -b -r1.161 det_report.m
--- compiler/det_report.m	2 Jul 2012 01:16:33 -0000	1.161
+++ compiler/det_report.m	24 Oct 2012 05:48:13 -0000
@@ -1429,7 +1429,8 @@
 
 det_report_unify_context(!.First, Last, _Context, UnifyContext, DetInfo,
         LHS, RHS, AllPieces) :-
-    unify_context_first_to_pieces(!First, UnifyContext, [], UnifyContextPieces),
+    unify_context_first_to_pieces(!First, UnifyContext, [],
+        UnifyContextPieces),
     det_get_proc_info(DetInfo, ProcInfo),
     proc_info_get_varset(ProcInfo, VarSet),
     det_info_get_module_info(DetInfo, ModuleInfo),
Index: compiler/distance_granularity.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/distance_granularity.m,v
retrieving revision 1.19
diff -u -b -r1.19 distance_granularity.m
--- compiler/distance_granularity.m	23 Apr 2012 03:34:47 -0000	1.19
+++ compiler/distance_granularity.m	24 Oct 2012 05:48:13 -0000
@@ -188,8 +188,8 @@
 apply_dg_to_preds([PredId | PredIdList], Distance, !ModuleInfo) :-
     module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
     % We need to know what the pred_id will be for the specified predicate
-    % before we actually clone it (this avoids doing one more pass to update the
-    % pred_id in the recursive plain calls).
+    % before we actually clone it (this avoids doing one more pass to update
+    % the pred_id in the recursive plain calls).
     module_info_get_predicate_table(!.ModuleInfo, PredicateTable),
     get_next_pred_id(PredicateTable, NewPredId),
 
@@ -267,8 +267,8 @@
 
         proc_info_get_goal(ProcInfo0, Body),
         apply_dg_to_goal(Body, BodyClone, PredId, ProcId, PredIdSpecialized,
-            SymNameSpecialized, ProcInfo0, ProcInfo1, !ModuleInfo, Distance, no,
-            no, MaybeGranularityVar, _),
+            SymNameSpecialized, ProcInfo0, ProcInfo1, !ModuleInfo,
+            Distance, no, no, MaybeGranularityVar, _),
         (
             MaybeGranularityVar = yes(_),
             % The granularity variable has been created while the procedure was
@@ -333,12 +333,11 @@
             Type = parallel_conj,
             (
                 ContainRecursiveCalls = yes,
-                create_if_then_else_goal(Goals, GoalInfo, !.MaybeGranularityVar,
-                    PredIdSpecialized, CallerProcId, Distance, !:Goal,
-                    !ProcInfo, !.ModuleInfo)
+                create_if_then_else_goal(Goals, GoalInfo,
+                    !.MaybeGranularityVar, PredIdSpecialized, CallerProcId,
+                    Distance, !:Goal, !ProcInfo, !.ModuleInfo)
             ;
-                ContainRecursiveCalls = no,
-                true
+                ContainRecursiveCalls = no
             )
         ),
         IsRecursiveCallInParallelConj = no
@@ -470,9 +469,9 @@
         PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
         Distance, IsInParallelConj, !MaybeGranularityVar,
         !HasRecursiveCallsInParallelConj) :-
-    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, PredIdSpecialized,
-        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, IsInParallelConj,
-        !MaybeGranularityVar, IsRecursiveCall),
+    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId,
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, IsInParallelConj, !MaybeGranularityVar, IsRecursiveCall),
     list.append(!.GoalsAcc, [Goal], !:GoalsAcc),
     (
         IsRecursiveCall = yes,
@@ -484,8 +483,8 @@
         !:HasRecursiveCallsInParallelConj = !.HasRecursiveCallsInParallelConj
     ),
     apply_dg_to_conj(Goals, !GoalsAcc, CallerPredId, CallerProcId,
-        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance,
-        IsInParallelConj, !MaybeGranularityVar,
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, IsInParallelConj, !MaybeGranularityVar,
         !HasRecursiveCallsInParallelConj).
 
     % Create the if_then_else goal surrounding the recursive plain call as
@@ -576,8 +575,8 @@
                     list.append(CallArgs0, [Var], CallArgs),
 
                     % If the original predicate is a function then the
-                    % specialized version is a predicate. Therefore, there is no
-                    % need for the unify context anymore.
+                    % specialized version is a predicate. Therefore,
+                    % there is no need for the unify context anymore.
                     CallUnifyContext = no,
 
                     GoalExpr = plain_call(CalleePredId, CalleeProcId, CallArgs,
@@ -777,13 +776,13 @@
 apply_dg_to_disj([Goal0 | Goals], !GoalsAcc, CallerPredId, CallerProcId,
         PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
         Distance, !MaybeGranularityVar) :-
-    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, PredIdSpecialized,
-        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, no,
-        !MaybeGranularityVar, _),
+    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId,
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, no, !MaybeGranularityVar, _),
     list.append( !.GoalsAcc, [Goal], !:GoalsAcc),
     apply_dg_to_disj(Goals, !GoalsAcc, CallerPredId, CallerProcId,
-        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance,
-        !MaybeGranularityVar).
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, !MaybeGranularityVar).
 
     % Apply the distance granularity transformation to a switch.
     %
@@ -800,13 +799,13 @@
         PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
         Distance, !MaybeGranularityVar) :-
     Case = case(MainConsId, OtherConsIds, Goal0),
-    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId, PredIdSpecialized,
-        SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance, no,
-        !MaybeGranularityVar, _),
+    apply_dg_to_goal(Goal0, Goal, CallerPredId, CallerProcId,
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, no, !MaybeGranularityVar, _),
     !:CasesAcc = [case(MainConsId, OtherConsIds, Goal) | !.CasesAcc],
     apply_dg_to_switch(Cases, !CasesAcc, CallerPredId, CallerProcId,
-        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo, Distance,
-        !MaybeGranularityVar).
+        PredIdSpecialized, SymNameSpecialized, !ProcInfo, !ModuleInfo,
+        Distance, !MaybeGranularityVar).
 
     % Create the string name of the specialized predicate (same format as
     % make_pred_name in prog_util) out of the name of the original one.
@@ -835,8 +834,8 @@
     % Update the recursive calls in each procedure in the list so that the
     % pred_id called is the one of the specialized procedure.
     %
-:- pred update_original_predicate_procs(pred_id::in, list(proc_id)::in, int::in,
-    pred_id::in, sym_name::in, pred_info::in, pred_info::out,
+:- pred update_original_predicate_procs(pred_id::in, list(proc_id)::in,
+    int::in, pred_id::in, sym_name::in, pred_info::in, pred_info::out,
     module_info::in, module_info::out) is det.
 
 update_original_predicate_procs(_PredId, [], _Distance, _PredIdSpecialized,
@@ -857,8 +856,8 @@
     update_original_predicate_procs(PredId, ProcIds, Distance,
         PredIdSpecialized, SymNameSpecialized, !PredInfo, !ModuleInfo).
 
-    % Update the recursive calls of a goal so that the pred_id called is the one
-    % of the specialized procedure.
+    % Update the recursive calls of a goal so that the pred_id called
+    % is the one of the specialized procedure.
     %
 :- pred update_original_predicate_goal(hlds_goal::in, hlds_goal::out,
     pred_id::in, proc_id::in, pred_id::in, sym_name::in,
@@ -890,8 +889,8 @@
             flatten_conj(Goals1, Goals)
         ;
             Type = parallel_conj,
-            % No need to flatten parallel conjunctions as the transformation may
-            % only create plain conjunctions
+            % No need to flatten parallel conjunctions as the transformation
+            % may only create plain conjunctions
             % (see update_original_predicate_plain_call).
             Goals = Goals1
         ),
Index: compiler/elds_to_erlang.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/elds_to_erlang.m,v
retrieving revision 1.44
diff -u -b -r1.44 elds_to_erlang.m
--- compiler/elds_to_erlang.m	10 Sep 2012 17:08:57 -0000	1.44
+++ compiler/elds_to_erlang.m	24 Oct 2012 05:48:13 -0000
@@ -232,7 +232,8 @@
 :- pred output_wrapper_init_fn_export_ann(bool::in, list(pred_proc_id)::in,
     list(pred_proc_id)::in, io::di, io::uo) is det.
 
-output_wrapper_init_fn_export_ann(AddMainWrapper, InitPreds, FinalPreds, !IO) :-
+output_wrapper_init_fn_export_ann(AddMainWrapper, InitPreds, FinalPreds,
+        !IO) :-
     (
         AddMainWrapper = yes,
         comma(!IO),
Index: compiler/equiv_type.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/equiv_type.m,v
retrieving revision 1.99
diff -u -b -r1.99 equiv_type.m
--- compiler/equiv_type.m	10 Sep 2012 13:33:07 -0000	1.99
+++ compiler/equiv_type.m	24 Oct 2012 05:48:13 -0000
@@ -777,8 +777,9 @@
     tvarset::in, tvarset::out, equiv_type_info::in, equiv_type_info::out,
     used_modules::in, used_modules::out) is det.
 
-replace_in_type_defn(Location, EqvMap, EqvInstMap, TypeCtor, TypeDefn0, TypeDefn,
-        ContainsCirc, !VarSet, !EquivTypeInfo, !UsedModules) :-
+replace_in_type_defn(Location, EqvMap, EqvInstMap, TypeCtor,
+        TypeDefn0, TypeDefn, ContainsCirc, !VarSet,
+        !EquivTypeInfo, !UsedModules) :-
     (
         TypeDefn0 = parse_tree_eqv_type(TypeBody0),
         replace_in_type_location_2(Location, EqvMap, [TypeCtor],
Index: compiler/erl_call_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_call_gen.m,v
retrieving revision 1.21
diff -u -b -r1.21 erl_call_gen.m
--- compiler/erl_call_gen.m	2 Jul 2012 01:16:33 -0000	1.21
+++ compiler/erl_call_gen.m	24 Oct 2012 05:48:13 -0000
@@ -221,7 +221,8 @@
 :- pred make_semidet_call(elds_call_target::in, list(elds_expr)::in,
     prog_vars::in, elds_expr::in, elds_expr::out) is det.
 
-make_semidet_call(CallTarget, InputExprs, OutputVars, SuccessExpr, Statement) :-
+make_semidet_call(CallTarget, InputExprs, OutputVars, SuccessExpr,
+        Statement) :-
     CallExpr = elds_call(CallTarget, InputExprs),
     UnpackTerm = elds_tuple(exprs_from_vars(OutputVars)),
     ( if
Index: compiler/erl_code_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_code_gen.m,v
retrieving revision 1.46
diff -u -b -r1.46 erl_code_gen.m
--- compiler/erl_code_gen.m	2 Jul 2012 01:16:33 -0000	1.46
+++ compiler/erl_code_gen.m	24 Oct 2012 05:48:13 -0000
@@ -662,8 +662,8 @@
             MaybeSuccessExpr, Statement, !Info)
     ;
         GoalExpr = negation(SubGoal),
-        erl_gen_negation(SubGoal, CodeModel, InstMap, Context, MaybeSuccessExpr,
-            Statement, !Info)
+        erl_gen_negation(SubGoal, CodeModel, InstMap, Context,
+            MaybeSuccessExpr, Statement, !Info)
     ;
         GoalExpr = conj(_ConjType, Goals),
         % XXX Currently we treat parallel conjunction the same as
Index: compiler/erl_code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_code_util.m,v
retrieving revision 1.27
diff -u -b -r1.27 erl_code_util.m
--- compiler/erl_code_util.m	2 Jul 2012 01:16:33 -0000	1.27
+++ compiler/erl_code_util.m	24 Oct 2012 05:48:13 -0000
@@ -74,7 +74,8 @@
 
     % Lookup the type of a variable.
     %
-:- pred erl_variable_type(erl_gen_info::in, prog_var::in, mer_type::out) is det.
+:- pred erl_variable_type(erl_gen_info::in, prog_var::in, mer_type::out)
+    is det.
 
     % Add the given string as the name of an environment variable used by
     % the function being generated.
Index: compiler/erl_rtti.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_rtti.m,v
retrieving revision 1.26
diff -u -b -r1.26 erl_rtti.m
--- compiler/erl_rtti.m	5 Jul 2011 03:34:31 -0000	1.26
+++ compiler/erl_rtti.m	24 Oct 2012 05:48:13 -0000
@@ -332,7 +332,8 @@
     erl_gen_arg_list_arg_modes(ModuleInfo, no_opt_dummy_args,
         ExtraVarsWs, ArgTypes, ArgModes,
         WrapperInputVarsPlusExtras, WrapperOutputVars),
-    WrapperInputVars = list.delete_elems(WrapperInputVarsPlusExtras, ExtraVars),
+    WrapperInputVars =
+        list.delete_elems(WrapperInputVarsPlusExtras, ExtraVars),
 
     determinism_to_code_model(Detism, CodeModel),
     WrapperOutputVarsExprs = exprs_from_vars(WrapperOutputVars),
@@ -561,7 +562,8 @@
         gen_init_special_pred(ModuleInfo,
             CompareProcLabel, CompareExpr, !VarSet),
 
-        erlang_type_ctor_details(ModuleInfo, Details, ELDSDetails0, RttiDefns0),
+        erlang_type_ctor_details(ModuleInfo, Details, ELDSDetails0,
+            RttiDefns0),
         reduce_list_term_complexity(ELDSDetails0, ELDSDetails,
             [], RevAssignments, !VarSet),
 
@@ -832,7 +834,8 @@
     ).
 
 :- pred convert_arg_to_elds_expr(module_info::in, T::in, int::in,
-    elds_expr::out, list(elds_rtti_defn)::in, list(elds_rtti_defn)::out) is det.
+    elds_expr::out, list(elds_rtti_defn)::in, list(elds_rtti_defn)::out)
+    is det.
 
 convert_arg_to_elds_expr(MI, Term, Index, ELDS, !Defns) :-
     ( arg(Term, do_not_allow, Index, Arg) ->
Index: compiler/erl_unify_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/erl_unify_gen.m,v
retrieving revision 1.21
diff -u -b -r1.21 erl_unify_gen.m
--- compiler/erl_unify_gen.m	11 Jun 2012 03:13:20 -0000	1.21
+++ compiler/erl_unify_gen.m	24 Oct 2012 05:48:13 -0000
@@ -127,7 +127,8 @@
         % end
         %
         Statement = elds_case_expr(Test, [TrueCase, FalseCase]),
-        Test      = elds_binop((=:=), expr_from_var(Var1), expr_from_var(Var2)),
+        Test      = elds_binop((=:=),
+                        expr_from_var(Var1), expr_from_var(Var2)),
         TrueCase  = elds_case(elds_true, expr_or_void(MaybeSuccessExpr)),
         FalseCase = elds_case(elds_false, elds_term(elds_fail))
     ).
Index: compiler/exception_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/exception_analysis.m,v
retrieving revision 1.62
diff -u -b -r1.62 exception_analysis.m
--- compiler/exception_analysis.m	5 Sep 2012 06:18:13 -0000	1.62
+++ compiler/exception_analysis.m	24 Oct 2012 05:48:13 -0000
@@ -728,7 +728,8 @@
     proc_result::in, proc_result::out,
     module_info::in, module_info::out) is det.
 
-check_nonrecursive_call(VarTypes, PPId, Args, PredInfo, !Result, !ModuleInfo) :-
+check_nonrecursive_call(VarTypes, PPId, Args, PredInfo, !Result,
+        !ModuleInfo) :-
     module_info_get_globals(!.ModuleInfo, Globals),
     globals.lookup_bool_option(Globals, intermodule_analysis,
         IntermodAnalysis),
Index: compiler/float_regs.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/float_regs.m,v
retrieving revision 1.3
diff -u -b -r1.3 float_regs.m
--- compiler/float_regs.m	2 Jul 2012 01:16:33 -0000	1.3
+++ compiler/float_regs.m	24 Oct 2012 05:48:13 -0000
@@ -9,8 +9,8 @@
 % File: float_regs.m
 % Author: wangp.
 %
-% In the following we assume that Mercury `float' is wider than a word, and that
-% we are targeting a Mercury abstract machine with float registers.
+% In the following we assume that Mercury `float' is wider than a word,
+% and that we are targeting a Mercury abstract machine with float registers.
 % The module is not used otherwise.
 %
 % Arguments in first-order calls are passed via float registers if the formal
@@ -313,8 +313,8 @@
 add_arg_regs_in_mode(ModuleInfo, VarType, ArgMode0, ArgMode) :-
     add_arg_regs_in_mode_2(ModuleInfo, set.init, VarType, ArgMode0, ArgMode).
 
-:- pred add_arg_regs_in_mode_2(module_info::in, set(inst_name)::in, mer_type::in,
-    mer_mode::in, mer_mode::out) is det.
+:- pred add_arg_regs_in_mode_2(module_info::in, set(inst_name)::in,
+    mer_type::in, mer_mode::in, mer_mode::out) is det.
 
 add_arg_regs_in_mode_2(ModuleInfo, Seen, VarType, ArgMode0, ArgMode) :-
     mode_get_insts(ModuleInfo, ArgMode0, InitialInst0, FinalInst0),
Index: compiler/gcc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/gcc.m,v
retrieving revision 1.36
diff -u -b -r1.36 gcc.m
--- compiler/gcc.m	10 Sep 2010 05:14:57 -0000	1.36
+++ compiler/gcc.m	24 Oct 2012 05:48:13 -0000
@@ -606,7 +606,8 @@
 % Routines to generate code for switches.
 %
 
-:- pred gen_start_switch(gcc.expr::in, gcc.gcc_type::in, io::di, io::uo) is det.
+:- pred gen_start_switch(gcc.expr::in, gcc.gcc_type::in, io::di, io::uo)
+    is det.
 
 :- pred gen_case_label(gcc.expr::in, gcc.label::in, io::di, io::uo) is det.
 
Index: compiler/globals.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/globals.m,v
retrieving revision 1.106
diff -u -b -r1.106 globals.m
--- compiler/globals.m	19 Jul 2012 11:44:12 -0000	1.106
+++ compiler/globals.m	24 Oct 2012 05:48:13 -0000
@@ -220,7 +220,8 @@
 :- pred convert_reuse_strategy(string::in, int::in, reuse_strategy::out)
     is semidet.
 :- pred convert_env_type(string::in, env_type::out) is semidet.
-:- pred convert_ssdb_trace_level(string::in, bool::in, ssdb_trace_level::out) is semidet.
+:- pred convert_ssdb_trace_level(string::in, bool::in, ssdb_trace_level::out)
+    is semidet.
 
 %-----------------------------------------------------------------------------%
 %
@@ -256,7 +257,8 @@
 :- pred get_ssdb_trace_level(globals::in, ssdb_trace_level::out) is det.
 :- pred get_maybe_thread_safe(globals::in, may_be_thread_safe::out) is det.
 :- pred get_c_compiler_type(globals::in, c_compiler_type::out) is det.
-:- pred get_csharp_compiler_type(globals::in, csharp_compiler_type::out) is det.
+:- pred get_csharp_compiler_type(globals::in, csharp_compiler_type::out)
+    is det.
 :- pred get_reuse_strategy(globals::in, reuse_strategy::out) is det.
 :- pred get_maybe_il_version_number(globals::in, maybe(il_version_number)::out)
     is det.
@@ -271,7 +273,8 @@
 :- pred set_tags_method(tags_method::in, globals::in, globals::out) is det.
 :- pred set_trace_level(trace_level::in, globals::in, globals::out) is det.
 :- pred set_trace_level_none(globals::in, globals::out) is det.
-:- pred set_ssdb_trace_level(ssdb_trace_level::in, globals::in, globals::out) is det.
+:- pred set_ssdb_trace_level(ssdb_trace_level::in,
+    globals::in, globals::out) is det.
 :- pred set_maybe_feedback_info(maybe(feedback_info)::in, 
     globals::in, globals::out) is det.
 
Index: compiler/goal_expr_to_goal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_expr_to_goal.m,v
retrieving revision 1.8
diff -u -b -r1.8 goal_expr_to_goal.m
--- compiler/goal_expr_to_goal.m	10 Sep 2012 13:33:07 -0000	1.8
+++ compiler/goal_expr_to_goal.m	24 Oct 2012 05:48:13 -0000
@@ -256,8 +256,8 @@
             !SVarStore, !VarSet, !ModuleInfo, !QualInfo, !Specs),
         MainDisjState =
             hlds_goal_svar_state(HLDSMainGoal0, AfterMainSVarState),
-        transform_orelse_goals(LocKind, OrElseExprs, Renaming, OrElseDisjStates,
-            BeforeDisjSVarState, !SVarStore, !VarSet,
+        transform_orelse_goals(LocKind, OrElseExprs, Renaming,
+            OrElseDisjStates, BeforeDisjSVarState, !SVarStore, !VarSet,
             !ModuleInfo, !QualInfo, !Specs),
         AllDisjStates = [MainDisjState | OrElseDisjStates],
         svar_finish_disjunction(Context, AllDisjStates, HLDSGoals, !VarSet,
Index: compiler/goal_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_util.m,v
retrieving revision 1.195
diff -u -b -r1.195 goal_util.m
--- compiler/goal_util.m	2 Jul 2012 01:16:33 -0000	1.195
+++ compiler/goal_util.m	24 Oct 2012 05:48:13 -0000
@@ -2082,7 +2082,8 @@
             ->
                 list.take_upto(ConjNum - 1, Conjs0, HeadConjs),
                 HeadInstdeltas = map(
-                    (func(G) = goal_info_get_instmap_delta(G ^ hlds_goal_info)),
+                    (func(G) =
+                        goal_info_get_instmap_delta(G ^ hlds_goal_info)),
                     HeadConjs),
                 foldl(apply_instmap_delta_sv, HeadInstdeltas, 
                     Instmap0, Instmap),
Index: compiler/hlds_args.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_args.m,v
retrieving revision 1.6
diff -u -b -r1.6 hlds_args.m
--- compiler/hlds_args.m	30 Dec 2010 11:17:54 -0000	1.6
+++ compiler/hlds_args.m	24 Oct 2012 05:48:13 -0000
@@ -290,15 +290,22 @@
 
 %-----------------------------------------------------------------------------%
 
-proc_arg_vector_get_instance_type_infos(V)      = V ^ pav_instance_type_infos.
-proc_arg_vector_get_instance_typeclass_infos(V) =
-    V ^ pav_instance_typeclass_infos.
-proc_arg_vector_get_univ_type_infos(V)          = V ^ pav_univ_type_infos.
-proc_arg_vector_get_exist_type_infos(V)         = V ^ pav_exist_type_infos.
-proc_arg_vector_get_univ_typeclass_infos(V)     = V ^ pav_univ_typeclass_infos.
-proc_arg_vector_get_exist_typeclass_infos(V)    = V ^ pav_exist_typeclass_infos.
-proc_arg_vector_get_user_args(V)                = V ^ pav_user_args.
-proc_arg_vector_get_maybe_ret_value(V)          = V ^ pav_maybe_ret_value.
+proc_arg_vector_get_instance_type_infos(V)
+    = V ^ pav_instance_type_infos.
+proc_arg_vector_get_instance_typeclass_infos(V)
+    = V ^ pav_instance_typeclass_infos.
+proc_arg_vector_get_univ_type_infos(V)
+    = V ^ pav_univ_type_infos.
+proc_arg_vector_get_exist_type_infos(V)
+    = V ^ pav_exist_type_infos.
+proc_arg_vector_get_univ_typeclass_infos(V)
+    = V ^ pav_univ_typeclass_infos.
+proc_arg_vector_get_exist_typeclass_infos(V)
+    = V ^ pav_exist_typeclass_infos.
+proc_arg_vector_get_user_args(V)
+    = V ^ pav_user_args.
+proc_arg_vector_get_maybe_ret_value(V)
+    = V ^ pav_maybe_ret_value.
 
 proc_arg_vector_set_instance_type_infos(ITI, !V) :-
     !V ^ pav_instance_type_infos := ITI.
Index: compiler/hlds_goal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_goal.m,v
retrieving revision 1.240
diff -u -b -r1.240 hlds_goal.m
--- compiler/hlds_goal.m	8 Oct 2012 04:14:45 -0000	1.240
+++ compiler/hlds_goal.m	24 Oct 2012 05:48:13 -0000
@@ -1343,14 +1343,14 @@
     hlds_goal_info::in, hlds_goal_info::out) is det.
 :- pred goal_info_set_maybe_ctgc(maybe(ctgc_goal_info)::in,
     hlds_goal_info::in, hlds_goal_info::out) is det.
-:- pred goal_info_set_lfu(set_of_progvar::in, hlds_goal_info::in,
-    hlds_goal_info::out) is det.
-:- pred goal_info_set_lbu(set_of_progvar::in, hlds_goal_info::in,
-    hlds_goal_info::out) is det.
-:- pred goal_info_set_reuse(reuse_description::in, hlds_goal_info::in,
-    hlds_goal_info::out) is det.
-:- pred goal_info_set_maybe_dp_info(maybe(dp_goal_info)::in, hlds_goal_info::in,
-    hlds_goal_info::out) is det.
+:- pred goal_info_set_lfu(set_of_progvar::in,
+    hlds_goal_info::in, hlds_goal_info::out) is det.
+:- pred goal_info_set_lbu(set_of_progvar::in,
+    hlds_goal_info::in, hlds_goal_info::out) is det.
+:- pred goal_info_set_reuse(reuse_description::in,
+    hlds_goal_info::in, hlds_goal_info::out) is det.
+:- pred goal_info_set_maybe_dp_info(maybe(dp_goal_info)::in,
+    hlds_goal_info::in, hlds_goal_info::out) is det.
 
     % The following functions produce an 'unexpected' error when the
     % requested values have not been set.
@@ -1366,10 +1366,10 @@
     is det.
 :- pred goal_info_get_consuming_vars(hlds_goal_info::in, set_of_progvar::out)
     is det.
-:- pred goal_info_get_make_visible_vars(hlds_goal_info::in, set_of_progvar::out)
-    is det.
-:- pred goal_info_get_need_visible_vars(hlds_goal_info::in, set_of_progvar::out)
-    is det.
+:- pred goal_info_get_make_visible_vars(hlds_goal_info::in,
+    set_of_progvar::out) is det.
+:- pred goal_info_get_need_visible_vars(hlds_goal_info::in,
+    set_of_progvar::out) is det.
 
 :- pred goal_info_set_occurring_vars(set_of_progvar::in,
     hlds_goal_info::in, hlds_goal_info::out) is det.
@@ -2878,7 +2878,8 @@
                 MaybeOutputVars = MaybeOutputVars0
             ;
                 MaybeOutputVars0 = yes(OutputVars0),
-                rename_var_list(need_not_rename, Subn, OutputVars0, OutputVars),
+                rename_var_list(need_not_rename, Subn,
+                    OutputVars0, OutputVars),
                 MaybeOutputVars = yes(OutputVars)
             ),
             incremental_rename_vars_in_goal(Subn, SubnUpdates,
@@ -3093,7 +3094,8 @@
         MaybeRBMM = no
     ;
         MaybeRBMM0 = yes(RBMM0),
-        RBMM0 = rbmm_goal_info(Created0, Removed0, Carried0, Alloc0, NonAlloc0),
+        RBMM0 = rbmm_goal_info(Created0, Removed0, Carried0, Alloc0,
+            NonAlloc0),
         rename_vars_in_var_set(Must, Subn, Created0, Created),
         rename_vars_in_var_set(Must, Subn, Removed0, Removed),
         rename_vars_in_var_set(Must, Subn, Carried0, Carried),
Index: compiler/hlds_out_pred.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_out_pred.m,v
retrieving revision 1.13
diff -u -b -r1.13 hlds_out_pred.m
--- compiler/hlds_out_pred.m	2 Jul 2012 01:16:34 -0000	1.13
+++ compiler/hlds_out_pred.m	24 Oct 2012 05:48:13 -0000
@@ -909,7 +909,8 @@
                 (
                     MaybeOldOutermost = yes(OldOutermost),
                     io.write_string(", OldOutermost is ", !IO),
-                    mercury_output_var(VarSet, AppendVarNums, OldOutermost, !IO)
+                    mercury_output_var(VarSet, AppendVarNums, OldOutermost,
+                        !IO)
                 ;
                     MaybeOldOutermost = no
                 ),
Index: compiler/hlds_statistics.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_statistics.m,v
retrieving revision 1.5
diff -u -b -r1.5 hlds_statistics.m
--- compiler/hlds_statistics.m	13 Feb 2012 00:11:40 -0000	1.5
+++ compiler/hlds_statistics.m	24 Oct 2012 05:48:13 -0000
@@ -63,7 +63,8 @@
 :- pred write_proc_stats_for_pred(io.output_stream::in, string::in,
     module_info::in, pair(pred_id, pred_info)::in, io::di, io::uo) is det.
 
-write_proc_stats_for_pred(OutStream, Msg, ModuleInfo, PredId - PredInfo, !IO) :-
+write_proc_stats_for_pred(OutStream, Msg, ModuleInfo, PredId - PredInfo,
+        !IO) :-
     (
         ( pred_info_is_imported(PredInfo)
         ; is_unify_or_compare_pred(PredInfo)
Index: compiler/inst_match.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inst_match.m,v
retrieving revision 1.101
diff -u -b -r1.101 inst_match.m
--- compiler/inst_match.m	22 Jun 2012 17:20:10 -0000	1.101
+++ compiler/inst_match.m	24 Oct 2012 05:48:13 -0000
@@ -1105,8 +1105,8 @@
         % We do not yet allow `free' to match `any'.
         % Among other things, changing this would break compare_inst
         % in modecheck_call.m.
-        inst_results_bound_inst_list_is_ground_or_any(InstResultsA, BoundInstsA,
-            !.Info ^ imi_module_info)
+        inst_results_bound_inst_list_is_ground_or_any(InstResultsA,
+            BoundInstsA, !.Info ^ imi_module_info)
     ;
         InstA = bound(UniqA, _InstResultsA, BoundInstsA),
         InstB = bound(UniqB, _InstResultsB, BoundInstsB),
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.127
diff -u -b -r1.127 layout_out.m
--- compiler/layout_out.m	24 Oct 2012 04:59:52 -0000	1.127
+++ compiler/layout_out.m	24 Oct 2012 05:48:13 -0000
@@ -1269,11 +1269,9 @@
     io.write_string(",", !IO),
     (
         MaybeCoveragePoints = yes({CoveragePointsSlot, NumCoveragePoints}),
-        /*
-        ** If MR_DEEP_PROFILING_COVERAGE is not defined but
-        ** --deep-profiling-coverage is this generated code will not compile, as
-        ** these fields in this structure will not be present.
-        */
+        % If MR_DEEP_PROFILING_COVERAGE is not defined but
+        % --deep-profiling-coverage is, this generated code will not compile,
+        % as these fields in this structure will not be present.
         io.write_int(NumCoveragePoints, !IO),
         io.write_string(",\n", !IO),
         CoveragePointsStaticSlotName =
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.154
diff -u -b -r1.154 live_vars.m
--- compiler/live_vars.m	2 Jul 2012 01:16:34 -0000	1.154
+++ compiler/live_vars.m	24 Oct 2012 05:48:13 -0000
@@ -884,7 +884,8 @@
         % accumulating set.
         OuterAccStackVars = OuterAccStackVars0
             `set_of_var.union` InnerStackVars
-            `set_of_var.union` (LiveSet `set_of_var.difference` OuterNonLocals),
+            `set_of_var.union`
+                (LiveSet `set_of_var.difference` OuterNonLocals),
         ParStackVars = parallel_conjunction(OuterNonLocals,
             OuterLocalStackVars, OuterAccStackVars)
     ;
@@ -894,7 +895,8 @@
         % control.  The same is true in the case for
         % after_loop_control_scope/2 below.
         StackVars = StackVars0 `set_of_var.union` InnerStackVars
-            `set_of_var.union` (LiveSet `set_of_var.difference` OuterNonLocals),
+            `set_of_var.union`
+                (LiveSet `set_of_var.difference` OuterNonLocals),
         ParStackVars = loop_control_scope(OuterNonLocals, StackVars)
     ;
         OuterParStackVars = after_loop_control_scope(StackVarsList,
@@ -987,7 +989,8 @@
 par_stack_vars_get_nonlocals(not_in_parallel_context, set_of_var.init).
 par_stack_vars_get_nonlocals(parallel_conjunction(NonLocals, _, _), NonLocals).
 par_stack_vars_get_nonlocals(loop_control_scope(NonLocals, _), NonLocals).
-par_stack_vars_get_nonlocals(after_loop_control_scope(_, _, _), set_of_var.init).
+par_stack_vars_get_nonlocals(after_loop_control_scope(_, _, _),
+    set_of_var.init).
 
 :- pred par_stack_vars_next_par_conjunct(
     parallel_stackvars::in, parallel_stackvars::out) is det.
@@ -1016,8 +1019,8 @@
         !.ParStackVars = loop_control_scope(_, _),
         unexpected($module, $pred, "recursive call in loop control scope")
     ;
-        !.ParStackVars = after_loop_control_scope(StackVarsList0, DelayDeathSet,
-            StackVars),
+        !.ParStackVars = after_loop_control_scope(StackVarsList0,
+            DelayDeathSet, StackVars),
         StackVarsList = [StackVars | StackVarsList0],
         cartesian_product_list(StackVarsList, NonoverlapSets),
         MaybeNeedLC = yes(need_for_loop_control(NonoverlapSets)),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.186
diff -u -b -r1.186 liveness.m
--- compiler/liveness.m	2 Jul 2012 01:16:34 -0000	1.186
+++ compiler/liveness.m	24 Oct 2012 05:48:13 -0000
@@ -1322,7 +1322,8 @@
         DelayedDead = DelayedDeadGoal
     ).
 
-:- pred delay_death_cases(list(case)::in, assoc_list(case, set_of_progvar)::out,
+:- pred delay_death_cases(list(case)::in,
+    assoc_list(case, set_of_progvar)::out,
     set_of_progvar::in, set_of_progvar::in, prog_varset::in,
     maybe(pair(set_of_progvar))::out) is det.
 
Index: compiler/make.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make.m,v
retrieving revision 1.69
diff -u -b -r1.69 make.m
Index: compiler/make.program_target.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make.program_target.m,v
retrieving revision 1.117
diff -u -b -r1.117 make.program_target.m
--- compiler/make.program_target.m	11 May 2012 03:56:48 -0000	1.117
+++ compiler/make.program_target.m	24 Oct 2012 05:48:13 -0000
@@ -853,8 +853,8 @@
             Succeeded = no
         ;
             % Ensure all interface files are present before continuing.
-            % This prevents a problem when two parallel branches try to generate
-            % the same missing interface file later.
+            % This prevents a problem when two parallel branches
+            % try to generate the same missing interface file later.
             make_all_interface_files(Globals, AllModules, Succeeded1,
                 !Info, !IO),
             ( Succeeded1 = no, KeepGoing = no ->
Index: compiler/make_tags.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/make_tags.m,v
retrieving revision 1.68
diff -u -b -r1.68 make_tags.m
--- compiler/make_tags.m	22 Nov 2011 23:04:52 -0000	1.68
+++ compiler/make_tags.m	24 Oct 2012 05:48:13 -0000
@@ -480,7 +480,8 @@
         TypeCtorsDefns, !TypeTable, !Specs).
 
 :- pred convert_direct_arg_functors_if_suitable(module_name::in, bool::in,
-    int::in, type_ctor::in, hlds_type_defn::in, type_table::in, type_table::out,
+    int::in, type_ctor::in, hlds_type_defn::in,
+    type_table::in, type_table::out,
     list(error_spec)::in, list(error_spec)::out) is det.
 
 convert_direct_arg_functors_if_suitable(ModuleName, DebugTypeRep, MaxTag,
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.521
diff -u -b -r1.521 mercury_compile.m
--- compiler/mercury_compile.m	27 Mar 2012 23:29:11 -0000	1.521
+++ compiler/mercury_compile.m	24 Oct 2012 05:48:13 -0000
@@ -128,7 +128,8 @@
 
     % Expand @File arguments.
     % Each argument in the above form is replaced with a list of arguments
-    % where each arg is each line in the file File which is not just whitespace.
+    % where each arg is each line in the file File which is not just
+    % whitespace.
     %
 :- pred expand_at_file_arguments(list(string)::in, io.res(list(string))::out,
     io::di, io::uo) is det.
@@ -1249,8 +1250,9 @@
 
 process_module_2_callback(OptionArgs, FileOrModule, MaybeModulesToRecompile,
         HaveReadModuleMap0, Globals, Result, !IO) :-
-    process_module_2(Globals, OptionArgs, FileOrModule, MaybeModulesToRecompile,
-        HaveReadModuleMap0, ModulesToLink, ExtraObjFiles, !IO),
+    process_module_2(Globals, OptionArgs, FileOrModule,
+        MaybeModulesToRecompile, HaveReadModuleMap0, ModulesToLink,
+        ExtraObjFiles, !IO),
     Result = {ModulesToLink, ExtraObjFiles}.
 
 :- pred process_module_2(globals::in, list(string)::in, file_or_module::in,
@@ -2022,9 +2024,9 @@
     bool::out, bool::out, list(error_spec)::in, list(error_spec)::out,
     io::di, io::uo) is det.
 
-invoke_module_qualify_items(Globals, Items0, Items, EventSpecMap0, EventSpecMap,
-        ModuleName, EventSpecFileName, Verbose, Stats, MQInfo,
-        UndefTypes, UndefModes, !Specs, !IO) :-
+invoke_module_qualify_items(Globals, Items0, Items,
+        EventSpecMap0, EventSpecMap, ModuleName, EventSpecFileName,
+        Verbose, Stats, MQInfo, UndefTypes, UndefModes, !Specs, !IO) :-
     maybe_write_out_errors_no_module(Verbose, Globals, !Specs, !IO),
     maybe_write_string(Verbose, "% Module qualifying items...\n", !IO),
     maybe_flush_output(Verbose, !IO),
Index: compiler/mercury_compile_front_end.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile_front_end.m,v
retrieving revision 1.12
diff -u -b -r1.12 mercury_compile_front_end.m
--- compiler/mercury_compile_front_end.m	8 Oct 2012 04:14:46 -0000	1.12
+++ compiler/mercury_compile_front_end.m	24 Oct 2012 05:48:13 -0000
@@ -673,7 +673,8 @@
     (
         BenchmarkModes = yes,
         globals.lookup_int_option(Globals, benchmark_modes_repeat, Repeats),
-        promise_equivalent_solutions [!:HLDS, SafeToContinue, ModeSpecs, Time] (
+        promise_equivalent_solutions [!:HLDS, SafeToContinue, ModeSpecs, Time]
+        (
             benchmark_det(modecheck_module,
                 !.HLDS, {!:HLDS, SafeToContinue, ModeSpecs}, Repeats, Time)
         ),
Index: compiler/mercury_compile_middle_passes.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile_middle_passes.m,v
retrieving revision 1.18
diff -u -b -r1.18 mercury_compile_middle_passes.m
--- compiler/mercury_compile_middle_passes.m	19 Jul 2012 11:44:12 -0000	1.18
+++ compiler/mercury_compile_middle_passes.m	24 Oct 2012 05:48:13 -0000
@@ -217,8 +217,8 @@
 
     maybe_simplify(no, simplify_pass_pre_implicit_parallelism, Verbose, Stats,
         !HLDS, [], _SimplifySpecsPreImpPar, !IO),
-    maybe_dump_hlds(!.HLDS, 172, "pre_implicit_parallelism_simplify", !DumpInfo,
-        !IO),
+    maybe_dump_hlds(!.HLDS, 172, "pre_implicit_parallelism_simplify",
+        !DumpInfo, !IO),
 
     maybe_implicit_parallelism(Verbose, Stats, !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 173, "implicit_parallelism", !DumpInfo, !IO),
@@ -865,7 +865,8 @@
         ForceDisableSSDB = no
     ->
         maybe_write_string(Verbose,
-            "% Maybe apply source to source debugging transformation ...\n", !IO),
+            "% Maybe apply source to source debugging transformation ...\n",
+            !IO),
         ssdebug_transform_module(!HLDS, !IO),
         maybe_write_string(Verbose, "% done.\n", !IO),
         maybe_report_stats(Stats, !IO)
Index: compiler/mercury_to_mercury.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
retrieving revision 1.364
diff -u -b -r1.364 mercury_to_mercury.m
--- compiler/mercury_to_mercury.m	8 Oct 2012 04:14:46 -0000	1.364
+++ compiler/mercury_to_mercury.m	24 Oct 2012 05:48:13 -0000
@@ -82,7 +82,8 @@
 
     % Output the specified item, followed by ".\n".
     %
-:- pred mercury_output_item(merc_out_info::in, item::in, io::di, io::uo) is det.
+:- pred mercury_output_item(merc_out_info::in, item::in, io::di, io::uo)
+    is det.
 
     % Output a `:- pred' declaration, making sure that the variable
     % number appears in variable names if the boolean argument
@@ -3084,8 +3085,8 @@
     list(prog_var)::in, list(prog_var)::in, list(prog_var)::in,
     goal::in, prog_varset::in, int::in, string::in, io::di, io::uo) is det.
 
-mercury_output_promise_eqv_solutions_goal(Vars, StateVars, DotSVars, ColonSVars,
-        Goal, VarSet, Indent, Keyword, !IO) :-
+mercury_output_promise_eqv_solutions_goal(Vars, StateVars,
+        DotSVars, ColonSVars, Goal, VarSet, Indent, Keyword, !IO) :-
     (
         Vars = [],
         StateVars = [],
@@ -3687,7 +3688,8 @@
 %-----------------------------------------------------------------------------%
 
 mercury_output_pragma_trailing_info(TrailingInfo, !IO) :-
-    TrailingInfo = pragma_info_trailing_info(PredNameArityPFMn, TrailingStatus),
+    TrailingInfo =
+        pragma_info_trailing_info(PredNameArityPFMn, TrailingStatus),
     PredNameArityPFMn = pred_name_arity_pf_mn(SymName, Arity, PredOrFunc,
         ModeNum),
     io.write_string(":- pragma trailing_info(", !IO),
Index: compiler/ml_foreign_proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_foreign_proc_gen.m,v
retrieving revision 1.10
diff -u -b -r1.10 ml_foreign_proc_gen.m
--- compiler/ml_foreign_proc_gen.m	15 Jun 2011 17:30:09 -0000	1.10
+++ compiler/ml_foreign_proc_gen.m	24 Oct 2012 05:48:13 -0000
@@ -201,7 +201,8 @@
     ),
 
     % Generate <declaration of one local variable for each arg>
-    ml_gen_pragma_csharp_java_decls(!.Info, MutableSpecial, Args, ArgDeclsList),
+    ml_gen_pragma_csharp_java_decls(!.Info, MutableSpecial, Args,
+        ArgDeclsList),
     expect(unify(ExtraArgs, []), $module, $pred, "extra args"),
 
     % Generate code to set the values of the input variables.
Index: compiler/ml_type_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_type_gen.m,v
retrieving revision 1.104
diff -u -b -r1.104 ml_type_gen.m
--- compiler/ml_type_gen.m	11 Jun 2012 03:13:21 -0000	1.104
+++ compiler/ml_type_gen.m	24 Oct 2012 05:48:13 -0000
@@ -704,7 +704,8 @@
             GCStatement = gc_no_stmt,
             EntityDefn = mlds_data(SecondaryTagClassId, no_initializer,
                 GCStatement),
-            DeclFlags = mlds.set_access(ml_static_const_decl_flags, acc_public),
+            DeclFlags = mlds.set_access(ml_static_const_decl_flags,
+                acc_public),
             MLDS_ReservedObjDefn = mlds_defn(MLDS_ReservedObjEntityName,
                 MLDS_Context, DeclFlags, EntityDefn),
             MLDS_Members = [MLDS_ReservedObjDefn | MLDS_Members0]
Index: compiler/mlds_to_c.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mlds_to_c.m,v
retrieving revision 1.264
diff -u -b -r1.264 mlds_to_c.m
--- compiler/mlds_to_c.m	8 Jun 2012 15:46:21 -0000	1.264
+++ compiler/mlds_to_c.m	24 Oct 2012 05:48:13 -0000
@@ -271,7 +271,8 @@
     list.filter(defn_is_type, PublicDefns, PublicTypeDefns,
         PublicNonTypeDefns),
     MLDS_ModuleName = mercury_module_name_to_mlds(ModuleName),
-    mlds_output_defns(Opts, Indent, yes, MLDS_ModuleName, PublicTypeDefns, !IO),
+    mlds_output_defns(Opts, Indent, yes, MLDS_ModuleName, PublicTypeDefns,
+        !IO),
     io.nl(!IO),
     StdOpts = Opts ^ m2co_std_func_decl := yes,
     mlds_output_decls(StdOpts, Indent, MLDS_ModuleName, PublicNonTypeDefns,
@@ -1905,7 +1906,8 @@
             MaybeBody, _Attributes, _EnvVarNames),
         mlds_output_maybe(MaybePredProcId, mlds_output_pred_proc_id(Opts),
             !IO),
-        mlds_output_func(Opts, Indent, Name, Context, Signature, MaybeBody, !IO)
+        mlds_output_func(Opts, Indent, Name, Context, Signature, MaybeBody,
+            !IO)
     ;
         DefnBody = mlds_class(ClassDefn),
         mlds_output_class(Opts, Indent, Name, Context, ClassDefn, !IO)
Index: compiler/mlds_to_cs.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mlds_to_cs.m,v
retrieving revision 1.22
diff -u -b -r1.22 mlds_to_cs.m
--- compiler/mlds_to_cs.m	15 Jul 2012 07:39:30 -0000	1.22
+++ compiler/mlds_to_cs.m	24 Oct 2012 05:48:13 -0000
@@ -1585,8 +1585,8 @@
 needs_initialization(init_struct(_, _)) = yes.
 needs_initialization(init_array(_)) = yes.
 
-:- pred output_initializer_alloc_only(csharp_out_info::in, mlds_initializer::in,
-    maybe(mlds_type)::in, io::di, io::uo) is det.
+:- pred output_initializer_alloc_only(csharp_out_info::in,
+    mlds_initializer::in, maybe(mlds_type)::in, io::di, io::uo) is det.
 
 output_initializer_alloc_only(Info, Initializer, MaybeType, !IO) :-
     (
@@ -3348,8 +3348,8 @@
         output_bracketed_rval(Info, Rval, !IO)
     ).
 
-:- pred output_bracketed_rval(csharp_out_info::in, mlds_rval::in, io::di, io::uo)
-    is det.
+:- pred output_bracketed_rval(csharp_out_info::in, mlds_rval::in,
+    io::di, io::uo) is det.
 
 output_bracketed_rval(Info, Rval, !IO) :-
     (
@@ -3694,8 +3694,8 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred mlds_output_code_addr(csharp_out_info::in, mlds_code_addr::in, bool::in,
-    io::di, io::uo) is det.
+:- pred mlds_output_code_addr(csharp_out_info::in, mlds_code_addr::in,
+    bool::in, io::di, io::uo) is det.
 
 mlds_output_code_addr(Info, CodeAddr, IsCall, !IO) :-
     ( CodeAddr = code_addr_proc(_, Sig)
Index: compiler/mlds_to_il.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mlds_to_il.m,v
retrieving revision 1.228
diff -u -b -r1.228 mlds_to_il.m
--- compiler/mlds_to_il.m	8 Jun 2012 15:36:58 -0000	1.228
+++ compiler/mlds_to_il.m	24 Oct 2012 05:48:13 -0000
@@ -545,7 +545,8 @@
 
 rename_atomic(comment(S)) = comment(S).
 rename_atomic(assign(L, R)) = assign(rename_lval(L), rename_rval(R)).
-rename_atomic(assign_if_in_heap(L, R)) = assign(rename_lval(L), rename_rval(R)).
+rename_atomic(assign_if_in_heap(L, R)) =
+    assign(rename_lval(L), rename_rval(R)).
 rename_atomic(delete_object(O)) = delete_object(rename_rval(O)).
 rename_atomic(new_object(L, Tag, ExplicitSecTag, Type, MaybeSize, Ctxt, Args,
         Types, MayUseAtomic, AllocId))
Index: compiler/mlds_to_java.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mlds_to_java.m,v
retrieving revision 1.174
diff -u -b -r1.174 mlds_to_java.m
--- compiler/mlds_to_java.m	22 Aug 2011 07:56:09 -0000	1.174
+++ compiler/mlds_to_java.m	24 Oct 2012 05:48:13 -0000
@@ -1096,7 +1096,8 @@
 
     add_to_address_map(ClassName, CodeAddrs, !AddrOfMap).
 
-    % The highest arity for which there is a specialised MethodPtr<n> interface.
+    % The highest arity for which there is a specialised MethodPtr<n>
+    % interface.
     %
 :- func max_specialised_method_ptr_arity = int.
 
@@ -4864,7 +4865,8 @@
         io.write_string(")", !IO)
     ).
 
-    % java_builtin_type(MLDS_Type, JavaUnboxedType, JavaBoxedType, UnboxMethod):
+    % java_builtin_type(MLDS_Type, JavaUnboxedType, JavaBoxedType,
+    %   UnboxMethod):
     %
     % For a given Mercury type, check if this corresponds to a Java type
     % which has both unboxed (builtin) and boxed (class) versions, and if so,
Index: compiler/mode_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mode_debug.m,v
retrieving revision 1.35
diff -u -b -r1.35 mode_debug.m
--- compiler/mode_debug.m	23 Apr 2012 03:34:48 -0000	1.35
+++ compiler/mode_debug.m	24 Oct 2012 05:48:13 -0000
@@ -94,7 +94,8 @@
                 maybe_flush_output(Statistics, !IO),
                 ( instmap_is_reachable(InstMap) ->
                     instmap_to_assoc_list(InstMap, NewInsts),
-                    mode_info_get_last_checkpoint_insts(!.ModeInfo, OldInstMap),
+                    mode_info_get_last_checkpoint_insts(!.ModeInfo,
+                        OldInstMap),
                     mode_info_get_varset(!.ModeInfo, VarSet),
                     mode_info_get_instvarset(!.ModeInfo, InstVarSet),
                     write_var_insts(NewInsts, OldInstMap, VarSet, InstVarSet,
Index: compiler/mode_ordering.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mode_ordering.m,v
retrieving revision 1.41
diff -u -b -r1.41 mode_ordering.m
--- compiler/mode_ordering.m	13 Feb 2012 00:11:42 -0000	1.41
+++ compiler/mode_ordering.m	24 Oct 2012 05:48:13 -0000
@@ -251,7 +251,8 @@
                 MakeVisibleVars = set_of_var.init,
                 NeedVisibleVars = set_of_var.list_to_set([VarA, VarB])
             ),
-            ConsumingVarsList = solutions.solutions((pred(Var::out) is nondet :-
+            ConsumingVarsList = solutions.solutions(
+                (pred(Var::out) is nondet :-
                 inst_graph.same_graph_corresponding_nodes(InstGraph,
                     VarA, VarB, VarC, VarD),
                 ( set_of_var.contains(ProdVars, VarC) ->
@@ -260,7 +261,9 @@
                     Var = VarC
                 ;
                     fail
-                ))),
+                    )
+                )
+            ),
             ConsumingVars = set_of_var.sorted_list_to_set(ConsumingVarsList)
         ;
             RHS0 = rhs_functor(_ConsId, _IsExistConstruct, ArgVars),
Index: compiler/modecheck_unify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modecheck_unify.m,v
retrieving revision 1.148
diff -u -b -r1.148 modecheck_unify.m
--- compiler/modecheck_unify.m	2 Jul 2012 01:16:35 -0000	1.148
+++ compiler/modecheck_unify.m	24 Oct 2012 05:48:13 -0000
@@ -1267,7 +1267,8 @@
         UnifyTypeInfoVars = [_ | _],
         list.length(UnifyTypeInfoVars, NumTypeInfoVars),
         list.duplicate(NumTypeInfoVars, ground(shared, none), ExpectedInsts),
-        mode_info_set_call_context(call_context_unify(UnifyContext), !ModeInfo),
+        mode_info_set_call_context(call_context_unify(UnifyContext),
+            !ModeInfo),
         InitialArgNum = 0,
         modecheck_var_has_inst_list_no_exact_match(UnifyTypeInfoVars,
             ExpectedInsts, InitialArgNum, _InstVarSub, !ModeInfo),
@@ -1570,7 +1571,8 @@
     ;       ho_arg_not_ground.
 
 :- pred match_modes_by_higher_order_insts(module_info::in, instmap::in,
-    vartypes::in, prog_vars::in, pred_info::in, match_modes_result::out) is det.
+    vartypes::in, prog_vars::in, pred_info::in, match_modes_result::out)
+    is det.
 
 match_modes_by_higher_order_insts(ModuleInfo, InstMap, VarTypes, ArgVars,
         CalleePredInfo, Result) :-
Index: compiler/module_cmds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/module_cmds.m,v
retrieving revision 1.22
diff -u -b -r1.22 module_cmds.m
--- compiler/module_cmds.m	19 Jul 2012 11:44:12 -0000	1.22
+++ compiler/module_cmds.m	24 Oct 2012 05:48:13 -0000
@@ -994,7 +994,8 @@
         MainFunc = "main_2_p_0"
     ),
 
-    % Add `-pa <dir>' options to find any other libraries specified by the user.
+    % Add `-pa <dir>' options to find any other libraries specified
+    % by the user.
     globals.lookup_accumulating_option(Globals, mercury_library_directories,
         MercuryLibDirs0),
     MercuryLibDirs = list.map((func(LibDir) = LibDir/"lib"/GradeDir),
@@ -1056,7 +1057,8 @@
         MainFunc = "main_2_p_0"
     ),
 
-    % Add `-pa <dir>' options to find any other libraries specified by the user.
+    % Add `-pa <dir>' options to find any other libraries specified
+    % by the user.
     globals.lookup_accumulating_option(Globals, mercury_library_directories,
         MercuryLibDirs0),
     MercuryLibDirs = list.map((func(LibDir) = LibDir/"lib"/GradeDir),
Index: compiler/module_qual.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/module_qual.m,v
retrieving revision 1.196
diff -u -b -r1.196 module_qual.m
--- compiler/module_qual.m	8 Oct 2012 04:14:46 -0000	1.196
+++ compiler/module_qual.m	24 Oct 2012 05:48:13 -0000
@@ -921,7 +921,8 @@
         Continue = yes
     ).
 
-:- pred do_module_qualify_mutable(item_mutable_info::in, item_mutable_info::out,
+:- pred do_module_qualify_mutable(
+    item_mutable_info::in, item_mutable_info::out,
     mq_info::in, mq_info::out, list(error_spec)::in, list(error_spec)::out)
     is det.
 
Index: compiler/modules.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modules.m,v
retrieving revision 1.474
diff -u -b -r1.474 modules.m
--- compiler/modules.m	8 Oct 2012 04:14:46 -0000	1.474
+++ compiler/modules.m	24 Oct 2012 05:48:13 -0000
@@ -2501,7 +2501,8 @@
     digraph(sym_name)::in, digraph(sym_name)::in,
     io::di, io::uo) is det.
 
-maybe_output_imports_graph(Globals, Module, IntDepsGraph, ImplDepsGraph, !IO) :-
+maybe_output_imports_graph(Globals, Module, IntDepsGraph, ImplDepsGraph,
+        !IO) :-
     globals.lookup_bool_option(Globals, imports_graph, ImportsGraph),
     globals.lookup_bool_option(Globals, verbose, Verbose),
     (
Index: compiler/par_loop_control.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/par_loop_control.m,v
retrieving revision 1.9
diff -u -b -r1.9 par_loop_control.m
--- compiler/par_loop_control.m	2 Jul 2012 01:16:36 -0000	1.9
+++ compiler/par_loop_control.m	24 Oct 2012 05:48:13 -0000
@@ -950,7 +950,8 @@
             FixupGoalInfoConjs =
                 [FixupGoalInfoLastConj | FixupGoalInfoEarlierConjs],
             goals_fixup_goal_info(FixupGoalInfoConjs, FixupGoalInfo),
-            goals_use_parent_stack(UseParentStackEarlierConjs, UseParentStack0),
+            goals_use_parent_stack(UseParentStackEarlierConjs,
+                UseParentStack0),
             combine_use_parent_stack(UseParentStackLastConj, UseParentStack0,
                 UseParentStack),
             Conjs = EarlierConjs ++ [LastConj],
Index: compiler/passes_aux.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/passes_aux.m,v
retrieving revision 1.107
diff -u -b -r1.107 passes_aux.m
--- compiler/passes_aux.m	22 Aug 2011 04:23:13 -0000	1.107
+++ compiler/passes_aux.m	24 Oct 2012 05:48:13 -0000
@@ -141,7 +141,8 @@
     module_info::in, module_info::out) is det.
 
 :- pred process_all_nonimported_procs_update(
-    update_proc_task::update_proc_task, update_proc_task::out(update_proc_task),
+    update_proc_task::update_proc_task,
+    update_proc_task::out(update_proc_task),
     module_info::in, module_info::out) is det.
 
 %-----------------------------------------------------------------------------%
Index: compiler/proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/proc_gen.m,v
retrieving revision 1.55
diff -u -b -r1.55 proc_gen.m
--- compiler/proc_gen.m	24 Oct 2012 04:59:52 -0000	1.55
+++ compiler/proc_gen.m	24 Oct 2012 05:48:13 -0000
@@ -1087,13 +1087,15 @@
                 get_next_label(SkipLabel, !CI),
                 get_next_label(SkipLabelCopy, !CI),
                 PruneTraceTicketCode = from_list([
-                    llds_instr(if_val(unop(logical_not, lval(FromFullSlotLval)),
+                    llds_instr(
+                        if_val(unop(logical_not, lval(FromFullSlotLval)),
                         code_label(SkipLabel)), ""),
                     llds_instr(prune_ticket, "prune retry ticket"),
                     llds_instr(label(SkipLabel), "")
                 ]),
                 PruneTraceTicketCodeCopy = from_list([
-                    llds_instr(if_val(unop(logical_not, lval(FromFullSlotLval)),
+                    llds_instr(
+                        if_val(unop(logical_not, lval(FromFullSlotLval)),
                         code_label(SkipLabelCopy)), ""),
                     llds_instr(prune_ticket, "prune retry ticket"),
                     llds_instr(label(SkipLabelCopy), "")
Index: compiler/prog_io_mode_defn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_io_mode_defn.m,v
retrieving revision 1.3
diff -u -b -r1.3 prog_io_mode_defn.m
--- compiler/prog_io_mode_defn.m	23 May 2011 05:08:10 -0000	1.3
+++ compiler/prog_io_mode_defn.m	24 Oct 2012 05:48:13 -0000
@@ -118,8 +118,8 @@
                         [always(Pieces)])]),
                 MaybeItem = error1([Spec])
             ;
-                % Check that the inst is a valid user-defined inst, i.e. that it
-                % does not have the form of one of the builtin insts.
+                % Check that the inst is a valid user-defined inst, i.e.
+                % that it does not have the form of one of the builtin insts.
                 \+ (
                     convert_inst(no_allow_constrained_inst_var, HeadTerm,
                         UserInst),
Index: compiler/prog_io_pragma.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_io_pragma.m,v
retrieving revision 1.154
diff -u -b -r1.154 prog_io_pragma.m
--- compiler/prog_io_pragma.m	8 Oct 2012 04:14:47 -0000	1.154
+++ compiler/prog_io_pragma.m	24 Oct 2012 05:48:13 -0000
@@ -2145,7 +2145,8 @@
 parse_box_policy(term.functor(term.atom("always_boxed"), [], _),
     always_boxed).
 
-:- pred parse_affects_liveness(term::in, proc_affects_liveness::out) is semidet.
+:- pred parse_affects_liveness(term::in, proc_affects_liveness::out)
+    is semidet.
 
 parse_affects_liveness(Term, AffectsLiveness) :-
     Term = term.functor(term.atom(Functor), [], _),
@@ -2159,7 +2160,8 @@
         AffectsLiveness = proc_does_not_affect_liveness
     ).
 
-:- pred parse_allocates_memory(term::in, proc_allocates_memory::out) is semidet.
+:- pred parse_allocates_memory(term::in, proc_allocates_memory::out)
+    is semidet.
 
 parse_allocates_memory(Term, AllocatesMemory) :-
     Term = term.functor(term.atom(Functor), [], _),
Index: compiler/prog_io_type_defn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_io_type_defn.m,v
retrieving revision 1.8
diff -u -b -r1.8 prog_io_type_defn.m
--- compiler/prog_io_type_defn.m	10 Sep 2012 13:33:08 -0000	1.8
+++ compiler/prog_io_type_defn.m	24 Oct 2012 05:48:13 -0000
@@ -609,10 +609,12 @@
                 MaybeDirectArgCtors),
             (
                 MaybeDirectArgCtors = yes(_),
-                Pieces = [words("Error: solver type definitions cannot have a"),
-                    quote("direct_arg"), words("attribute."), nl],
+                Pieces = [words("Error: solver type definitions"),
+                    words("cannot have a"), quote("direct_arg"),
+                    words("attribute."), nl],
                 Spec = error_spec(severity_error, phase_term_to_parse_tree,
-                    [simple_msg(get_term_context(HeadTerm), [always(Pieces)])]),
+                    [simple_msg(get_term_context(HeadTerm),
+                        [always(Pieces)])]),
                 MaybeItem = error1([Spec])
             ;
                 MaybeDirectArgCtors = no,
Index: compiler/prog_io_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_io_util.m,v
retrieving revision 1.76
diff -u -b -r1.76 prog_io_util.m
--- compiler/prog_io_util.m	10 Sep 2012 13:33:08 -0000	1.76
+++ compiler/prog_io_util.m	24 Oct 2012 05:48:13 -0000
@@ -480,8 +480,8 @@
     Context = term.context_init,
     Var = term.coerce_var(TVar),
     unparse_type_list(Args, ArgTerms),
-    Term = term.functor(term.atom(""), [term.variable(Var, Context) | ArgTerms],
-        Context).
+    Term = term.functor(term.atom(""),
+        [term.variable(Var, Context) | ArgTerms], Context).
 unparse_type(kinded_type(_, _), _) :-
     unexpected($module, $pred, "kind annotation").
 
Index: compiler/prog_mutable.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_mutable.m,v
retrieving revision 1.36
diff -u -b -r1.36 prog_mutable.m
--- compiler/prog_mutable.m	3 Nov 2011 01:01:36 -0000	1.36
+++ compiler/prog_mutable.m	24 Oct 2012 05:48:13 -0000
@@ -652,8 +652,9 @@
     Origin = compiler(mutable_decl),
     WithType = no,
     WithInst = no,
-    LockPredDecl = item_pred_decl_info(Origin, VarSet, InstVarSet, ExistQVars,
-        pf_predicate, mutable_lock_pred_sym_name(ModuleName, Name), [],
+    LockPredDecl = item_pred_decl_info(Origin, VarSet, InstVarSet,
+        ExistQVars, pf_predicate,
+        mutable_lock_pred_sym_name(ModuleName, Name), [],
         WithType, WithInst, yes(detism_det),
         cond_true, purity_impure, Constraints, Context, -1),
     LockPredDeclItem = item_pred_decl(LockPredDecl).
@@ -666,8 +667,9 @@
     Origin = compiler(mutable_decl),
     WithType = no,
     WithInst = no,
-    UnlockPredDecl = item_pred_decl_info(Origin, VarSet, InstVarSet, ExistQVars,
-        pf_predicate, mutable_unlock_pred_sym_name(ModuleName, Name), [],
+    UnlockPredDecl = item_pred_decl_info(Origin, VarSet, InstVarSet,
+        ExistQVars, pf_predicate,
+        mutable_unlock_pred_sym_name(ModuleName, Name), [],
         WithType, WithInst, yes(detism_det),
         cond_true, purity_impure, Constraints, Context, -1),
     UnlockPredDeclItem = item_pred_decl(UnlockPredDecl).
Index: compiler/prog_type_subst.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_type_subst.m,v
retrieving revision 1.11
diff -u -b -r1.11 prog_type_subst.m
--- compiler/prog_type_subst.m	2 Jul 2012 01:16:36 -0000	1.11
+++ compiler/prog_type_subst.m	24 Oct 2012 05:48:13 -0000
@@ -373,17 +373,27 @@
 :- pred apply_type_args_to_kind(kind::in, list(mer_type)::in, kind::out)
     is det.
 
-apply_type_args_to_kind(Kind, [], Kind).
-apply_type_args_to_kind(kind_star, [_ | _], _) :-
-    unexpected($module, $pred, "too many args in apply_n").
-apply_type_args_to_kind(kind_arrow(Kind0, Kind1), [ArgType | ArgTypes], Kind) :-
-    ( get_type_kind(ArgType) = Kind0 ->
-        apply_type_args_to_kind(Kind1, ArgTypes, Kind)
+apply_type_args_to_kind(Kind0, ArgTypes, Kind) :-
+    (
+        ArgTypes = [],
+        Kind = Kind0
+    ;
+        ArgTypes = [HeadArgType | TailArgTypes],
+        (
+            Kind0 = kind_star,
+            unexpected($module, $pred, "too many args in apply_n")
+        ;
+            Kind0 = kind_arrow(KindA, KindB),
+            ( get_type_kind(HeadArgType) = KindA ->
+                apply_type_args_to_kind(KindB, TailArgTypes, Kind)
     ;
         unexpected($module, $pred, "kind error in apply_n")
+            )
+        ;
+            Kind0 = kind_variable(_),
+            unexpected($module, $pred, "unbound kind variable")
+        )
     ).
-apply_type_args_to_kind(kind_variable(_), [_ | _], _) :-
-    unexpected($module, $pred, "unbound kind variable").
 
 :- pred ensure_type_has_kind(kind::in, mer_type::in, mer_type::out) is det.
 
Index: compiler/rbmm.region_arguments.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rbmm.region_arguments.m,v
retrieving revision 1.9
diff -u -b -r1.9 rbmm.region_arguments.m
--- compiler/rbmm.region_arguments.m	13 Feb 2012 00:11:47 -0000	1.9
+++ compiler/rbmm.region_arguments.m	24 Oct 2012 05:48:13 -0000
@@ -1,4 +1,4 @@
-% -----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % vim: ft=mercury ts=4 sw=4 et
 %-----------------------------------------------------------------------------%
 % Copyright (C) 2009-2012 The University of Melbourne.
Index: compiler/rtti.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rtti.m,v
retrieving revision 1.100
diff -u -b -r1.100 rtti.m
--- compiler/rtti.m	5 Jul 2011 03:34:33 -0000	1.100
+++ compiler/rtti.m	24 Oct 2012 05:48:13 -0000
@@ -188,7 +188,8 @@
                 foreign_enum_axioms        :: equality_axioms,
                 foreign_enum_functors      :: list(foreign_enum_functor),
                 foreign_enum_ordinal_table :: map(int, foreign_enum_functor),
-                foreign_enum_name_table    :: map(string, foreign_enum_functor),
+                foreign_enum_name_table    :: map(string,
+                                                foreign_enum_functor),
                 foreign_enum_functor_number_mapping
                                            :: list(int)
             )
@@ -855,8 +856,8 @@
 
     % Analogous to rtti_id_c_type.
     %
-:- pred rtti_id_maybe_element_csharp_type(rtti_id_maybe_element::in, string::out,
-    is_array::out) is det.
+:- pred rtti_id_maybe_element_csharp_type(rtti_id_maybe_element::in,
+    string::out, is_array::out) is det.
 :- pred rtti_id_csharp_type(rtti_id::in, string::out, is_array::out) is det.
 :- pred ctor_rtti_name_csharp_type(ctor_rtti_name::in, string::out,
     is_array::out) is det.
Index: compiler/rtti_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rtti_out.m,v
retrieving revision 1.90
diff -u -b -r1.90 rtti_out.m
--- compiler/rtti_out.m	6 Sep 2011 05:20:43 -0000	1.90
+++ compiler/rtti_out.m	24 Oct 2012 05:48:13 -0000
@@ -1208,7 +1208,8 @@
     map(string, enum_functor)::in, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
 
-output_enum_name_ordered_table(Info, RttiTypeCtor, FunctorMap, !DeclSet, !IO) :-
+output_enum_name_ordered_table(Info, RttiTypeCtor, FunctorMap,
+        !DeclSet, !IO) :-
     Functors = map.values(FunctorMap),
     FunctorRttiNames = list.map(enum_functor_rtti_name, Functors),
     output_generic_rtti_data_defn_start(Info,
@@ -1252,7 +1253,8 @@
     map(string, map(int, du_functor))::in, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
 
-output_du_name_ordered_table(Info, RttiTypeCtor, NameArityMap, !DeclSet, !IO) :-
+output_du_name_ordered_table(Info, RttiTypeCtor, NameArityMap,
+        !DeclSet, !IO) :-
     map.values(NameArityMap, ArityMaps),
     list.map(map.values, ArityMaps, FunctorLists),
     list.condense(FunctorLists, Functors),
Index: compiler/rtti_to_mlds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/rtti_to_mlds.m,v
retrieving revision 1.108
diff -u -b -r1.108 rtti_to_mlds.m
Index: compiler/ssdebug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ssdebug.m,v
retrieving revision 1.39
diff -u -b -r1.39 ssdebug.m
--- compiler/ssdebug.m	19 Jul 2012 11:44:13 -0000	1.39
+++ compiler/ssdebug.m	24 Oct 2012 05:48:13 -0000
@@ -251,7 +251,8 @@
             !ModuleInfo)
     ).
 
-:- pred module_info_ssdb_trace_level(module_info::in, ssdb_trace_level::out) is det.
+:- pred module_info_ssdb_trace_level(module_info::in, ssdb_trace_level::out)
+    is det.
 
 module_info_ssdb_trace_level(ModuleInfo, SSTraceLevel) :-
     module_info_get_globals(ModuleInfo, Globals),
Index: compiler/stack_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_alloc.m,v
retrieving revision 1.35
diff -u -b -r1.35 stack_alloc.m
--- compiler/stack_alloc.m	2 Jul 2012 01:16:37 -0000	1.35
+++ compiler/stack_alloc.m	24 Oct 2012 05:48:13 -0000
@@ -161,7 +161,8 @@
 
 alloc_at_call_site(NeedAtCall, AllocData, !StackAlloc) :-
     NeedAtCall = need_across_call(ForwardVars, ResumeVars, NondetLiveVars),
-    LiveSet0 = set_of_var.union_list([ForwardVars, ResumeVars, NondetLiveVars]),
+    LiveSet0 = set_of_var.union_list([ForwardVars, ResumeVars,
+        NondetLiveVars]),
     filter_out_dummy_vars(AllocData, LiveSet0, LiveSet),
 
     !.StackAlloc = stack_alloc(LiveSets0),
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.170
diff -u -b -r1.170 stack_layout.m
--- compiler/stack_layout.m	24 Oct 2012 04:59:52 -0000	1.170
+++ compiler/stack_layout.m	24 Oct 2012 05:48:13 -0000
@@ -997,7 +997,8 @@
             find_sequence(RevHeadVarNumVector, RevHeadVarNums0,
                 0, OldHeadVarNumOffset)
         ->
-            HeadVarNumSlot = NextHeadVarNum0 - OldHeadVarNumOffset - NumHeadVars
+            HeadVarNumSlot =
+                NextHeadVarNum0 - OldHeadVarNumOffset - NumHeadVars
         ;
             RevHeadVarNums = RevHeadVarNumVector ++ RevHeadVarNums0,
             !ExecTraceInfo ^ eti_rev_proc_head_var_nums := RevHeadVarNums,
Index: compiler/stack_opt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_opt.m,v
retrieving revision 1.59
diff -u -b -r1.59 stack_opt.m
--- compiler/stack_opt.m	2 Jul 2012 01:16:37 -0000	1.59
+++ compiler/stack_opt.m	24 Oct 2012 05:48:13 -0000
@@ -199,7 +199,8 @@
     globals.lookup_int_option(Globals, debug_stack_opt, DebugStackOpt),
     pred_id_to_int(PredId, PredIdInt),
     trace [io(!IO)] (
-        maybe_write_progress_message("\nbefore stack opt cell",
+        maybe_write_progress_message(
+            "\nbefore stack opt cell",
             DebugStackOpt, PredIdInt, !.ProcInfo, !.ModuleInfo, !IO)
     ),
     optimize_live_sets(!.ModuleInfo, OptStackAlloc, !ProcInfo,
@@ -207,18 +208,21 @@
     (
         Changed = yes,
         trace [io(!IO)] (
-            maybe_write_progress_message("\nafter stack opt transformation",
+            maybe_write_progress_message(
+                "\nafter stack opt transformation",
                 DebugStackOpt, PredIdInt, !.ProcInfo, !.ModuleInfo, !IO)
         ),
         requantify_proc_general(ordinary_nonlocals_no_lambda, !ProcInfo),
         trace [io(!IO)] (
-            maybe_write_progress_message("\nafter stack opt requantify",
+            maybe_write_progress_message(
+                "\nafter stack opt requantify",
                 DebugStackOpt, PredIdInt, !.ProcInfo, !.ModuleInfo, !IO)
         ),
         recompute_instmap_delta_proc(recompute_atomic_instmap_deltas,
             !ProcInfo, !ModuleInfo),
         trace [io(!IO)] (
-            maybe_write_progress_message("\nafter stack opt recompute instmaps",
+            maybe_write_progress_message("
+                \nafter stack opt recompute instmaps",
                 DebugStackOpt, PredIdInt, !.ProcInfo, !.ModuleInfo, !IO)
         )
     ;
Index: compiler/structure_reuse.analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.analysis.m,v
retrieving revision 1.33
diff -u -b -r1.33 structure_reuse.analysis.m
--- compiler/structure_reuse.analysis.m	5 Sep 2012 06:18:15 -0000	1.33
+++ compiler/structure_reuse.analysis.m	24 Oct 2012 05:48:13 -0000
@@ -227,8 +227,8 @@
         % Handle requests for "intermediate" reuse versions of procedures
         % and repeat the analyses.
         globals.lookup_int_option(Globals, structure_reuse_repeat, Repeats),
-        handle_structure_reuse_requests(Repeats, SharingTable, InternalRequests,
-            !ReuseTable, !ModuleInfo, DepProcs0, DepProcs,
+        handle_structure_reuse_requests(Repeats, SharingTable,
+            InternalRequests, !ReuseTable, !ModuleInfo, DepProcs0, DepProcs,
             IntermodRequests0, IntermodRequests),
 
         % Create reuse versions of procedures.  Update goals to reuse cells
Index: compiler/structure_reuse.indirect.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.indirect.m,v
retrieving revision 1.41
diff -u -b -r1.41 structure_reuse.indirect.m
--- compiler/structure_reuse.indirect.m	2 Jul 2012 01:16:37 -0000	1.41
+++ compiler/structure_reuse.indirect.m	24 Oct 2012 05:48:13 -0000
@@ -1,4 +1,4 @@
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % vim: ft=mercury ff=unix ts=4 sw=4 et
 %-----------------------------------------------------------------------------%
 % Copyright (C) 2006-2012 The University of Melbourne.
@@ -11,7 +11,7 @@
 %
 % Determine the indirect reuse.  This requires a fixpoint computation.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- module structure_reuse.indirect.
 :- interface.
@@ -23,7 +23,7 @@
 
 :- import_module set.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
     % Represents a request to perform analyses of a procedure with
     % restriction on which arguments may be clobbered.
@@ -64,8 +64,8 @@
     set(ppid_no_clobbers)::out, set(sr_request)::out,
     set(sr_request)::in, set(sr_request)::out) is det.
 
-%------------------------------------------------------------------------------%
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- implementation.
 
@@ -97,11 +97,11 @@
 :- import_module solutions.
 :- import_module string.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- type dep_procs == set(ppid_no_clobbers).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 indirect_reuse_pass(SharingTable, !ModuleInfo, !ReuseTable, DepProcs,
         Requests, IntermodRequests) :-
@@ -1196,7 +1196,8 @@
 sr_fixpoint_table_description(Table) = fixpoint_table.description(Table).
 
 sr_fixpoint_table_new_as(ModuleInfo, ProcInfo, Id, ReuseAs, !Table) :-
-    add_to_fixpoint_table(reuse_as_and_status_subsumed_by(ModuleInfo, ProcInfo),
+    add_to_fixpoint_table(
+        reuse_as_and_status_subsumed_by(ModuleInfo, ProcInfo),
         Id, ReuseAs, !Table).
 
 sr_fixpoint_table_get_as(PPId, ReuseAs, !Table) :-
@@ -1224,6 +1225,6 @@
 sr_fixpoint_table_get_final_as_semidet(PPId, T, Elem) :-
     get_from_fixpoint_table_final_semidet(PPId, T, Elem).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 :- end_module structure_reuse.indirect.
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: compiler/structure_reuse.versions.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.versions.m,v
retrieving revision 1.27
diff -u -b -r1.27 structure_reuse.versions.m
--- compiler/structure_reuse.versions.m	13 Feb 2012 00:11:49 -0000	1.27
+++ compiler/structure_reuse.versions.m	24 Oct 2012 05:48:13 -0000
@@ -1,6 +1,6 @@
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % vim: ft=mercury ff=unix ts=4 sw=4 et
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2006-2012 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 +12,7 @@
 % Provide the functionality to create optimised versions of those procedures
 % for which reuse was detected.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- module structure_reuse.versions.
 :- interface.
@@ -21,7 +21,7 @@
 :- import_module hlds.hlds_pred.
 :- import_module transform_hlds.ctgc.structure_reuse.domain.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 
     % For each of the entries in the reuse table:
@@ -54,8 +54,8 @@
 :- pred create_fake_reuse_procedure(pred_proc_id::in, no_clobber_args::in,
     module_info::in, module_info::out) is det.
 
-%------------------------------------------------------------------------------%
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- implementation.
 
@@ -80,7 +80,7 @@
 :- import_module require.
 :- import_module set.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- type reuse_name == sym_name.
 
@@ -96,7 +96,7 @@
     make_pred_name(PredModule, "ctgc", yes(PredOrFunc), PredName,
         newpred_structure_reuse(ProcInt, NoClobbers), ReuseName).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
     % This process can be split into separate steps:
     % - determine all the pred-proc-ids of procedure with conditional reuse;
@@ -181,7 +181,7 @@
         unexpected($module, $pred, "no reuse information")
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 create_fresh_pred_proc_info_copy(PPId, NoClobbers, NewPPId, !ModuleInfo) :-
     module_info_pred_proc_info(!.ModuleInfo, PPId, PredInfo0, ProcInfo0),
@@ -231,7 +231,7 @@
         ExistQTVars, ProgConstraints, AssertIds, VarNameRemap,
         ProcInfo, ReuseProcId, ReusePredInfo).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- type convert_potential_reuse
     --->    convert_potential_reuse
@@ -495,7 +495,7 @@
     process_goal(ConvertPotentialReuse, ReuseMap, ModuleInfo, Goal0, Goal),
     Case = case(MainConsId, OtherConsIds, Goal).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 create_fake_reuse_procedure(PPId, NoClobbers, !ModuleInfo) :-
     PPId = proc(PredId, ProcId),
@@ -520,6 +520,6 @@
             !ModuleInfo)
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 :- end_module structure_reuse.versions.
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: compiler/structure_sharing.domain.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_sharing.domain.m,v
retrieving revision 1.48
diff -u -b -r1.48 structure_sharing.domain.m
--- compiler/structure_sharing.domain.m	2 Jul 2012 01:16:38 -0000	1.48
+++ compiler/structure_sharing.domain.m	24 Oct 2012 05:48:13 -0000
@@ -411,7 +411,8 @@
         CallerTypeVarSet, CallerHeadTypeParams),
     sharing_as_rename(VarRenaming, TypeSubst, FormalSharing, ActualSharing).
 
-sharing_as_comb(ModuleInfo, ProcInfo, NewSharing, OldSharing) = ResultSharing :-
+sharing_as_comb(ModuleInfo, ProcInfo, NewSharing, OldSharing) =
+        ResultSharing :-
     (
         NewSharing = sharing_as_real_as(NewSharingSet),
         (
@@ -559,8 +560,8 @@
         true
     ).
 
-    % When two positions within the constructed term refer to the same variable,
-    % this must be recorded as an extra sharing pair.
+    % When two positions within the constructed term refer to the same
+    % variable, this must be recorded as an extra sharing pair.
     % E.g.: X = f(Y,Y), then the sharing between f/1 and f/2 must be recorded.
     % XXX Different implementation!
     %
Index: compiler/tabling_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tabling_analysis.m,v
retrieving revision 1.27
diff -u -b -r1.27 tabling_analysis.m
--- compiler/tabling_analysis.m	5 Sep 2012 06:18:15 -0000	1.27
+++ compiler/tabling_analysis.m	24 Oct 2012 05:48:13 -0000
@@ -915,7 +915,8 @@
 
 analysis_name = "mm_tabling_analysis".
 
-:- instance analysis(no_func_info, any_call, mm_tabling_analysis_answer) where [
+:- instance analysis(no_func_info, any_call, mm_tabling_analysis_answer) where
+[
     analysis_name(_, _) = analysis_name,
     analysis_version_number(_, _) = 1,
     preferred_fixpoint_type(_, _) = least_fixpoint,
Index: compiler/term_constr_build.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_build.m,v
retrieving revision 1.37
diff -u -b -r1.37 term_constr_build.m
--- compiler/term_constr_build.m	2 Jul 2012 01:16:38 -0000	1.37
+++ compiler/term_constr_build.m	24 Oct 2012 05:48:13 -0000
@@ -1,10 +1,10 @@
 %-----------------------------------------------------------------------------%
 % vim: ft=mercury ts=4 sw=4 et
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2003, 2005-2012 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: term_constr_build.m.
 % Main author: juliensf.
@@ -17,7 +17,7 @@
 % TODO:
 % Make the abstract representations more independent of the HLDS.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- module transform_hlds.term_constr_build.
 :- interface.
@@ -31,7 +31,7 @@
 :- import_module io.
 :- import_module list.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
     % This structure holds the values of options used to control the build
     % pass.
@@ -55,8 +55,8 @@
     list(pred_proc_id)::in, term_build_options::in, term2_errors::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
-%------------------------------------------------------------------------------%
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- implementation.
 
@@ -253,7 +253,7 @@
         io.nl(!DebugIO)
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for traversing HLDS goals and collecting constraints from them.
 %
@@ -366,7 +366,7 @@
 set_intermod_status(Status, !TraversalInfo) :-
     !TraversalInfo ^ tti_intermod_status := Status.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for abstracting goals.
 %
@@ -389,7 +389,8 @@
         Locals, NonLocals).
 
 :- pred build_abstract_goal_2(hlds_goal_expr::in, hlds_goal_info::in,
-    abstract_goal::out, tti_traversal_info::in, tti_traversal_info::out) is det.
+    abstract_goal::out, tti_traversal_info::in, tti_traversal_info::out)
+    is det.
 
 build_abstract_goal_2(GoalExpr, GoalInfo, AbstractGoal, !Info) :-
     (
@@ -493,7 +494,7 @@
         unexpected($module, $pred, "shorthand")
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Additional predicates for abstracting (parallel) conjunctions.
 %
@@ -506,7 +507,7 @@
     AbstractGoals = simplify_conjuncts(AbstractGoals0),
     AbstractGoal = term_conj(AbstractGoals, [], []).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Additional predicates for abstracting calls.
 %
@@ -612,7 +613,7 @@
     Polyhedron = polyhedron.from_constraints(Constraints),
     AbstractGoal = term_primitive(Polyhedron, [], []).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Additional predicates for abstracting switches and disjunctions.
 %
@@ -749,7 +750,7 @@
 detect_switch_var(hlds_goal(shorthand(_), _), _, _) :-
     unexpected($module, $pred, "shorthand").
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Additional predicates for abstracting from_ground_term scopes,
 % which act like giant construction unifications.
@@ -833,7 +834,7 @@
     !:TotalSize = !.TotalSize + Size,
     accumulate_sum(Sizes, !TotalSize).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Additional predicates for abstracting unifications.
 %
@@ -1017,7 +1018,7 @@
         true
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
     % Because quantification returns a conservative estimate of nonlocal
     % vars, this returns a list of local vars that may omit some of the
Index: compiler/term_constr_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_data.m,v
retrieving revision 1.14
diff -u -b -r1.14 term_constr_data.m
--- compiler/term_constr_data.m	23 May 2011 05:08:13 -0000	1.14
+++ compiler/term_constr_data.m	24 Oct 2012 05:48:13 -0000
@@ -16,7 +16,7 @@
 % which is an abstraction of a Mercury program in terms of linear arithmetic
 % constraints on term sizes.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % AR Goals.
 %
@@ -37,7 +37,7 @@
 % XXX In order to handle higher-order we need to either modify the
 % exiting AR call goal or add a new AR goal type.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Mapping the HLDS to the AR
 %
Index: compiler/term_constr_fixpoint.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_fixpoint.m,v
retrieving revision 1.12
diff -u -b -r1.12 term_constr_fixpoint.m
--- compiler/term_constr_fixpoint.m	23 May 2011 05:08:13 -0000	1.12
+++ compiler/term_constr_fixpoint.m	24 Oct 2012 05:48:13 -0000
@@ -354,7 +354,7 @@
         post_process_abstract_goal(Locals, Info, Poly, !Polyhedron)
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- pred post_process_abstract_goal(size_vars::in, fixpoint_info::in,
     polyhedron::in, polyhedron::in, polyhedron::out) is det.
@@ -368,7 +368,7 @@
     ),
     polyhedron.intersection(GoalPolyhedron, !Polyhedron).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for handling disjunctions.
 %
@@ -445,7 +445,7 @@
     !:Acc = [Op(X, Y) | !.Acc],
     pairwise_map_2(Op, Rest, !Acc).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Fixpoint test.
 %
Index: compiler/term_constr_main.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_main.m,v
retrieving revision 1.24
diff -u -b -r1.24 term_constr_main.m
--- compiler/term_constr_main.m	23 May 2011 05:08:13 -0000	1.24
+++ compiler/term_constr_main.m	24 Oct 2012 05:48:13 -0000
@@ -196,8 +196,8 @@
     maybe(constr_arg_size_info)::in, maybe(constr_arg_size_info)::in,
     maybe(constr_termination_info)::in, size_vars::in, io::di, io::uo) is det.
 
-%------------------------------------------------------------------------------%
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- implementation.
 
@@ -229,7 +229,7 @@
 :- import_module term.
 :- import_module varset.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % The 'termination2_info' structure
 %
@@ -431,7 +431,7 @@
         ArgSizeOnly = yes
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Procedures for storing 'termination2_info' in the HLDS.
 %
@@ -474,7 +474,8 @@
         MakeOptInt = no
     ).
 
-:- pred make_opt_int(list(pred_id)::in, module_info::in, io::di, io::uo) is det.
+:- pred make_opt_int(list(pred_id)::in, module_info::in, io::di, io::uo)
+    is det.
 
 make_opt_int(PredIds, ModuleInfo, !IO) :-
     module_info_get_globals(ModuleInfo, Globals),
@@ -669,6 +670,6 @@
         TermInfo ^ term_status = no
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 :- end_module transform_hlds.term_constr_main.
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: compiler/term_constr_pass2.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_pass2.m,v
retrieving revision 1.15
diff -u -b -r1.15 term_constr_pass2.m
--- compiler/term_constr_pass2.m	23 May 2011 05:08:13 -0000	1.15
+++ compiler/term_constr_pass2.m	24 Oct 2012 05:48:13 -0000
@@ -372,7 +372,8 @@
     % Builds a map from `pred_proc_id' to a list of the edges that begin
     % with the `pred_proc_id.
     %
-:- func partition_edges(list(abstract_ppid), edges) = map(abstract_ppid, edges).
+:- func partition_edges(list(abstract_ppid), edges)
+    = map(abstract_ppid, edges).
 
 partition_edges([], _) = map.init.
 partition_edges([ProcId | SCC], Edges0) = Map :-
Index: compiler/term_constr_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_constr_util.m,v
retrieving revision 1.24
diff -u -b -r1.24 term_constr_util.m
--- compiler/term_constr_util.m	2 Jul 2012 01:16:38 -0000	1.24
+++ compiler/term_constr_util.m	24 Oct 2012 05:48:13 -0000
@@ -1,17 +1,17 @@
 %-----------------------------------------------------------------------------%
 % vim: ft=mercury ts=4 sw=4 et
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 % Copyright (C) 1997-2003, 2005-2012 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: term_constr_util.m.
 % Main author: juliensf.
 %
 % This module defines some utility predicates used by the termination analyser.
 %
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- module transform_hlds.term_constr_util.
 :- interface.
@@ -30,7 +30,7 @@
 :- import_module map.
 :- import_module maybe.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for storing things in the HLDS.
 %
@@ -50,7 +50,7 @@
 
 :- func get_abstract_proc(module_info, pred_proc_id) = abstract_proc.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for size_vars.
 %
@@ -115,7 +115,7 @@
     maybe(pragma_termination_info)::in, prog_context::in,
     maybe(constr_termination_info)::out) is det.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
     % substitute_size_vars: Takes a list of constraints and a
     % var_substitution.  Returns the constraints with the specified
@@ -124,7 +124,7 @@
 :- func substitute_size_vars(constraints, map(size_var, size_var))
     = constraints.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for printing out debugging traces. The first boolean argument
 % of these predicates should be the value of the --debug-term option.
@@ -153,7 +153,7 @@
 
 :- pred dump_size_vars(size_vars::in, size_varset::in, io::di, io::uo) is det.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- pred update_arg_size_info(pred_proc_id::in, polyhedron::in, module_info::in,
     module_info::out) is det.
@@ -183,8 +183,8 @@
 :- pred change_procs_constr_arg_size_info(list(proc_id)::in, bool::in,
     constr_arg_size_info::in, proc_table::in, proc_table::out) is det.
 
-%------------------------------------------------------------------------------%
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 :- implementation.
 
@@ -205,7 +205,7 @@
 :- import_module term.
 :- import_module varset.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 set_pred_proc_ids_constr_arg_size_info([], _ArgSize, !ModuleInfo).
 set_pred_proc_ids_constr_arg_size_info([PPId | PPIds], ArgSize, !ModuleInfo) :-
@@ -229,7 +229,7 @@
     proc_info_get_termination2_info(ProcInfo, TermInfo),
     MaybeArgSizeInfo = TermInfo ^ success_constrs.
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 make_size_var_map(ProgVars, SizeVarset, SizeVarMap) :-
     make_size_var_map(ProgVars, varset.init, SizeVarset, SizeVarMap).
@@ -283,7 +283,7 @@
 add_context_to_constr_termination_info(yes(can_loop(_)), Context,
         yes(can_loop([Context - imported_pred]))).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 substitute_size_vars(Constraints0, SubstMap) = Constraints :-
     SubVarInCoeff = (func(OldVar - Rat) = NewVar - Rat :-
@@ -296,7 +296,7 @@
     ),
     Constraints = list.map(SubVarInEqn, Constraints0).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Utility procedures used by various parts of the IR analysis.
 %
@@ -339,7 +339,7 @@
 
 is_zero_size_var(Zeros, SizeVar) :- set.member(SizeVar, Zeros).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 %
 % Predicates for printing out debugging traces ...
 %
@@ -390,7 +390,7 @@
     io.write_list(Vars, ", ", WriteSizeVar, !IO),
     io.write_char(']', !IO).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 dump_size_vars(Vars, Varset, !IO) :-
     dump_size_varset_2(Vars, Varset, !IO).
@@ -409,12 +409,12 @@
     io.format(" = %s\n", [s(Name)], !IO),
     dump_size_varset_2(Vars, Varset, !IO).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 update_arg_size_info(PPID, Polyhedron, !ModuleInfo) :-
     set_pred_proc_ids_constr_arg_size_info([PPID], Polyhedron, !ModuleInfo).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 change_procs_constr_termination_info([], _, _, !ProcTable).
 change_procs_constr_termination_info([ProcId | ProcIds], Override, Termination,
@@ -453,7 +453,7 @@
     ),
     change_procs_constr_arg_size_info(ProcIds, Override, ArgSize, !ProcTable).
 
-%----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 get_abstract_scc(ModuleInfo, SCC) =
     list.map(get_abstract_proc(ModuleInfo), SCC).
@@ -469,6 +469,6 @@
         unexpected($module, $pred, "no abstract rep. for proc")
     ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 :- end_module transform_hlds.term_constr_util.
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: compiler/term_pass2.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_pass2.m,v
retrieving revision 1.38
diff -u -b -r1.38 term_pass2.m
--- compiler/term_pass2.m	23 May 2011 05:08:14 -0000	1.38
+++ compiler/term_pass2.m	24 Oct 2012 05:48:13 -0000
@@ -82,7 +82,7 @@
                 termination_error_contexts
             ).
 
-%------------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
 
 prove_termination_in_scc(SCC, PassInfo, SingleArgs, Termination,
         !ModuleInfo, !IO) :-
@@ -542,7 +542,8 @@
     list(termination_error_context)::out) is det.
 
 zero_or_positive_weight_cycles_2([], _, _, []).
-zero_or_positive_weight_cycles_2([PPId | PPIds], CallWeights, Module, Cycles) :-
+zero_or_positive_weight_cycles_2([PPId | PPIds], CallWeights, Module,
+        Cycles) :-
     zero_or_positive_weight_cycles_from(PPId, CallWeights, Module, Cycles1),
     zero_or_positive_weight_cycles_2(PPIds, CallWeights, Module, Cycles2),
     list.append(Cycles1, Cycles2, Cycles).
Index: compiler/term_traversal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_traversal.m,v
retrieving revision 1.70
diff -u -b -r1.70 term_traversal.m
--- compiler/term_traversal.m	2 Jul 2012 01:16:38 -0000	1.70
+++ compiler/term_traversal.m	24 Oct 2012 05:48:13 -0000
@@ -178,7 +178,8 @@
         proc_info_get_argmodes(CallProcInfo, CallArgModes),
         % XXX intermod
         proc_info_get_maybe_arg_size_info(CallProcInfo, CallArgSizeInfo),
-        proc_info_get_maybe_termination_info(CallProcInfo, CallTerminationInfo),
+        proc_info_get_maybe_termination_info(CallProcInfo,
+            CallTerminationInfo),
 
         partition_call_args(!.ModuleInfo, CallArgModes, Args, InVars, OutVars),
 
Index: compiler/try_expand.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/try_expand.m,v
retrieving revision 1.24
diff -u -b -r1.24 try_expand.m
--- compiler/try_expand.m	2 Jul 2012 01:16:38 -0000	1.24
+++ compiler/try_expand.m	24 Oct 2012 05:48:13 -0000
@@ -587,7 +587,8 @@
             umc_implicit("try_expand"), [], UnifyThenInitialIOVar),
         conjoin_goals(UnifyThenInitialIOVar, Then1, Then),
 
-        RenamingExcp = map.from_assoc_list([GoalInitialIOVar - TryIOOutputVar]),
+        RenamingExcp =
+            map.from_assoc_list([GoalInitialIOVar - TryIOOutputVar]),
         rename_some_vars_in_goal(RenamingExcp, ExcpHandling1, ExcpHandling)
     ;
         MaybeIO = no,
Index: compiler/tupling.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tupling.m,v
retrieving revision 1.70
diff -u -b -r1.70 tupling.m
--- compiler/tupling.m	2 Jul 2012 01:16:39 -0000	1.70
+++ compiler/tupling.m	24 Oct 2012 05:48:13 -0000
@@ -1593,9 +1593,9 @@
     map.foldl(build_insert_map_2(CellVar, FieldVars, FieldVarsSet),
         IntervalInfo ^ ii_anchor_follow_map, map.init, InsertMap).
 
-:- pred build_insert_map_2(prog_var::in, list(prog_var)::in, set_of_progvar::in,
-    anchor::in, anchor_follow_info::in, insert_map::in, insert_map::out)
-    is det.
+:- pred build_insert_map_2(prog_var::in, list(prog_var)::in,
+    set_of_progvar::in, anchor::in, anchor_follow_info::in,
+    insert_map::in, insert_map::out) is det.
 
 build_insert_map_2(CellVar, FieldVars, FieldVarsSet, Anchor,
         anchor_follow_info(FollowVars, _), !InsertMap) :-
Index: compiler/type_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/type_util.m,v
retrieving revision 1.218
diff -u -b -r1.218 type_util.m
--- compiler/type_util.m	2 Jul 2012 01:16:39 -0000	1.218
+++ compiler/type_util.m	24 Oct 2012 05:48:13 -0000
@@ -687,7 +687,8 @@
             ( search_type_ctor_defn(TypeTable, TypeCtor, TypeDefn)->
                 get_type_defn_body(TypeDefn, TypeBody),
                 (
-                    TypeBody = hlds_du_type(_, _, _, DuTypeKind, _, _, _, _, _),
+                    TypeBody = hlds_du_type(_, _, _, DuTypeKind,
+                        _, _, _, _, _),
                     (
                         DuTypeKind = du_type_kind_direct_dummy,
                         IsDummy = is_dummy_type
Index: compiler/unify_proc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/unify_proc.m,v
retrieving revision 1.224
diff -u -b -r1.224 unify_proc.m
--- compiler/unify_proc.m	2 Jul 2012 01:16:39 -0000	1.224
+++ compiler/unify_proc.m	24 Oct 2012 05:48:13 -0000
@@ -791,7 +791,8 @@
 
             create_pure_atomic_complicated_unification(ResultVar,
                 compare_functor("="), Context, umc_explicit, [], UnifyGoal),
-            Goal0 = hlds_goal(conj(plain_conj, [CallGoal, UnifyGoal]), GoalInfo)
+            Goal0 = hlds_goal(conj(plain_conj, [CallGoal, UnifyGoal]),
+                GoalInfo)
         ;
             MaybeCompare = no,
             unexpected($module, $pred, "MaybeCompare = no")
Index: compiler/write_deps_file.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/write_deps_file.m,v
retrieving revision 1.15
diff -u -b -r1.15 write_deps_file.m
--- compiler/write_deps_file.m	8 Oct 2011 08:16:57 -0000	1.15
+++ compiler/write_deps_file.m	24 Oct 2012 05:48:13 -0000
@@ -1837,7 +1837,8 @@
             "$(", MakeVarName, ".os) ", InitObjFileName, " ",
             All_MLObjsString, " ", All_MLLibsDepString, "\n",
         "\t$(ML) $(ALL_GRADEFLAGS) $(ALL_MLFLAGS) -- $(ALL_LDFLAGS) ",
-            "$(EXEFILE_OPT)", ExeFileName, "$(EXT_FOR_EXE) ", InitObjFileName, " \\\n",
+            "$(EXEFILE_OPT)", ExeFileName, "$(EXT_FOR_EXE) ",
+            InitObjFileName, " \\\n",
         "\t\t$(", MakeVarName, ".os) ", All_MLObjsString, " $(ALL_MLLIBS)\n"],
 
     globals.get_target(Globals, Target),
Index: compiler/x86_64_instrs.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/x86_64_instrs.m,v
retrieving revision 1.3
diff -u -b -r1.3 x86_64_instrs.m
--- compiler/x86_64_instrs.m	27 Feb 2007 20:36:28 -0000	1.3
+++ compiler/x86_64_instrs.m	24 Oct 2012 05:48:13 -0000
@@ -214,8 +214,8 @@
     ;       byte(
                 byte_exprs          :: list(string) 
             )
-            % 'byte_exprs' contains zero or more expressions. Each expression is
-            % assembled into the next byte.
+            % 'byte_exprs' contains zero or more expressions.
+            % Each expression is assembled into the next byte.
 
     ;       comm(
                 comm_symbol         :: string,
@@ -336,8 +336,8 @@
     ;       global(
                 global_symbol       :: string
             )
-            % makes the global_symbol' visible to other programs that are linked
-            % with it.
+            % makes the global_symbol' visible to other programs
+            % that are linked with it.
 
     ;       globl(
                 globl_symbol        :: string
@@ -538,8 +538,8 @@
     ;       rept(
                 rept_count          :: int
             )
-            % Repeat the sequence of lines between the '.rept' directive and the
-            % next '.endr' directive 'rept_count' times.
+            % Repeat the sequence of lines between the '.rept' directive
+            % and the next '.endr' directive 'rept_count' times.
 
     ;       sbttl(
                 sbttl_subheading   :: string
@@ -591,8 +591,8 @@
     ;       sleb128(
                 sleb128_exprs       :: list(string)
             )
-            % Stand for "signed little endian base 128". It is a variable length
-            % representation of numbers used by the DWARF symbolic.
+            % Stand for "signed little endian base 128". It is a variable
+            % length representation of numbers used by the DWARF symbolic.
 
     ;       space(
                 space_size          :: int,
@@ -638,7 +638,8 @@
     ;       title(
                 title_heading       :: string
             )
-            % Use 'title_heading' as the title when generating assembly listing.
+            % Use 'title_heading' as the title when generating
+            % the assembly listing.
 
     ;       x86_64_pseudo_type(
                 type_name           :: string,
@@ -1009,7 +1010,8 @@
 
     ;       imul(
                 imul_src            :: operand,
-                                    % register, memory location, immediate value
+                                    % register, memory location,
+                                    % immediate value
                 imul_dest           :: maybe(operand),
                                     % register
                 imul_multiplicand   :: maybe(operand)
@@ -1095,8 +1097,8 @@
                 mov_dest         :: operand
                                  % register or memory location
             )
-            % Copies 'mov_src' to 'mov_dest'. 'mov_dest' cannot be immediate op.
-            % Details on amd64-prog-man-vol3 manual p173.
+            % Copies 'mov_src' to 'mov_dest'. 'mov_dest' cannot be
+            % immediate op. Details on amd64-prog-man-vol3 manual p173.
 
     ;       mul(
                 mul_op          :: operand
@@ -1145,7 +1147,8 @@
 
     ;       push(
                 push_op           :: operand
-                                  % register, memory location or immediate value
+                                  % register, memory location
+                                  % or immediate value
             )
             % Pushes the content of operand onto the stack. 
             % Details on amd64-prog-man-vol3 manual p215.
@@ -1240,8 +1243,8 @@
                 shld_dest2          :: operand  
                                     % register
             )
-            % Shift 'shld_dest1' to the left by 'shld_amount' and shift in a bit
-            % pattern in 'shld_dest2' from the right. 
+            % Shift 'shld_dest1' to the left by 'shld_amount' and shift in
+            % a bit pattern in 'shld_dest2' from the right.
             % Details on amd64-prog-man-vol3 manual p251.
 
     ;       shr(
Index: compiler/xml_documentation.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/xml_documentation.m,v
retrieving revision 1.35
diff -u -b -r1.35 xml_documentation.m
--- compiler/xml_documentation.m	2 Jul 2012 01:18:55 -0000	1.35
+++ compiler/xml_documentation.m	24 Oct 2012 05:48:13 -0000
@@ -582,7 +582,8 @@
         Xml = elem("inst_to_inst", [], [XmlFrom, XmlTo])
     ;
         Mode = user_defined_mode(Name, Args),
-        Ref = attr("ref", sym_name_and_arity_to_id("mode", Name, length(Args))),
+        Ref = attr("ref",
+            sym_name_and_arity_to_id("mode", Name, length(Args))),
         XmlArgs = xml_list("mode_args", mer_inst_to_xml(InstVarSet), Args),
         Xml = elem("user_defined_mode", [Ref], [name_to_xml(Name), XmlArgs])
     ).
cvs diff: Diffing compiler/notes
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/base64
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/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/fixed
cvs diff: Diffing extras/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_allegro
cvs diff: Diffing extras/graphics/mercury_allegro/examples
cvs diff: Diffing extras/graphics/mercury_allegro/samples
cvs diff: Diffing extras/graphics/mercury_allegro/samples/demo
cvs diff: Diffing extras/graphics/mercury_allegro/samples/mandel
cvs diff: Diffing extras/graphics/mercury_allegro/samples/pendulum2
cvs diff: Diffing extras/graphics/mercury_allegro/samples/speed
cvs diff: Diffing extras/graphics/mercury_cairo
cvs diff: Diffing extras/graphics/mercury_cairo/samples
cvs diff: Diffing extras/graphics/mercury_cairo/samples/data
cvs diff: Diffing extras/graphics/mercury_cairo/tutorial
cvs diff: Diffing extras/graphics/mercury_glfw
cvs diff: Diffing extras/graphics/mercury_glfw/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/log4m
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/monte
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/mopenssl
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/net
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/posix/samples
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/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
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 m4
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 runtime/notes
cvs diff: Diffing samples
cvs diff: Diffing samples/appengine
cvs diff: Diffing samples/appengine/war
cvs diff: Diffing samples/appengine/war/WEB-INF
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/c_interface/standalone_c
cvs diff: Diffing samples/concurrency
cvs diff: Diffing samples/concurrency/dining_philosophers
cvs diff: Diffing samples/concurrency/midimon
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/java_interface
cvs diff: Diffing samples/java_interface/java_calls_mercury
cvs diff: Diffing samples/java_interface/mercury_calls_java
cvs diff: Diffing samples/lazy_list
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/solver_types
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 ssdb
cvs diff: Diffing tests
cvs diff: Diffing tests/analysis
cvs diff: Diffing tests/analysis/ctgc
cvs diff: Diffing tests/analysis/excp
cvs diff: Diffing tests/analysis/ext
cvs diff: Diffing tests/analysis/sharing
cvs diff: Diffing tests/analysis/table
cvs diff: Diffing tests/analysis/trail
cvs diff: Diffing tests/analysis/unused_args
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/feedback
cvs diff: Diffing tests/feedback/mandelbrot
cvs diff: Diffing tests/feedback/mmc
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/par_conj
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/stm
cvs diff: Diffing tests/stm/orig
cvs diff: Diffing tests/stm/orig/stm-compiler
cvs diff: Diffing tests/stm/orig/stm-compiler/test1
cvs diff: Diffing tests/stm/orig/stm-compiler/test10
cvs diff: Diffing tests/stm/orig/stm-compiler/test2
cvs diff: Diffing tests/stm/orig/stm-compiler/test3
cvs diff: Diffing tests/stm/orig/stm-compiler/test4
cvs diff: Diffing tests/stm/orig/stm-compiler/test5
cvs diff: Diffing tests/stm/orig/stm-compiler/test6
cvs diff: Diffing tests/stm/orig/stm-compiler/test7
cvs diff: Diffing tests/stm/orig/stm-compiler/test8
cvs diff: Diffing tests/stm/orig/stm-compiler/test9
cvs diff: Diffing tests/stm/orig/stm-compiler-par
cvs diff: Diffing tests/stm/orig/stm-compiler-par/bm1
cvs diff: Diffing tests/stm/orig/stm-compiler-par/bm2
cvs diff: Diffing tests/stm/orig/stm-compiler-par/stmqueue
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test1
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test10
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test11
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test2
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test3
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test4
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test5
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test6
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test7
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test8
cvs diff: Diffing tests/stm/orig/stm-compiler-par/test9
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test1
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test2
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test3
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test4
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test5
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test6
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test7
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test8
cvs diff: Diffing tests/stm/orig/stm-compiler-par-asm_fast/test9
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/trailing
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 messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list