[m-rev.] for review: checking calls to string.format and io.format

Zoltan Somogyi zs at cs.mu.OZ.AU
Wed Jan 25 16:30:09 AEDT 2006


For review by anyone. The new facility will be initially unused until
after it has been installed on all our machines.

Zoltan.

Give the compiler the capability of detecting errors that manifest themselves
as mismatches between the format string and the list of values to be printed
in calls to string.format and io.format.

This capability is controlled through two new options:

	--warn-known-bad-format-call
	--warn-unknown-format-call

The first (which will default to "on" once this change has bootstrapped)
controls whether the compiler emits warnings for statically known mismatches.
The second (which will default to "off") controls whether the compiler emits
warnings in cases where either the format string or the structure of the list
of values to be printed is not available statically to be checked.

NEWS:
	Mention the new capability.

compiler/options.m:
	Add the two new options.

doc/user_guide.texi:
	Document the new options.

compiler/format_call.m:
	New module to implement the new capability.

compiler/notes/compiler_structure.html:
	Document the new module.

compiler/check_hlds.m:
	Include the new module.

compiler/simplify.m:
	Invoke the new module if the procedure being processed contains calls
	to string.format or io.format.

	Fix an old bug: we could generate warnings or even errors when
	simplifying predicate bodies imported from other modules via
	intermodule optimization.

	Don't export get/set predicates that do not need to be exported.

compiler/det_report.m:
	Add new kinds of error specifications for the errors detected by the
	new module.

	Separate out the context of each error specification, in order
	to allow the error messages to be sorted by context; this makes
	the output much easier to read.

compiler/common.m:
compiler/det_analysis.m:
compiler/simplify.m:
	Conform to the change to det_report.m.

mdbcomp/prim_data.m:
	Add a utility function for forming the possibly qualified names of
	library modules (such as "io" and "string").

library/Mercury.options:
compiler/Mercury.options:
	Add the lines that disable the new checks in the modules that need them
	disabled. The new lines are commented out until installed compilers all
	understand them, at which point in time we will add the requirement to
	understand the option to configure.in.

compiler/fact_table.m:
compiler/mlds_to_il.m:
	Fix three bugs reported by the new check that have apparently escaped
	detection all this time.

library/rtti_implementation.m:
	Change some code to avoid a spurious warning from the new checks.

library/string.m:
	Rename a predicate to avoid an unnecessary and confusing overloading of 
	its name.

	Replace __ with . as module qualifier connective.

compiler/handle_options.m:
library/pprint.m:
	Misc cleanups.

tests/invalid/string_format_bad.{m,err_exp}:
tests/invalid/string_format_unknown.{m,err_exp}:
	New test cases to test the new warnings.

tests/invalid/Mmakefile:
tests/invalid/Mercury.options:
	Enable the new test cases.

cvs diff: Diffing .
Index: NEWS
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/NEWS,v
retrieving revision 1.397
diff -u -b -r1.397 NEWS
--- NEWS	25 Jan 2006 03:20:58 -0000	1.397
+++ NEWS	25 Jan 2006 03:40:51 -0000
@@ -26,6 +26,9 @@
 * We have added an `injection' module, for reversible maps that are injective.
 
 Changes to the Mercury compiler:
+* The compiler now generates error messages for mismatches between format
+  strings and lists of values to be printed in calls to string.format and
+  io.format.
 * The compiler now generates better error messages for determinism errors
   involving single-solution contexts.
 * We have significantly improved the compiler's performance on predicates
@@ -186,6 +189,17 @@
 
 * We have added string.word_wrap/2.
 
+Changes to the Mercury compiler:
+
+* The compiler now generates error messages for known mismatches between format
+  strings and lists of values to be printed in calls to string.format and
+  io.format, unless the user specifies the --no-warn-known-bad-format-call
+  option.
+
+  If the user specifies the --warn-unknown-format-call option, the compiler
+  will also generate error messages for calls to string.format and io.format
+  in which the format string or the structure of the list of values to be
+  printed are not statically available.
 
 Changes to the extras distribution:
 
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/Mercury.options,v
retrieving revision 1.19
diff -u -b -r1.19 Mercury.options
--- compiler/Mercury.options	11 Jan 2006 05:59:22 -0000	1.19
+++ compiler/Mercury.options	25 Jan 2006 03:48:41 -0000
@@ -42,6 +42,10 @@
 MCFLAGS-mode_robdd.tfeirn = -O3
 MCFLAGS-mode_robdd.implications = -O0
 
+# rl_info.m contains a general purpose wrapper around string.format
+# that needs this option.
+# MCFLAGS-aditi_backend.rl_info = --no-warn-unknown-format-calls
+
 # The c_code in the module gcc.m needs the header files from the GNU C
 # distribution.  Note that we need to compile these with
 # -DMR_NO_BACKWARDS_COMPAT, because otherwise there are name
Index: compiler/check_hlds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/check_hlds.m,v
retrieving revision 1.10
diff -u -b -r1.10 check_hlds.m
--- compiler/check_hlds.m	12 Oct 2005 23:51:34 -0000	1.10
+++ compiler/check_hlds.m	23 Jan 2006 02:06:16 -0000
@@ -70,6 +70,7 @@
 
 % Warnings about simple code
 :- include_module common.
+:- include_module format_call.
 :- include_module simplify.
 
 :- include_module goal_path.
Index: compiler/common.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/common.m,v
retrieving revision 1.87
diff -u -b -r1.87 common.m
--- compiler/common.m	28 Nov 2005 04:11:39 -0000	1.87
+++ compiler/common.m	24 Jan 2006 03:24:17 -0000
@@ -576,8 +576,9 @@
                 types_match_exactly_list(OutputArgTypes1, OutputArgTypes2)
             ->
                 goal_info_get_context(GoalInfo, Context),
-                simplify_info_do_add_msg(
-                    duplicate_call(SeenCall, PrevContext, Context), !Info)
+                Msg = duplicate_call(SeenCall, PrevContext),
+                ContextMsg = context_det_msg(Context, Msg),
+                simplify_info_do_add_det_msg(ContextMsg, !Info)
             ;
                 true
             ),
Index: compiler/det_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/det_analysis.m,v
retrieving revision 1.183
diff -u -b -r1.183 det_analysis.m
--- compiler/det_analysis.m	17 Nov 2005 15:57:08 -0000	1.183
+++ compiler/det_analysis.m	24 Jan 2006 03:54:29 -0000
@@ -79,7 +79,7 @@
     %
 :- pred det_infer_proc(pred_id::in, proc_id::in, module_info::in,
     module_info::out, globals::in, determinism::out, determinism::out,
-    list(det_msg)::out) is det.
+    list(context_det_msg)::out) is det.
 
     % Infers the determinism of `Goal0' and returns this in `Detism'.
     % It annotates the goal and all its subgoals with their determinism
@@ -87,7 +87,8 @@
     %
 :- pred det_infer_goal(hlds_goal::in, hlds_goal::out, instmap::in,
     soln_context::in, list(failing_context)::in, det_info::in,
-    determinism::out, list(failing_context)::out, list(det_msg)::out) is det.
+    determinism::out, list(failing_context)::out, list(context_det_msg)::out)
+    is det.
 
     % Work out how many solutions are needed for a given determinism.
     %
@@ -176,7 +177,7 @@
 
 :- pred global_inference_single_pass(pred_proc_list::in, bool::in,
     module_info::in, module_info::out,
-    list(det_msg)::in, list(det_msg)::out,
+    list(context_det_msg)::in, list(context_det_msg)::out,
     maybe_changed::in, maybe_changed::out, io::di, io::uo) is det.
 
 global_inference_single_pass([], _, !ModuleInfo, !Msgs, !Changed, !IO).
@@ -283,7 +284,10 @@
         determinism_to_code_model(ToBeCheckedDetism, ToBeCheckedCodeModel),
         ToBeCheckedCodeModel \= model_det
     ->
-        !:Msgs = [has_io_state_but_not_det(PredId, ProcId) | !.Msgs]
+        proc_info_context(Proc0, ProcContext),
+        IOStateMsg = has_io_state_but_not_det(PredId, ProcId),
+        IOStateContextMsg = context_det_msg(ProcContext, IOStateMsg),
+        !:Msgs = [IOStateContextMsg | !.Msgs]
     ;
         true
     ),
@@ -300,7 +304,17 @@
         ; NewDetism = nondet
         )
     ->
-        list.cons(export_model_non_proc(PredId, ProcId, NewDetism), !Msgs)
+        (
+            get_exported_proc_context(ExportedProcs, PredId, ProcId,
+                PragmaContext)
+        ->
+            ExportMsg = export_model_non_proc(PredId, ProcId, NewDetism),
+            ExportContextMsg = context_det_msg(PragmaContext, ExportMsg),
+            list.cons(ExportContextMsg, !Msgs)
+        ;
+            unexpected(this_file,
+                "Cannot find proc in table of pragma exported procs")
+        )
     ;
         true
     ),
@@ -315,6 +329,16 @@
     map__det_update(Preds0, PredId, Pred, Preds),
     module_info_set_preds(Preds, !ModuleInfo).
 
+:- pred get_exported_proc_context(list(pragma_exported_proc)::in,
+    pred_id::in, proc_id::in, prog_context::out) is semidet.
+
+get_exported_proc_context([Proc | Procs], PredId, ProcId, Context) :-
+    ( Proc = pragma_exported_proc(PredId, ProcId, _, Context0) ->
+        Context = Context0
+    ;
+        get_exported_proc_context(Procs, PredId, ProcId, Context)
+    ).
+
 %-----------------------------------------------------------------------------%
 
 det_infer_goal(Goal0 - GoalInfo0, Goal - GoalInfo, InstMap0, !.SolnContext,
@@ -464,7 +488,7 @@
 :- pred det_infer_goal_2(hlds_goal_expr::in, hlds_goal_expr::out,
     hlds_goal_info::in, instmap::in, soln_context::in,
     list(failing_context)::in, det_info::in, determinism::out,
-    list(failing_context)::out, list(det_msg)::out) is det.
+    list(failing_context)::out, list(context_det_msg)::out) is det.
 
 det_infer_goal_2(GoalExpr0, GoalExpr, GoalInfo, InstMap0, SolnContext,
         RightFailingContexts, DetInfo, Detism, GoalFailingContexts, !:Msgs) :-
@@ -488,10 +512,12 @@
         ->
             true
         ;
+            goal_info_get_context(GoalInfo, Context),
             det_info_get_pred_id(DetInfo, PredId),
             det_info_get_proc_id(DetInfo, ProcId),
             Msg = par_conj_not_det(Detism, PredId, ProcId, GoalInfo, Goals),
-            !:Msgs = [Msg | !.Msgs]
+            ContextMsg = context_det_msg(Context, Msg),
+            !:Msgs = [ContextMsg | !.Msgs]
         ),
         GoalExpr = par_conj(Goals)
     ;
@@ -572,10 +598,13 @@
                 !:Msgs = [],
                 determinism_components(Detism, CanFail, at_most_many)
             ;
+                goal_info_get_context(GoalInfo, GoalContext),
                 det_get_proc_info(DetInfo, ProcInfo),
                 proc_info_varset(ProcInfo, VarSet),
-                !:Msgs = [cc_pred_in_wrong_context(GoalInfo, Detism0,
-                    PredId, ProcId0, VarSet, RightFailingContexts)],
+                Msg = cc_pred_in_wrong_context(GoalInfo, Detism0,
+                    PredId, ProcId0, VarSet, RightFailingContexts),
+                ContextMsg = context_det_msg(GoalContext, Msg),
+                !:Msgs = [ContextMsg],
                 ProcId = ProcId0,
                 % Code elsewhere relies on the assumption that
                 % SolnContext = all_solns => NumSolns \= at_most_many_cc,
@@ -599,6 +628,7 @@
     ;
         GoalExpr0 = generic_call(GenericCall, _ArgVars, _Modes, CallDetism),
         determinism_components(CallDetism, CanFail, NumSolns),
+        goal_info_get_context(GoalInfo, Context),
         (
             NumSolns = at_most_many_cc,
             SolnContext = all_solns
@@ -609,8 +639,10 @@
             % or introduced later (for calls).
             det_get_proc_info(DetInfo, ProcInfo),
             proc_info_varset(ProcInfo, VarSet),
-            !:Msgs = [higher_order_cc_pred_in_wrong_context(GoalInfo,
-                CallDetism, VarSet, RightFailingContexts)],
+            Msg = higher_order_cc_pred_in_wrong_context(GoalInfo, CallDetism,
+                VarSet, RightFailingContexts),
+            ContextMsg = context_det_msg(Context, Msg),
+            !:Msgs = [ContextMsg],
             % Code elsewhere relies on the assumption that
             % SolnContext = all_soln => NumSolns \= at_most_many_cc,
             % so we need to enforce that here.
@@ -621,7 +653,6 @@
         ),
         (
             CanFail = can_fail,
-            goal_info_get_context(GoalInfo, Context),
             GoalFailingContexts = [Context - generic_call_goal(GenericCall)]
         ;
             CanFail = cannot_fail,
@@ -805,9 +836,10 @@
             ( set__empty(BugVars) ->
                 ScopeMsgs1 = []
             ;
-                ScopeMsg1 = promise_equivalent_solutions_missing_vars(Context,
-                    VarSet, BugVars),
-                ScopeMsgs1 = [ScopeMsg1]
+                ScopeMsg1 = promise_equivalent_solutions_missing_vars(VarSet,
+                    BugVars),
+                ContextScopeMsg1 = context_det_msg(Context, ScopeMsg1),
+                ScopeMsgs1 = [ContextScopeMsg1]
             ),
             % Which vars were listed in the promise_equivalent_solutions
             % but not bound inside the scope?
@@ -815,9 +847,10 @@
             ( set__empty(ExtraVars) ->
                 ScopeMsgs2 = []
             ;
-                ScopeMsg2 = promise_equivalent_solutions_extra_vars(Context,
-                    VarSet, ExtraVars),
-                ScopeMsgs2 = [ScopeMsg2]
+                ScopeMsg2 = promise_equivalent_solutions_extra_vars(VarSet,
+                    ExtraVars),
+                ContextScopeMsg2 = context_det_msg(Context, ScopeMsg2),
+                ScopeMsgs2 = [ContextScopeMsg2]
             ),
             ScopeMsgs = ScopeMsgs1 ++ ScopeMsgs2
         ;
@@ -844,7 +877,12 @@
                 may_throw_exception(Attributes) = will_not_throw_exception,
                 Detism0 = erroneous
             ->
-                !:Msgs = [will_not_throw_with_erroneous(PredId, ProcId)]
+                proc_info_context(ProcInfo, ProcContext),
+                WillNotThrowMsg =
+                    will_not_throw_with_erroneous(PredId, ProcId),
+                WillNotThrowContextMsg =
+                    context_det_msg(ProcContext, WillNotThrowMsg),
+                !:Msgs = [WillNotThrowContextMsg]
             ;
                 !:Msgs = []
             ),
@@ -859,9 +897,13 @@
                 NumSolns1 = at_most_many_cc,
                 SolnContext = all_solns
             ->
+                goal_info_get_context(GoalInfo, GoalContext),
                 proc_info_varset(ProcInfo, VarSet),
-                !:Msgs = [cc_pred_in_wrong_context(GoalInfo, Detism0,
-                    PredId, ProcId, VarSet, RightFailingContexts) | !.Msgs],
+                WrongContextMsg = cc_pred_in_wrong_context(GoalInfo, Detism0,
+                    PredId, ProcId, VarSet, RightFailingContexts),
+                WrongContextContextMsg = context_det_msg(GoalContext,
+                    WrongContextMsg),
+                !:Msgs = [WrongContextContextMsg | !.Msgs],
                 NumSolns = at_most_many
             ;
                 NumSolns = NumSolns1
@@ -877,7 +919,10 @@
             )
         ;
             MaybeDetism = no,
-            !:Msgs = [pragma_c_code_without_det_decl(PredId, ProcId)],
+            proc_info_context(ProcInfo, Context),
+            Msg = pragma_c_code_without_det_decl(PredId, ProcId),
+            ContextMsg = context_det_msg(Context, Msg),
+            !:Msgs = [ContextMsg],
             Detism = erroneous,
             GoalFailingContexts = []
         ),
@@ -893,7 +938,7 @@
 :- pred det_infer_conj(list(hlds_goal)::in, list(hlds_goal)::out, instmap::in,
     soln_context::in, list(failing_context)::in, det_info::in,
     determinism::out, list(failing_context)::in, list(failing_context)::out,
-    list(det_msg)::out) is det.
+    list(context_det_msg)::out) is det.
 
 det_infer_conj([], [], _InstMap0, _SolnContext, _RightFailingContexts,
         _DetInfo, det, !ConjFailingContexts, []).
@@ -939,7 +984,7 @@
 :- pred det_infer_par_conj(list(hlds_goal)::in, list(hlds_goal)::out,
     instmap::in, soln_context::in, list(failing_context)::in, det_info::in,
     determinism::out, list(failing_context)::in, list(failing_context)::out,
-    list(det_msg)::out) is det.
+    list(context_det_msg)::out) is det.
 
 det_infer_par_conj([], [], _InstMap0, _SolnContext, _RightFailingContexts,
         _DetInfo, det, !ConjFailingContexts, []).
@@ -964,7 +1009,7 @@
     soln_context::in, list(failing_context)::in, det_info::in,
     can_fail::in, soln_count::in, determinism::out,
     list(failing_context)::in, list(failing_context)::out,
-    list(det_msg)::out) is det.
+    list(context_det_msg)::out) is det.
 
 det_infer_disj([], [], _InstMap0, _SolnContext, _RightFailingContexts,
         _DetInfo, CanFail, MaxSolns, Detism, !DisjFailingContexts, []) :-
@@ -1017,7 +1062,7 @@
     soln_context::in, list(failing_context)::in, det_info::in, can_fail::in,
     soln_count::in, determinism::out,
     list(failing_context)::in, list(failing_context)::out,
-    list(det_msg)::out) is det.
+    list(context_det_msg)::out) is det.
 
 det_infer_switch([], [], _InstMap0, _SolnContext, _RightFailingContexts,
         _DetInfo, CanFail, MaxSolns, Detism, !SwitchFailingContexts, []) :-
@@ -1082,7 +1127,7 @@
 :- pred det_check_for_noncanonical_type(prog_var::in, bool::in, can_fail::in,
     soln_context::in, list(failing_context)::in, list(failing_context)::in,
     hlds_goal_info::in, cc_unify_context::in, det_info::in, soln_count::out,
-    list(det_msg)::in, list(det_msg)::out) is det.
+    list(context_det_msg)::in, list(context_det_msg)::out) is det.
 
 det_check_for_noncanonical_type(Var, ExaminesRepresentation, CanFail,
         SolnContext, FailingContextsA, FailingContextsB, GoalInfo, GoalContext,
@@ -1099,13 +1144,18 @@
         det_type_has_user_defined_equality_pred(DetInfo, Type)
     ->
         ( CanFail = can_fail ->
+            goal_info_get_context(GoalInfo, Context),
             proc_info_varset(ProcInfo, VarSet),
-            !:Msgs = [cc_unify_can_fail(GoalInfo, Var, Type, VarSet,
-                GoalContext) | !.Msgs]
+            Msg = cc_unify_can_fail(GoalInfo, Var, Type, VarSet, GoalContext),
+            ContextMsg = context_det_msg(Context, Msg),
+            !:Msgs = [ContextMsg | !.Msgs]
         ; SolnContext = all_solns ->
+            goal_info_get_context(GoalInfo, Context),
             proc_info_varset(ProcInfo, VarSet),
-            !:Msgs = [cc_unify_in_wrong_context(GoalInfo, Var, Type, VarSet,
-                GoalContext, FailingContextsA ++ FailingContextsB) | !.Msgs]
+            Msg = cc_unify_in_wrong_context(GoalInfo, Var, Type, VarSet,
+                GoalContext, FailingContextsA ++ FailingContextsB),
+            ContextMsg = context_det_msg(Context, Msg),
+            !:Msgs = [ContextMsg | !.Msgs]
         ;
             true
         ),
Index: compiler/det_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/det_report.m,v
retrieving revision 1.110
diff -u -b -r1.110 det_report.m
--- compiler/det_report.m	28 Nov 2005 04:11:40 -0000	1.110
+++ compiler/det_report.m	24 Jan 2006 03:48:23 -0000
@@ -9,11 +9,13 @@
 % File: det_report.m.
 % Author: zs.
 
-% This module handles reporting of determinism errors and warnings.
+% This module handles reporting of determinism errors and warnings,
+% as well as errors and warnings from some other related compiler passes
+% such as simplify.
 
 %-----------------------------------------------------------------------------%
 
-:- module check_hlds__det_report.
+:- module check_hlds.det_report.
 :- interface.
 
 :- import_module check_hlds.det_util.
@@ -22,33 +24,43 @@
 :- import_module hlds.hlds_pred.
 :- import_module parse_tree.prog_data.
 
+:- import_module mdbcomp.prim_data.
+
 :- import_module io.
 :- import_module list.
 :- import_module set.
 :- import_module std_util.
+:- import_module string.
 
 %-----------------------------------------------------------------------------%
 
+:- type context_det_msg
+    --->    context_det_msg(prog_context, det_msg).
+
 :- type det_msg
-            % The followintg are warnings.
-    --->    multidet_disj(prog_context, list(prog_context))
-    ;       det_disj(prog_context, list(prog_context))
-    ;       semidet_disj(prog_context, list(prog_context))
-    ;       zero_soln_disj(prog_context, list(prog_context))
-    ;       zero_soln_disjunct(prog_context)
-    ;       ite_cond_cannot_fail(prog_context)
-    ;       ite_cond_cannot_succeed(prog_context)
-    ;       negated_goal_cannot_fail(prog_context)
-    ;       negated_goal_cannot_succeed(prog_context)
-    ;       goal_cannot_succeed(prog_context)
-    ;       det_goal_has_no_outputs(prog_context)
-    ;       warn_obsolete(pred_id, prog_context)
+            % The following are warnings.
+
+    --->    multidet_disj(list(prog_context))
+    ;       det_disj(list(prog_context))
+    ;       semidet_disj(list(prog_context))
+    ;       zero_soln_disj(list(prog_context))
+    ;       zero_soln_disjunct
+    ;       ite_cond_cannot_fail
+    ;       ite_cond_cannot_succeed
+    ;       negated_goal_cannot_fail
+    ;       negated_goal_cannot_succeed
+    ;       goal_cannot_succeed
+    ;       det_goal_has_no_outputs
+    ;       warn_obsolete(pred_id)
             % Warning about calls to predicates for which there is
             % a `:- pragma obsolete' declaration.
-    ;       warn_infinite_recursion(prog_context)
+    ;       warn_infinite_recursion
             % Warning about recursive calls which would cause infinite loops.
-    ;       duplicate_call(seen_call_id, prog_context, prog_context)
+    ;       duplicate_call(seen_call_id, prog_context)
             % Multiple calls with the same input args.
+    ;       unknown_format_string(sym_name, arity)
+    ;       unknown_format_values(sym_name, arity)
+    ;       bad_format(sym_name, arity, string)
 
             % The following are errors.
 
@@ -70,9 +82,9 @@
     ;       export_model_non_proc(pred_id, proc_id, determinism)
             % Procedure with multi or nondet detism exported
             % via :- pragma export ...
-    ;       promise_equivalent_solutions_missing_vars(prog_context,
-                prog_varset, set(prog_var))
-    ;       promise_equivalent_solutions_extra_vars(prog_context, prog_varset,
+    ;       promise_equivalent_solutions_missing_vars(prog_varset,
+                set(prog_var))
+    ;       promise_equivalent_solutions_extra_vars(prog_varset,
                 set(prog_var)).
 
 :- type seen_call_id
@@ -106,20 +118,20 @@
     % determinisms.
     %
 :- pred det_check_lambda(determinism::in, determinism::in, hlds_goal::in,
-    hlds_goal_info::in, det_info::in, list(det_msg)::out) is det.
+    hlds_goal_info::in, det_info::in, list(context_det_msg)::out) is det.
 
     % Print some determinism warning and/or error messages,
     % and update the module info accordingly.
     %
-:- pred det_report_and_handle_msgs(list(det_msg)::in,
+:- pred det_report_and_handle_msgs(list(context_det_msg)::in,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
     % Print some determinism warning and/or error messages,
     % and return the number of warnings and errors, so that code
     % somewhere elsewhere can update the module info.
     %
-:- pred det_report_msgs(list(det_msg)::in, module_info::in, int::out, int::out,
-    io::di, io::uo) is det.
+:- pred det_report_msgs(list(context_det_msg)::in, module_info::in,
+    int::out, int::out, io::di, io::uo) is det.
 
 :- type msg_modes
     --->    all_modes   % The warning should be reported only
@@ -146,7 +158,10 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type det_comparison  --->    tighter ; sameas ; looser.
+:- type det_comparison
+    --->    tighter
+    ;       sameas
+    ;       looser.
 
 :- pred compare_determinisms(determinism::in, determinism::in,
     det_comparison::out) is det.
@@ -212,9 +227,9 @@
             Cmp = sameas
         ;
             Cmp = looser,
-            globals__io_lookup_bool_option(warn_det_decls_too_lax,
+            globals.io_lookup_bool_option(warn_det_decls_too_lax,
                 ShouldIssueWarning, !IO),
-            globals__io_lookup_bool_option(warn_inferred_erroneous,
+            globals.io_lookup_bool_option(warn_inferred_erroneous,
                 WarnAboutInferredErroneous, !IO),
             pred_info_get_markers(PredInfo0, Markers),
             (
@@ -264,7 +279,7 @@
                 DeclaredDetism, InferredDetism, ReportSpec),
             proc_info_goal(ProcInfo0, Goal),
             proc_info_vartypes(ProcInfo0, VarTypes),
-            globals__io_get_globals(Globals, !IO),
+            globals.io_get_globals(Globals, !IO),
             det_info_init(!.ModuleInfo, VarTypes, PredId, ProcId, Globals,
                 DetInfo),
             det_diagnose_goal(Goal, DeclaredDetism, [], DetInfo, _, [], Specs),
@@ -277,7 +292,7 @@
     ( valid_determinism_for_eval_method(EvalMethod, InferredDetism) = yes ->
         proc_info_set_eval_method(EvalMethod, ProcInfo0, ProcInfo),
         pred_info_procedures(PredInfo0, ProcTable0),
-        map__det_update(ProcTable0, ProcId, ProcInfo, ProcTable),
+        map.det_update(ProcTable0, ProcId, ProcInfo, ProcTable),
         pred_info_set_procedures(ProcTable, PredInfo0, PredInfo),
         module_info_set_pred_info(PredId, PredInfo, !ModuleInfo)
     ;
@@ -288,11 +303,11 @@
             words("declaration not allowed for procedure"),
             words("with determinism `"
                 ++ determinism_to_string(InferredDetism) ++ "'.")], !IO),
-        globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+        globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
         (
             VerboseErrors = yes,
             solutions(get_valid_dets(EvalMethod), Detisms),
-            DetismStrs = list__map(determinism_to_string, Detisms),
+            DetismStrs = list.map(determinism_to_string, Detisms),
             DetismPieces = list_to_pieces(DetismStrs),
             write_error_pieces_not_first_line(Context, 0,
                 [words("The pragma requested is only valid"),
@@ -373,7 +388,7 @@
         proc_info_argmodes(ProcInfo, PredArgModes),
         pred_args_to_func_args(PredArgModes, FuncArgModes, _FuncResultMode),
         \+ (
-            list__member(FuncArgMode, FuncArgModes),
+            list.member(FuncArgMode, FuncArgModes),
             \+ mode_is_fully_input(!.ModuleInfo, FuncArgMode)
         )
     ->
@@ -387,7 +402,7 @@
             words("the primary mode of a function cannot be"),
             words("`" ++ mercury_det_to_string(InferredDetism) ++ "'.")],
         write_error_pieces(FuncContext, 0, Pieces, !IO),
-        globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+        globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
         (
             VerboseErrors = yes,
             ExtMsg = func_primary_mode_det_msg,
@@ -418,8 +433,11 @@
     ( Cmp = tighter ->
         det_info_get_pred_id(DetInfo, PredId),
         det_info_get_proc_id(DetInfo, ProcId),
-        Msgs = [error_in_lambda(DeclaredDetism, InferredDetism, Goal, GoalInfo,
-            PredId, ProcId)]
+        goal_info_get_context(GoalInfo, Context),
+        Msg = error_in_lambda(DeclaredDetism, InferredDetism, Goal, GoalInfo,
+            PredId, ProcId),
+        ContextMsg = context_det_msg(Context, Msg),
+        Msgs = [ContextMsg]
     ;
         % We don't bother issuing warnings if the determinism was too loose;
         % that will often be the case, and should not be warned about.
@@ -569,10 +587,10 @@
         VarStr = mercury_var_to_string(Var, VarSet, no),
         (
             det_lookup_var_type(ModuleInfo, ProcInfo, Var, TypeDefn),
-            hlds_data__get_type_defn_body(TypeDefn, TypeBody),
+            hlds_data.get_type_defn_body(TypeDefn, TypeBody),
             ConsTable = TypeBody ^ du_type_cons_tag_values
         ->
-            map__keys(ConsTable, ConsIds),
+            map.keys(ConsTable, ConsIds),
             det_diagnose_missing_consids(ConsIds, Cases, Missing),
             cons_id_list_to_pieces(Missing, MissingPieces),
             Pieces = [words("The switch on "), fixed(VarStr),
@@ -589,7 +607,7 @@
     ),
     det_diagnose_switch(Var, Cases, Desired, SwitchContext, DetInfo,
         Diagnosed2, !Specs),
-    bool__or(Diagnosed1, Diagnosed2, Diagnosed).
+    bool.or(Diagnosed1, Diagnosed2, Diagnosed).
 
 det_diagnose_goal_2(call(PredId, ProcId, _, _, CallContext, _), GoalInfo,
         Desired, Actual, _, DetInfo, yes, !Specs) :-
@@ -633,8 +651,8 @@
         !Specs),
     det_diagnose_goal(Else, Desired, SwitchContext, DetInfo, Diagnosed3,
         !Specs),
-    bool__or(Diagnosed2, Diagnosed3, Diagnosed23),
-    bool__or(Diagnosed1, Diagnosed23, Diagnosed).
+    bool.or(Diagnosed2, Diagnosed3, Diagnosed23),
+    bool.or(Diagnosed1, Diagnosed23, Diagnosed).
 
 det_diagnose_goal_2(not(_), GoalInfo, Desired, Actual, _, _, Diagnosed,
         !Specs) :-
@@ -694,7 +712,7 @@
     error_msg_spec::out(known_error_msg_spec)) is det.
 
 report_generic_call_context(Context, CallType, Spec) :-
-    hlds_goal__generic_call_id(CallType, CallId),
+    hlds_goal.generic_call_id(CallType, CallId),
     Pieces = [words(call_id_to_string(CallId))],
     Spec = error_msg_spec(no, Context, 0, Pieces).
 
@@ -728,7 +746,7 @@
     ;
         Diagnosed2 = no
     ),
-    bool__or(Diagnosed1, Diagnosed2, Diagnosed),
+    bool.or(Diagnosed1, Diagnosed2, Diagnosed),
     (
         Diagnosed = yes
     ;
@@ -759,7 +777,7 @@
         !Specs),
     det_diagnose_conj(Goals, Desired, SwitchContext, DetInfo, Diagnosed2,
         !Specs),
-    bool__or(Diagnosed1, Diagnosed2, Diagnosed).
+    bool.or(Diagnosed1, Diagnosed2, Diagnosed).
 
 :- pred det_diagnose_disj(list(hlds_goal)::in,
     determinism::in, determinism::in, list(switch_context)::in,
@@ -803,7 +821,7 @@
     ),
     det_diagnose_disj(Goals, Desired, Actual, SwitchContext, DetInfo,
         !ClausesWithSoln, Diagnosed2, !Specs),
-    bool__or(Diagnosed1, Diagnosed2, Diagnosed).
+    bool.or(Diagnosed1, Diagnosed2, Diagnosed).
 
 :- pred det_diagnose_switch(prog_var::in, list(case)::in, determinism::in,
     list(switch_context)::in, det_info::in, bool::out,
@@ -818,7 +836,7 @@
         !Specs),
     det_diagnose_switch(Var, Cases, Desired, SwitchContext0, DetInfo,
         Diagnosed2, !Specs),
-    bool__or(Diagnosed1, Diagnosed2, Diagnosed).
+    bool.or(Diagnosed1, Diagnosed2, Diagnosed).
 
 %-----------------------------------------------------------------------------%
 
@@ -829,7 +847,7 @@
 det_diagnose_missing_consids([ConsId | ConsIds], Cases, Missing) :-
     det_diagnose_missing_consids(ConsIds, Cases, Missing0),
     (
-        list__member(Case, Cases),
+        list.member(Case, Cases),
         Case = case(ConsId, _)
     ->
         Missing = Missing0
@@ -854,11 +872,12 @@
         PiecesHead = [fixed(ConsIdStr ++ ",")]
     ),
     cons_id_list_to_pieces(ConsIds, PiecesTail),
-    list__append(PiecesHead, PiecesTail, Pieces).
+    list.append(PiecesHead, PiecesTail, Pieces).
 
 %-----------------------------------------------------------------------------%
 
-:- type switch_context ---> switch_context(prog_var, cons_id).
+:- type switch_context
+    --->    switch_context(prog_var, cons_id).
 
 :- pred det_diagnose_switch_context(prog_context::in,
     list(switch_context)::in, det_info::in,
@@ -929,7 +948,7 @@
             InitSpecs = []
         ),
         pred_info_procedures(PredInfo, ProcTable),
-        map__lookup(ProcTable, ProcId, ProcInfo),
+        map.lookup(ProcTable, ProcId, ProcInfo),
         proc_info_declared_argmodes(ProcInfo, ArgModes),
         proc_info_inst_varset(ProcInfo, InstVarSet),
         PredPieces = describe_one_pred_name_mode(ModuleInfo,
@@ -977,10 +996,10 @@
             StartWords = "in unification"
         )
     ),
-    ( varset__search_name(VarSet, LHS, _) ->
+    ( varset.search_name(VarSet, LHS, _) ->
         (
             RHS = var(RV),
-            \+ varset__search_name(VarSet, RV, _)
+            \+ varset.search_name(VarSet, RV, _)
         ->
             Pieces = [words(StartWords), words("with"),
                 words(add_quotes(mercury_var_to_string(LHS, VarSet, no)))]
@@ -1004,6 +1023,8 @@
 :- type det_msg_type
     --->    simple_code_warning
     ;       call_warning
+    ;       format_unknown
+    ;       format_known_bad
     ;       det_error.
 
 det_report_and_handle_msgs(Msgs, !ModuleInfo, !IO) :-
@@ -1013,7 +1034,7 @@
     ;
         Msgs = [_ | _],
         det_report_msgs(Msgs, !.ModuleInfo, WarnCnt, ErrCnt, !IO),
-        globals__io_lookup_bool_option(halt_at_warn, HaltAtWarn, !IO),
+        globals.io_lookup_bool_option(halt_at_warn, HaltAtWarn, !IO),
         (
             (
                 ErrCnt > 0
@@ -1022,26 +1043,35 @@
                 HaltAtWarn = yes
             )
         ->
-            io__set_exit_status(1, !IO),
+            io.set_exit_status(1, !IO),
             module_info_incr_errors(!ModuleInfo)
         ;
             true
         )
     ).
 
-det_report_msgs(Msgs, ModuleInfo, WarnCnt, ErrCnt, !IO) :-
-    globals__io_lookup_bool_option(warn_simple_code, WarnSimple, !IO),
-    globals__io_lookup_bool_option(warn_duplicate_calls, WarnCalls, !IO),
-    det_report_msgs_2(Msgs, WarnSimple, WarnCalls, ModuleInfo,
+det_report_msgs(ContextMsgs0, ModuleInfo, WarnCnt, ErrCnt, !IO) :-
+    globals.io_lookup_bool_option(warn_simple_code, WarnSimple, !IO),
+    globals.io_lookup_bool_option(warn_duplicate_calls, WarnCalls, !IO),
+    globals.io_lookup_bool_option(warn_unknown_format_calls,
+        WarnUnknownFormat, !IO),
+    globals.io_lookup_bool_option(warn_known_bad_format_calls,
+        WarnKnownBadFormat, !IO),
+        % Programmers prefer reading messages in order of context.
+    list.sort(ContextMsgs0, ContextMsgs),
+    det_report_msgs_2(ContextMsgs, WarnSimple, WarnCalls,
+        WarnUnknownFormat, WarnKnownBadFormat, ModuleInfo,
         0, WarnCnt, 0, ErrCnt, !IO).
 
-:- pred det_report_msgs_2(list(det_msg)::in, bool::in, bool::in,
-    module_info::in, int::in, int::out, int::in, int::out, io::di, io::uo)
-    is det.
+:- pred det_report_msgs_2(list(context_det_msg)::in, bool::in, bool::in,
+    bool::in, bool::in, module_info::in, int::in, int::out, int::in, int::out,
+    io::di, io::uo) is det.
 
-det_report_msgs_2([], _, _, _ModuleInfo, !WarnCnt, !ErrCnt, !IO).
-det_report_msgs_2([Msg | Msgs], WarnSimple, WarnCalls, ModuleInfo,
-        !WarnCnt, !ErrCnt, !IO) :-
+det_report_msgs_2([], _, _, _, _, _ModuleInfo, !WarnCnt, !ErrCnt, !IO).
+det_report_msgs_2([ContextMsg | ContextMsgs], WarnSimple, WarnCalls,
+        WarnUnknownFormat, WarnKnownBadFormat, ModuleInfo, !WarnCnt,
+        !ErrCnt, !IO) :-
+    ContextMsg = context_det_msg(Context, Msg),
     det_msg_get_type(Msg, MsgType),
     (
         WarnSimple = no,
@@ -1054,39 +1084,54 @@
     ->
         true
     ;
-        det_report_msg(Msg, ModuleInfo, !IO),
-        (
-            MsgType = simple_code_warning,
-            !:WarnCnt = !.WarnCnt + 1
+        WarnUnknownFormat = no,
+        MsgType = format_unknown
+    ->
+        true
         ;
-            MsgType = call_warning,
+        WarnKnownBadFormat = no,
+        MsgType = format_known_bad
+    ->
+        true
+    ;
+        det_report_msg(Msg, Context, ModuleInfo, !IO),
+        (
+            ( MsgType = simple_code_warning
+            ; MsgType = call_warning
+            ; MsgType = format_unknown
+            ; MsgType = format_known_bad
+            ),
             !:WarnCnt = !.WarnCnt + 1
         ;
             MsgType = det_error,
             !:ErrCnt = !.ErrCnt + 1
         )
     ),
-    det_report_msgs_2(Msgs, WarnSimple, WarnCalls, ModuleInfo,
+    det_report_msgs_2(ContextMsgs, WarnSimple, WarnCalls,
+        WarnUnknownFormat, WarnKnownBadFormat, ModuleInfo,
         !WarnCnt, !ErrCnt, !IO).
 
 :- pred det_msg_get_type(det_msg::in, det_msg_type::out) is det.
 
-det_msg_get_type(multidet_disj(_, _), simple_code_warning).
-det_msg_get_type(det_disj(_, _), simple_code_warning).
-det_msg_get_type(semidet_disj(_, _), simple_code_warning).
-det_msg_get_type(zero_soln_disj(_, _), simple_code_warning).
-det_msg_get_type(zero_soln_disjunct(_), simple_code_warning).
-det_msg_get_type(ite_cond_cannot_fail(_), simple_code_warning).
-det_msg_get_type(ite_cond_cannot_succeed(_), simple_code_warning).
-det_msg_get_type(negated_goal_cannot_fail(_), simple_code_warning).
-det_msg_get_type(negated_goal_cannot_succeed(_), simple_code_warning).
-det_msg_get_type(goal_cannot_succeed(_), simple_code_warning).
-det_msg_get_type(det_goal_has_no_outputs(_), simple_code_warning).
+det_msg_get_type(multidet_disj(_), simple_code_warning).
+det_msg_get_type(det_disj(_), simple_code_warning).
+det_msg_get_type(semidet_disj(_), simple_code_warning).
+det_msg_get_type(zero_soln_disj(_), simple_code_warning).
+det_msg_get_type(zero_soln_disjunct, simple_code_warning).
+det_msg_get_type(ite_cond_cannot_fail, simple_code_warning).
+det_msg_get_type(ite_cond_cannot_succeed, simple_code_warning).
+det_msg_get_type(negated_goal_cannot_fail, simple_code_warning).
+det_msg_get_type(negated_goal_cannot_succeed, simple_code_warning).
+det_msg_get_type(goal_cannot_succeed, simple_code_warning).
+det_msg_get_type(det_goal_has_no_outputs, simple_code_warning).
     % XXX warn_obsolete isn't really a simple code warning.
     % We should add a separate warning type for this.
-det_msg_get_type(warn_obsolete(_, _), simple_code_warning).
-det_msg_get_type(warn_infinite_recursion(_), simple_code_warning).
-det_msg_get_type(duplicate_call(_, _, _), call_warning).
+det_msg_get_type(warn_obsolete(_), simple_code_warning).
+det_msg_get_type(warn_infinite_recursion, simple_code_warning).
+det_msg_get_type(duplicate_call(_, _), call_warning).
+det_msg_get_type(unknown_format_string(_, _), format_unknown).
+det_msg_get_type(unknown_format_values(_, _), format_unknown).
+det_msg_get_type(bad_format(_, _, _), format_known_bad).
 det_msg_get_type(cc_unify_can_fail(_, _, _, _, _), det_error).
 det_msg_get_type(cc_unify_in_wrong_context(_, _, _, _, _, _), det_error).
 det_msg_get_type(cc_pred_in_wrong_context(_, _, _, _, _, _), det_error).
@@ -1097,24 +1142,26 @@
 det_msg_get_type(has_io_state_but_not_det(_, _), det_error).
 det_msg_get_type(will_not_throw_with_erroneous(_, _), det_error).
 det_msg_get_type(export_model_non_proc(_, _, _), det_error).
-det_msg_get_type(promise_equivalent_solutions_missing_vars(_, _, _),
-    det_error).
-det_msg_get_type(promise_equivalent_solutions_extra_vars(_, _, _), det_error).
-
-det_msg_is_any_mode_msg(multidet_disj(_, _), all_modes).
-det_msg_is_any_mode_msg(det_disj(_, _), all_modes).
-det_msg_is_any_mode_msg(semidet_disj(_, _), all_modes).
-det_msg_is_any_mode_msg(zero_soln_disj(_, _), all_modes).
-det_msg_is_any_mode_msg(zero_soln_disjunct(_), all_modes).
-det_msg_is_any_mode_msg(ite_cond_cannot_fail(_), all_modes).
-det_msg_is_any_mode_msg(ite_cond_cannot_succeed(_), all_modes).
-det_msg_is_any_mode_msg(negated_goal_cannot_fail(_), all_modes).
-det_msg_is_any_mode_msg(negated_goal_cannot_succeed(_), all_modes).
-det_msg_is_any_mode_msg(goal_cannot_succeed(_), all_modes).
-det_msg_is_any_mode_msg(det_goal_has_no_outputs(_), all_modes).
-det_msg_is_any_mode_msg(warn_obsolete(_, _), all_modes).
-det_msg_is_any_mode_msg(warn_infinite_recursion(_), any_mode).
-det_msg_is_any_mode_msg(duplicate_call(_, _, _), any_mode).
+det_msg_get_type(promise_equivalent_solutions_missing_vars(_, _), det_error).
+det_msg_get_type(promise_equivalent_solutions_extra_vars(_, _), det_error).
+
+det_msg_is_any_mode_msg(multidet_disj(_), all_modes).
+det_msg_is_any_mode_msg(det_disj(_), all_modes).
+det_msg_is_any_mode_msg(semidet_disj(_), all_modes).
+det_msg_is_any_mode_msg(zero_soln_disj(_), all_modes).
+det_msg_is_any_mode_msg(zero_soln_disjunct, all_modes).
+det_msg_is_any_mode_msg(ite_cond_cannot_fail, all_modes).
+det_msg_is_any_mode_msg(ite_cond_cannot_succeed, all_modes).
+det_msg_is_any_mode_msg(negated_goal_cannot_fail, all_modes).
+det_msg_is_any_mode_msg(negated_goal_cannot_succeed, all_modes).
+det_msg_is_any_mode_msg(goal_cannot_succeed, all_modes).
+det_msg_is_any_mode_msg(det_goal_has_no_outputs, all_modes).
+det_msg_is_any_mode_msg(warn_obsolete(_), all_modes).
+det_msg_is_any_mode_msg(warn_infinite_recursion, any_mode).
+det_msg_is_any_mode_msg(duplicate_call(_, _), any_mode).
+det_msg_is_any_mode_msg(unknown_format_string(_, _), any_mode).
+det_msg_is_any_mode_msg(unknown_format_values(_, _), any_mode).
+det_msg_is_any_mode_msg(bad_format(_, _, _), any_mode).
 det_msg_is_any_mode_msg(cc_unify_can_fail(_, _, _, _, _), any_mode).
 det_msg_is_any_mode_msg(cc_unify_in_wrong_context(_, _, _, _, _, _), any_mode).
 det_msg_is_any_mode_msg(cc_pred_in_wrong_context(_, _, _, _, _, _), any_mode).
@@ -1126,54 +1173,55 @@
 det_msg_is_any_mode_msg(has_io_state_but_not_det(_, _), any_mode).
 det_msg_is_any_mode_msg(will_not_throw_with_erroneous(_, _), any_mode).
 det_msg_is_any_mode_msg(export_model_non_proc(_, _, _), any_mode).
-det_msg_is_any_mode_msg(promise_equivalent_solutions_missing_vars(_, _, _),
+det_msg_is_any_mode_msg(promise_equivalent_solutions_missing_vars(_, _),
     any_mode).
-det_msg_is_any_mode_msg(promise_equivalent_solutions_extra_vars(_, _, _),
+det_msg_is_any_mode_msg(promise_equivalent_solutions_extra_vars(_, _),
     any_mode).
 
-:- pred det_report_msg(det_msg::in, module_info::in, io::di, io::uo) is det.
+:- pred det_report_msg(det_msg::in, prog_context::in, module_info::in,
+    io::di, io::uo) is det.
 
-det_report_msg(multidet_disj(Context, DisjunctContexts), _, !IO) :-
+det_report_msg(multidet_disj(DisjunctContexts), Context, _, !IO) :-
     Pieces = [words("Warning: the disjunction with arms on lines"),
         words(det_report_context_lines(DisjunctContexts)),
         words("has no outputs, but can succeed more than once.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(det_disj(Context, DisjunctContexts), _, !IO) :-
+det_report_msg(det_disj(DisjunctContexts), Context, _, !IO) :-
     Pieces = [words("Warning: the disjunction with arms on lines"),
         words(det_report_context_lines(DisjunctContexts)),
         words("will succeed exactly once.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(semidet_disj(Context, DisjunctContexts), _, !IO) :-
+det_report_msg(semidet_disj(DisjunctContexts), Context, _, !IO) :-
     Pieces = [words("Warning: the disjunction with arms on lines"),
         words(det_report_context_lines(DisjunctContexts)),
         words("is semidet, yet it has an output.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(zero_soln_disj(Context, DisjunctContexts), _, !IO) :-
+det_report_msg(zero_soln_disj(DisjunctContexts), Context, _, !IO) :-
     Pieces = [words("Warning: the disjunction with arms on lines"),
         words(det_report_context_lines(DisjunctContexts)),
         words("cannot succeed.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(zero_soln_disjunct(Context), _, !IO) :-
+det_report_msg(zero_soln_disjunct, Context, _, !IO) :-
     Pieces = [words("Warning: this disjunct"),
         words("will never have any solutions.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(ite_cond_cannot_fail(Context), _, !IO) :-
+det_report_msg(ite_cond_cannot_fail, Context, _, !IO) :-
     Pieces = [words("Warning: the condition of this if-then-else"),
         words("cannot fail.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(ite_cond_cannot_succeed(Context), _, !IO) :-
+det_report_msg(ite_cond_cannot_succeed, Context, _, !IO) :-
     Pieces = [words("Warning: the condition of this if-then-else"),
         words("cannot succeed.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(negated_goal_cannot_fail(Context), _, !IO) :-
+det_report_msg(negated_goal_cannot_fail, Context, _, !IO) :-
     Pieces = [words("Warning: the negated goal cannot fail.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(negated_goal_cannot_succeed(Context), _, !IO) :-
+det_report_msg(negated_goal_cannot_succeed, Context, _, !IO) :-
     Pieces = [words("Warning: the negated goal cannot succeed.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(goal_cannot_succeed(Context), _, !IO) :-
+det_report_msg(goal_cannot_succeed, Context, _, !IO) :-
     Pieces0 = [words("Warning: this goal cannot succeed.")],
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         Pieces1 = [words("The compiler will optimize away this goal,"),
@@ -1187,9 +1235,9 @@
         Pieces = Pieces0
     ),
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(det_goal_has_no_outputs(Context), _, !IO) :-
+det_report_msg(det_goal_has_no_outputs, Context, _, !IO) :-
     Pieces0 = [words("Warning: det goal has no outputs.")],
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         Pieces1 = [words("The compiler will optimize away this goal,"),
@@ -1203,19 +1251,19 @@
         Pieces = Pieces0
     ),
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(warn_obsolete(PredId, Context), ModuleInfo, !IO) :-
+det_report_msg(warn_obsolete(PredId), Context, ModuleInfo, !IO) :-
     PredPieces = describe_one_pred_name(ModuleInfo, should_module_qualify,
         PredId),
     Pieces = [words("Warning: call to obsolete")] ++ PredPieces
         ++ [suffix(".")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(warn_infinite_recursion(Context), _ModuleInfo, !IO) :-
+det_report_msg(warn_infinite_recursion, Context, _ModuleInfo, !IO) :-
     % it would be better if we supplied more information than just
     % the line number, e.g. we should print the name of the containing
     % predicate.
     Pieces0 = [words("Warning: recursive call will lead"),
         words("to infinite recursion.")],
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         Pieces1 = [words("If this recursive call is executed,"),
@@ -1229,26 +1277,37 @@
         Pieces = Pieces0
     ),
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(duplicate_call(SeenCall, PrevContext, Context), ModuleInfo,
+det_report_msg(duplicate_call(SeenCall, PrevContext), Context, ModuleInfo,
         !IO) :-
     CallPieces = det_report_seen_call_id(ModuleInfo, SeenCall),
     CurPieces = [words("Warning: redundant") | CallPieces] ++ [suffix(".")],
     PrevPieces = [words("Here is the previous") | CallPieces] ++ [suffix(".")],
     write_error_pieces(Context, 0, CurPieces, !IO),
     write_error_pieces(PrevContext, 0, PrevPieces, !IO).
-det_report_msg(cc_unify_can_fail(GoalInfo, Var, Type, VarSet, GoalContext),
-        _ModuleInfo, !IO) :-
-    goal_info_get_context(GoalInfo, Context),
+det_report_msg(unknown_format_string(SymName, Arity), Context, _, !IO) :-
+    Pieces = [words("Unknown format string in call to"),
+        sym_name_and_arity(SymName / Arity), suffix(".")],
+    write_error_pieces(Context, 0, Pieces, !IO).
+det_report_msg(unknown_format_values(SymName, Arity), Context, _, !IO) :-
+    Pieces = [words("Unknown format values in call to"),
+        sym_name_and_arity(SymName / Arity), suffix(".")],
+    write_error_pieces(Context, 0, Pieces, !IO).
+det_report_msg(bad_format(SymName, Arity, Msg), Context, _, !IO) :-
+    Pieces = [words("Mismatched format and values in call to"),
+        sym_name_and_arity(SymName / Arity), suffix(":"), nl, words(Msg)],
+    write_error_pieces(Context, 0, Pieces, !IO).
+det_report_msg(cc_unify_can_fail(_GoalInfo, Var, Type, VarSet, GoalContext),
+        Context, _ModuleInfo, !IO) :-
     (
         GoalContext = switch,
         VarStr = mercury_var_to_string(Var, VarSet, no),
         Pieces0 = [words("In switch on variable `" ++ VarStr ++ "':"), nl]
     ;
         GoalContext = unify(UnifyContext),
-        hlds_out__unify_context_to_pieces(UnifyContext, [], Pieces0)
+        hlds_out.unify_context_to_pieces(UnifyContext, [], Pieces0)
     ),
     ( type_to_ctor_and_args(Type, TypeCtor, _TypeArgs) ->
-        TypeCtorStr = hlds_out__type_ctor_to_string(TypeCtor)
+        TypeCtorStr = hlds_out.type_ctor_to_string(TypeCtor)
     ;
         unexpected(this_file, "det_report_msg: type_to_ctor_and_args failed")
     ),
@@ -1265,7 +1324,7 @@
         words("is not guaranteed to succeed.")],
     Pieces = Pieces0 ++ Pieces1,
     write_error_pieces(Context, 0, Pieces, !IO),
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         VerbosePieces = [words("Since the type has a user-defined"),
@@ -1285,19 +1344,18 @@
         VerboseErrors = no,
         globals.io_set_extra_error_info(yes, !IO)
     ).
-det_report_msg(cc_unify_in_wrong_context(GoalInfo, Var, Type, VarSet,
-        GoalContext, FailingContexts), ModuleInfo, !IO) :-
-    goal_info_get_context(GoalInfo, Context),
+det_report_msg(cc_unify_in_wrong_context(_GoalInfo, Var, Type, VarSet,
+        GoalContext, FailingContexts), Context, ModuleInfo, !IO) :-
     (
         GoalContext = switch,
         VarStr = mercury_var_to_string(Var, VarSet, no),
         Pieces0 = [words("In switch on variable `" ++ VarStr ++ "':"), nl]
     ;
         GoalContext = unify(UnifyContext),
-        hlds_out__unify_context_to_pieces(yes, _, UnifyContext, [], Pieces0)
+        hlds_out.unify_context_to_pieces(yes, _, UnifyContext, [], Pieces0)
     ),
     ( type_to_ctor_and_args(Type, TypeCtor, _TypeArgs) ->
-        TypeCtorStr = hlds_out__type_ctor_to_string(TypeCtor)
+        TypeCtorStr = hlds_out.type_ctor_to_string(TypeCtor)
     ;
         unexpected(this_file, "det_report_msg: type_to_ctor_and_args failed")
     ),
@@ -1316,7 +1374,7 @@
     FirstSpec = error_msg_spec(yes, Context, 0, FirstPieces),
     LaterSpecs = failing_contexts_description(ModuleInfo, VarSet,
         FailingContexts),
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         VerbosePieces = [words("Since the type has a user-defined"),
@@ -1338,9 +1396,8 @@
         globals.io_set_extra_error_info(yes, !IO),
         write_error_specs([FirstSpec | LaterSpecs], !IO)
     ).
-det_report_msg(cc_pred_in_wrong_context(GoalInfo, Detism, PredId, _ModeId,
-        VarSet, FailingContexts), ModuleInfo, !IO) :-
-    goal_info_get_context(GoalInfo, Context),
+det_report_msg(cc_pred_in_wrong_context(_GoalInfo, Detism, PredId,
+        _ModeId, VarSet, FailingContexts), Context, ModuleInfo, !IO) :-
     PredPieces = describe_one_pred_name(ModuleInfo,
         should_not_module_qualify, PredId),
     DetStr = mercury_det_to_string(Detism),
@@ -1351,9 +1408,8 @@
     LaterSpecs = failing_contexts_description(ModuleInfo, VarSet,
         FailingContexts),
     write_error_specs([FirstSpec | LaterSpecs], !IO).
-det_report_msg(higher_order_cc_pred_in_wrong_context(GoalInfo, Detism, VarSet,
-        FailingContexts), ModuleInfo, !IO) :-
-    goal_info_get_context(GoalInfo, Context),
+det_report_msg(higher_order_cc_pred_in_wrong_context(_GoalInfo, Detism,
+        VarSet, FailingContexts), Context, ModuleInfo, !IO) :-
     DetStr = mercury_det_to_string(Detism),
     FirstPieces = [words("Error: higher-order call to predicate with"),
         words("determinism `" ++ DetStr ++ "'"),
@@ -1362,11 +1418,10 @@
     LaterSpecs = failing_contexts_description(ModuleInfo, VarSet,
         FailingContexts),
     write_error_specs([FirstSpec | LaterSpecs], !IO).
-det_report_msg(error_in_lambda(DeclaredDetism, InferredDetism, Goal, GoalInfo,
-            PredId, ProcId), ModuleInfo, !IO) :-
+det_report_msg(error_in_lambda(DeclaredDetism, InferredDetism,
+        Goal, _GoalInfo, PredId, ProcId), Context, ModuleInfo, !IO) :-
     PredPieces = describe_one_proc_name_mode(ModuleInfo,
         should_not_module_qualify, proc(PredId, ProcId)),
-    goal_info_get_context(GoalInfo, Context),
     Pieces =
         [words("In")] ++ PredPieces ++ [suffix(":"), nl,
         words("Determinism error in lambda expression."), nl,
@@ -1374,16 +1429,15 @@
             ++ "', inferred `" ++ determinism_to_string(InferredDetism)
             ++ "'.")],
     ReportSpec = error_msg_spec(no, Context, 0, Pieces),
-    globals__io_get_globals(Globals, !IO),
+    globals.io_get_globals(Globals, !IO),
     module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
     proc_info_vartypes(ProcInfo, VarTypes),
     det_info_init(ModuleInfo, VarTypes, PredId, ProcId, Globals, DetInfo),
     det_diagnose_goal(Goal, DeclaredDetism, [], DetInfo, _,
         [ReportSpec], Specs),
     write_error_specs(Specs, !IO).
-det_report_msg(par_conj_not_det(InferredDetism, PredId,
-        ProcId, GoalInfo, Goals), ModuleInfo, !IO) :-
-    goal_info_get_context(GoalInfo, Context),
+det_report_msg(par_conj_not_det(InferredDetism, PredId, ProcId,
+        _GoalInfo, Goals), Context, ModuleInfo, !IO) :-
     determinism_components(InferredDetism, CanFail, MaxSoln),
     ( CanFail \= cannot_fail ->
         First = "Error: parallel conjunct may fail."
@@ -1396,32 +1450,29 @@
     Rest = "The current implementation supports only single-solution"
         ++ "non-failing parallel conjunctions.",
     ReportSpec = error_msg_spec(no, Context, 0, [words(First), words(Rest)]),
-    globals__io_get_globals(Globals, !IO),
+    globals.io_get_globals(Globals, !IO),
     module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
     proc_info_vartypes(ProcInfo, VarTypes),
     det_info_init(ModuleInfo, VarTypes, PredId, ProcId, Globals, DetInfo),
     det_diagnose_conj(Goals, det, [], DetInfo, _, [ReportSpec], Specs),
     write_error_specs(Specs, !IO).
-det_report_msg(pragma_c_code_without_det_decl(PredId, ProcId),
+det_report_msg(pragma_c_code_without_det_decl(PredId, ProcId), Context,
         ModuleInfo, !IO) :-
-    module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
-    proc_info_context(ProcInfo, Context),
     ProcPieces = describe_one_proc_name_mode(ModuleInfo,
         should_not_module_qualify, proc(PredId, ProcId)),
     Pieces = [words("In")] ++ ProcPieces ++ [suffix(":"), nl,
         words("error: `:- pragma c_code(...)' for a procedure"),
         words("without a determinism declaration.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(has_io_state_but_not_det(PredId, ProcId), ModuleInfo, !IO) :-
-    module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
-    proc_info_context(ProcInfo, Context),
+det_report_msg(has_io_state_but_not_det(PredId, ProcId), Context, ModuleInfo,
+        !IO) :-
     ProcPieces = describe_one_proc_name_mode(ModuleInfo,
         should_not_module_qualify, proc(PredId, ProcId)),
     Pieces = [words("In")] ++ ProcPieces ++ [suffix(":"), nl,
         words("error: invalid determinism for a predicate"),
         words("with I/O state arguments.")],
     write_error_pieces(Context, 0, Pieces, !IO),
-    globals__io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
+    globals.io_lookup_bool_option(verbose_errors, VerboseErrors, !IO),
     (
         VerboseErrors = yes,
         VerbosePieces = [words("Valid determinisms are "),
@@ -1431,10 +1482,8 @@
         VerboseErrors = no,
         globals.io_set_extra_error_info(yes, !IO)
     ).
-det_report_msg(will_not_throw_with_erroneous(PredId, ProcId), ModuleInfo,
-        !IO) :-
-    module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
-    proc_info_context(ProcInfo, Context),
+det_report_msg(will_not_throw_with_erroneous(PredId, ProcId), Context,
+        ModuleInfo, !IO) :-
     ProcPieces = describe_one_proc_name_mode(ModuleInfo,
         should_not_module_qualify, proc(PredId, ProcId)),
     Pieces = ProcPieces ++
@@ -1444,25 +1493,16 @@
         words("This attribute cannot be applied"),
         words("to erroneous procedures.")],
     write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(export_model_non_proc(PredId, ProcId, Detism), ModuleInfo,
-        !IO) :-
-    module_info_get_pragma_exported_procs(ModuleInfo, ExportedProcs),
-    (
-        get_exported_proc_context(ExportedProcs, PredId, ProcId, Context)
-    ->
+det_report_msg(export_model_non_proc(_PredId, _ProcId, Detism), Context,
+        _ModuleInfo, !IO) :-
         Pieces = [words("Error: "),
             fixed(":- pragma export' declaration"),
             words("for a procedure that has a determinism of"),
             fixed(hlds_out.determinism_to_string(Detism) ++ ",")
             ],
-        error_util.write_error_pieces(Context, 0, Pieces, !IO)
-    ;
-        unexpected(this_file,
-            "Cannot find proc in table of pragma exported procs")
-    ).
-det_report_msg(
-        promise_equivalent_solutions_missing_vars(Context, VarSet, Vars),
-        _, !IO) :-
+    write_error_pieces(Context, 0, Pieces, !IO).
+det_report_msg(promise_equivalent_solutions_missing_vars(VarSet, Vars),
+        Context, _, !IO) :-
     VarNames = list.map(lookup_var_name_in_varset(VarSet),
         set.to_sorted_list(Vars)),
     (
@@ -1479,7 +1519,7 @@
     Pieces = [words("Error: the promise_equivalent_solutions goal binds "),
           words(ListStr)] ++ list_to_pieces(VarNames) ++ [suffix(".")],
     error_util.write_error_pieces(Context, 0, Pieces, !IO).
-det_report_msg(promise_equivalent_solutions_extra_vars(Context, VarSet, Vars),
+det_report_msg(promise_equivalent_solutions_extra_vars(VarSet, Vars), Context,
         _, !IO) :-
     VarNames = list.map(lookup_var_name_in_varset(VarSet),
         set.to_sorted_list(Vars)),
@@ -1503,22 +1543,12 @@
 lookup_var_name_in_varset(VarSet, Var) =
     mercury_var_to_string(Var, VarSet, no).
 
-:- pred get_exported_proc_context(list(pragma_exported_proc)::in,
-    pred_id::in, proc_id::in, prog_context::out) is semidet.
-
-get_exported_proc_context([ Proc | Procs], PredId, ProcId, Context) :-
-    ( Proc = pragma_exported_proc(PredId, ProcId, _, Context0) ->
-        Context = Context0
-    ;
-        get_exported_proc_context(Procs, PredId, ProcId, Context)
-    ).
-
 :- func failing_contexts_description(module_info::in, prog_varset::in,
     list(failing_context)::in) =
     (list(error_msg_spec)::out(known_error_msg_specs)) is det.
 
 failing_contexts_description(ModuleInfo, VarSet, FailingContexts) =
-    list__map(failing_context_description(ModuleInfo, VarSet),
+    list.map(failing_context_description(ModuleInfo, VarSet),
         FailingContexts).
 
 :- func failing_context_description(module_info::in, prog_varset::in,
@@ -1552,7 +1582,7 @@
         Pieces = [words("Call to"), fixed(Name), words("can fail.")]
     ;
         FailingGoal = generic_call_goal(GenericCall),
-        hlds_goal__generic_call_id(GenericCall, CallId),
+        hlds_goal.generic_call_id(GenericCall, CallId),
         Pieces = [words(capitalize(call_id_to_string(CallId))),
             words("can fail.")]
     ;
@@ -1587,7 +1617,7 @@
 
 det_report_context_lines_2([], _) = "".
 det_report_context_lines_2([Context | Contexts], First) = Str :-
-    term__context_line(Context, Line),
+    term.context_line(Context, Line),
     ( First = yes ->
         Punct = ""
     ; Contexts = [] ->
@@ -1604,23 +1634,23 @@
 :- type options_to_restore == assoc_list(option, option_data).
 
 disable_det_warnings(OptionsToRestore, !IO) :-
-    globals__io_lookup_option(warn_simple_code, WarnSimple, !IO),
-    globals__io_lookup_option(warn_det_decls_too_lax,
+    globals.io_lookup_option(warn_simple_code, WarnSimple, !IO),
+    globals.io_lookup_option(warn_det_decls_too_lax,
         WarnDeclsTooLax, !IO),
-    globals__io_set_option(warn_simple_code, bool(no), !IO),
-    globals__io_set_option(warn_det_decls_too_lax, bool(no), !IO),
+    globals.io_set_option(warn_simple_code, bool(no), !IO),
+    globals.io_set_option(warn_det_decls_too_lax, bool(no), !IO),
     OptionsToRestore = [
         warn_simple_code - WarnSimple,
         warn_det_decls_too_lax - WarnDeclsTooLax
     ].
 
 restore_det_warnings(OptionsToRestore, !IO) :-
-    list__foldl(restore_option, OptionsToRestore, !IO).
+    list.foldl(restore_option, OptionsToRestore, !IO).
 
 :- pred restore_option(pair(option, option_data)::in, io::di, io::uo) is det.
 
 restore_option(Option - Value, !IO) :-
-    globals__io_set_option(Option, Value, !IO).
+    globals.io_set_option(Option, Value, !IO).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/fact_table.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/fact_table.m,v
retrieving revision 1.69
diff -u -b -r1.69 fact_table.m
--- compiler/fact_table.m	17 Nov 2005 15:57:11 -0000	1.69
+++ compiler/fact_table.m	25 Jan 2006 02:27:23 -0000
@@ -549,7 +549,7 @@
     ->
         Msg = "Type error in return value of function."
     ;
-        string__format("Type error in argument %s.", [i(ArgNum)], Msg)
+        string__format("Type error in argument %d.", [i(ArgNum)], Msg)
     ),
     add_error_report(Context, [words(Msg)], !Errors).
 
Index: compiler/format_call.m
===================================================================
RCS file: compiler/format_call.m
diff -N compiler/format_call.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ compiler/format_call.m	25 Jan 2006 02:02:02 -0000
@@ -0,0 +1,571 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2006 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: format_call.m.
+% Author: zs
+%
+% The job of this module is to generate warnings about calls to string.format
+% and io.format in which the format string and the supplied lists of values
+% do not agree. The difficult part of this job is actually finding the values
+% of the variables representing the format string and the list of values to
+% be printed.
+%
+% The general approach is a backwards traversal of the procedure body. During
+% this traversal, we assign an id to every conjunction (considering a cond and
+% then parts of an if-then-else to be a conjunction). When we find a call to
+% string.format or io.format, we remember the call site together with the
+% identities of the variables holding the format string and the values to
+% be printed, and include both variables in the set of variables whose values
+% we want to track. As we traverse unifications that bind variables we want to
+% track, we record their value in a map specific to the conjunction containing
+% the unification. Actually, we keep four such maps. Three record information
+% about bindings to function symbols: one for format strings, one for the
+% skeletons of the lists of values, and one for the elements of those lists.
+% The fourth map is for variable equivalences.
+%
+% We also record relationships between the conjunctions. Consider the code
+% structure below, which contains two relevant conjunctions: the outer one,
+% and the one containing the cond and then parts of the inner if-then-else.
+% Any attempt to trace the value of V2 requires also knowing the value of V1.
+% We therefore record that if you can't find the value of a variable such as V1
+% in the inner conjunction, you should continue the search in the outer
+% conjunction. We call this relationship "predecessor", since the only relevant
+% part of the outer conjunction is the one that appears before the inner one.
+% This is enforced by the mode system.
+%
+%   (
+%       ...,
+%       V1 = ...,
+%       ...,
+%       (
+%           ...
+%       ->
+%           V2 = ... V1 ...,
+%           string.format(..., V2, ...)
+%       ;
+%           V3 = ... V1 ...,
+%           string.format(..., V3, ...)
+%       ),
+%       ...
+%   )
+%
+% This design is about as cheap in terms of compilation time as we can make it.
+% Its cost has two components. The first component is the traversal, and its
+% cost is roughly proportional to the size of the procedure body. The second
+% cost is the checking of each call to string.format or io.format. The expected
+% complexity of this part is proportional to the number of such calls
+% multiplied by the average number of arguments they print. In the worst case,
+% this can be multiplied again by the number of conjunctions in the procedure
+% body, but I expect that in most cases the variables involved in the relevant
+% calls will be found in the same conjunction as the call itself, so the
+% typical number of conjunctions that has to be searched will in fact be one.
+%
+% Note that if the value of e.g. a format string is an input to the procedure 
+% or is computed by a call rather than a unification, we won't be able to check
+% whether the values match the format string. Whether we give a warning in such
+% cases is controlled by a separate option, which is consulted in det_report.m.
+%
+% We could in theory track e.g. format strings through calls to library
+% functions such as string.append. However, there is no convenient way to
+% evaluate the extent of a need for this capability until this change is
+% bootstrapped, so that is left for future work.
+%
+%-----------------------------------------------------------------------------%
+
+:- module check_hlds.format_call.
+:- interface.
+
+:- import_module check_hlds.det_report.
+:- import_module hlds.hlds_goal.
+:- import_module hlds.hlds_module.
+:- import_module parse_tree.prog_data.
+
+:- import_module mdbcomp.prim_data.
+
+:- import_module list.
+:- import_module set.
+
+:- pred is_format_call(module_name::in, string::in, list(prog_var)::in,
+    prog_var::out, prog_var::out) is semidet.
+
+:- pred find_format_call_errors(module_info::in, hlds_goal::in,
+    set(context_det_msg)::in, set(context_det_msg)::out) is det.
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module hlds.hlds_pred.
+:- import_module libs.compiler_util.
+
+:- import_module counter.
+:- import_module exception.
+:- import_module map.
+:- import_module require.
+:- import_module std_util.
+:- import_module string.
+:- import_module svmap.
+:- import_module svset.
+
+:- type format_call_site
+    --->    format_call_site(
+                format_string_var       :: prog_var,
+                formatted_values_var    :: prog_var,
+                called_pred_module      :: module_name,
+                called_pred_name        :: string,
+                called_pred_arity       :: arity,
+                call_context            :: prog_context,
+                containing_conj         :: conj_id
+            ).
+
+:- type list_skeleton_state
+    --->    list_skeleton_nil
+    ;       list_skeleton_cons(
+                head    :: prog_var,
+                tail    :: prog_var
+            ).
+
+    % Maps each variable representing a format string to the format string
+    % itself.
+:- type string_map          == map(prog_var, string).
+
+    % Maps each variable participating in the skeleton of the list of values to
+    % be printed to its value.
+:- type list_skeleton_map   == map(prog_var, list_skeleton_state).
+
+    % Maps each variable representing a value in the list of values to be
+    % printed to a dummy value of the same kind. We don't include the actual
+    % value to be printed, since (a) in almost all cases that won't be
+    % available statically in the program, and (b) we don't actually need it.
+:- type list_element_map    == map(prog_var, string.poly_type).
+
+    % Maps each variable defined in terms of another variable to the variable
+    % it is assigned from.
+:- type eqv_map             == map(prog_var, prog_var).
+
+    % The knowledge we have recorded from assign and construct unifications in
+    % a given conjunction.
+:- type conj_map
+    --->    conj_map(
+                string_map          :: string_map,
+                list_skeleton_map   :: list_skeleton_map,
+                list_element_map    :: list_element_map,
+                eqv_map             :: eqv_map
+            ).
+
+:- type conj_id
+    --->    conj_id(int).
+
+    % Maps the id of each conjunction to the knowledge we have derived from
+    % unifications in that conjunction.
+:- type conj_maps == map(conj_id, conj_map).
+
+    % Maps each conjunction to its predecessor (if any) in the sense documented
+    % above.
+:- type conj_pred_map == map(conj_id, conj_id).
+
+%-----------------------------------------------------------------------------%
+
+is_format_call(ModuleName, Name, Args, FormatStringVar, FormattedValuesVar) :-
+    Name = "format",
+    ( ModuleName = mercury_std_lib_module_name("string") ->
+        % We have these arguments regardless of whether we call the
+        % predicate or function version of string.format.
+        Args = [FormatStringVar, FormattedValuesVar, _ResultVar]
+    ; ModuleName = mercury_std_lib_module_name("io") ->
+        ( Args = [FormatStringVar, FormattedValuesVar, _IOIn, _IOOut]
+        ; Args = [_Stream, FormatStringVar, FormattedValuesVar, _IOIn, _IOOut]
+        )
+    ;
+        fail
+    ).
+
+%-----------------------------------------------------------------------------%
+
+find_format_call_errors(ModuleInfo, Goal, !Msgs) :-
+    map.init(ConjMaps0),
+    counter.init(0, Counter0),
+    traverse_goal(Goal, _, [], FormatCallSites, Counter0, _Counter,
+        ConjMaps0, ConjMaps, map.init, PredMap, set.init, _, ModuleInfo),
+    list.foldl(check_format_call_site(ConjMaps, PredMap), FormatCallSites,
+        !Msgs).
+
+:- pred check_format_call_site(conj_maps::in, conj_pred_map::in,
+    format_call_site::in, set(context_det_msg)::in, set(context_det_msg)::out)
+    is det.
+
+check_format_call_site(ConjMaps, PredMap, FormatCallSite, !Msgs) :-
+    FormatCallSite = format_call_site(StringVar, ValuesVar,
+        ModuleName, Name, Arity, Context, CurId),
+    SymName = qualified(ModuleName, Name),
+
+    (
+        follow_format_string(ConjMaps, PredMap, CurId, StringVar,
+            yes(FormatString0))
+    ->
+        MaybeFormatString = yes(FormatString0)
+    ;
+        MaybeFormatString = no,
+        StringMsg = unknown_format_string(SymName, Arity),
+        ContextStringMsg = context_det_msg(Context, StringMsg),
+        svset.insert(ContextStringMsg, !Msgs)
+    ),
+
+    (
+        follow_list(ConjMaps, PredMap, CurId, ValuesVar, yes(Skeleton)),
+        list.map(follow_list_value(ConjMaps, PredMap, CurId), Skeleton,
+            MaybeValueList),
+        project_all_yes(MaybeValueList, Values0)
+    ->
+        MaybeValues = yes(Values0)
+    ;
+        MaybeValues = no,
+        ValuesMsg = unknown_format_values(SymName, Arity),
+        ContextValuesMsg = context_det_msg(Context, ValuesMsg),
+        svset.insert(ContextValuesMsg, !Msgs)
+    ),
+
+    (
+        MaybeFormatString = yes(FormatString),
+        MaybeValues = yes(Values)
+    ->
+        promise_equivalent_solutions [Result] (
+            try(string.format(FormatString, Values), Result)
+        ),
+        (
+            Result = exception(ExceptionUniv),
+            ( univ_to_type(ExceptionUniv, ExceptionError) ->
+                ExceptionError = software_error(ExceptionMsg0),
+                ( string.append("string.format: ", Msg, ExceptionMsg0) ->
+                    ExceptionMsg = Msg
+                ;
+                    ExceptionMsg = ExceptionMsg0
+                ),
+                BadMsg = bad_format(SymName, Arity, ExceptionMsg),
+                ContextBadMsg = context_det_msg(Context, BadMsg),
+                svset.insert(ContextBadMsg, !Msgs)
+            ;
+                % We can't decode arbitrary exception values, but string.m
+                % shouldn't throw anything but software_errors, so ignoring
+                % the exception should be ok.
+                true
+            )
+        ;
+            % There is no need for any error message; the format works.
+            Result = succeeded(_)
+        )
+    ;
+        % Any error message has already been generated, if asked for.
+        true
+    ).
+
+:- pred follow_format_string(conj_maps::in, conj_pred_map::in, conj_id::in,
+    prog_var::in, maybe(string)::out) is det.
+
+follow_format_string(ConjMaps, PredMap, CurId, StringVar, MaybeString) :-
+    ConjMap = get_conj_map(ConjMaps, CurId),
+    ConjMap = conj_map(StringMap, _, _, EqvMap),
+    ( map.search(EqvMap, StringVar, EqvVar) ->
+        follow_format_string(ConjMaps, PredMap, CurId, EqvVar, MaybeString)
+    ; map.search(StringMap, StringVar, String) ->
+        MaybeString = yes(String)
+    ; map.search(PredMap, CurId, PredId) ->
+        follow_format_string(ConjMaps, PredMap, PredId, StringVar, MaybeString)
+    ;
+        MaybeString = no
+    ).
+
+:- pred follow_list(conj_maps::in, conj_pred_map::in, conj_id::in,
+    prog_var::in, maybe(list(prog_var))::out) is det.
+
+follow_list(ConjMaps, PredMap, CurId, ListVar, MaybeSkeleton) :-
+    ConjMap = get_conj_map(ConjMaps, CurId),
+    ConjMap = conj_map(_, ListMap, _, EqvMap),
+    ( map.search(EqvMap, ListVar, EqvVar) ->
+        follow_list(ConjMaps, PredMap, CurId, EqvVar, MaybeSkeleton)
+    ; map.search(ListMap, ListVar, ListState) ->
+        (
+            ListState = list_skeleton_nil,
+            Skeleton = [],
+            MaybeSkeleton = yes(Skeleton)
+        ;
+            ListState = list_skeleton_cons(HeadVar, TailVar),
+            follow_list(ConjMaps, PredMap, CurId, TailVar, MaybeSkeletonTail),
+            (
+                MaybeSkeletonTail = no,
+                MaybeSkeleton = no
+            ;
+                MaybeSkeletonTail = yes(SkeletonTail),
+                Skeleton = [HeadVar | SkeletonTail],
+                MaybeSkeleton = yes(Skeleton)
+            )
+        )
+    ; map.search(PredMap, CurId, PredId) ->
+        follow_list(ConjMaps, PredMap, PredId, ListVar, MaybeSkeleton)
+    ;
+        MaybeSkeleton = no
+    ).
+
+:- pred follow_list_value(conj_maps::in, conj_pred_map::in, conj_id::in,
+    prog_var::in, maybe(string.poly_type)::out) is det.
+
+follow_list_value(ConjMaps, PredMap, CurId, ElementVar, MaybeValue) :-
+    ConjMap = get_conj_map(ConjMaps, CurId),
+    ConjMap = conj_map(_, _, ElementMap, EqvMap),
+    ( map.search(EqvMap, ElementVar, EqvVar) ->
+        follow_list_value(ConjMaps, PredMap, CurId, EqvVar, MaybeValue)
+    ; map.search(ElementMap, ElementVar, Value) ->
+        MaybeValue = yes(Value)
+    ; map.search(PredMap, CurId, PredId) ->
+        follow_list_value(ConjMaps, PredMap, PredId, ElementVar, MaybeValue)
+    ;
+        MaybeValue = no
+    ).
+
+:- pred project_all_yes(list(maybe(T))::in, list(T)::out) is semidet.
+
+project_all_yes([], []).
+project_all_yes([yes(Value) | TailMaybes], [Value | Tail]) :-
+    project_all_yes(TailMaybes, Tail).
+
+%-----------------------------------------------------------------------------%
+
+:- pred traverse_goal(hlds_goal::in, conj_id::out,
+    list(format_call_site)::in, list(format_call_site)::out,
+    counter::in, counter::out, conj_maps::in, conj_maps::out,
+    conj_pred_map::in, conj_pred_map::out,
+    set(prog_var)::in, set(prog_var)::out, module_info::in) is det.
+
+traverse_goal(Goal, CurId, !FormatCallSites, !Counter, !ConjMaps, !PredMap,
+        !RelevantVars, ModuleInfo) :-
+    alloc_id(CurId, !Counter),
+    goal_to_conj_list(Goal, GoalConj),
+    traverse_conj(GoalConj, CurId, !FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, !RelevantVars, ModuleInfo).
+
+:- pred traverse_conj(list(hlds_goal)::in, conj_id::in,
+    list(format_call_site)::in, list(format_call_site)::out,
+    counter::in, counter::out, conj_maps::in, conj_maps::out,
+    conj_pred_map::in, conj_pred_map::out,
+    set(prog_var)::in, set(prog_var)::out, module_info::in) is det.
+
+traverse_conj([], _CurId, !FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, !RelevantVars, _ModuleInfo).
+traverse_conj([Goal | Goals], CurId, !FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, !RelevantVars, ModuleInfo) :-
+    traverse_conj(Goals, CurId, !FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, !RelevantVars, ModuleInfo),
+    Goal = GoalExpr - GoalInfo,
+    (
+        GoalExpr = conj(Conjuncts),
+        traverse_conj(Conjuncts, CurId, !FormatCallSites, !Counter,
+            !ConjMaps, !PredMap, !RelevantVars, ModuleInfo)
+    ;
+        GoalExpr = par_conj(Conjuncts),
+        traverse_conj(Conjuncts, CurId, !FormatCallSites, !Counter,
+            !ConjMaps, !PredMap, !RelevantVars, ModuleInfo)
+    ;
+        GoalExpr = disj(Disjuncts),
+        traverse_disj(Disjuncts, CurId, !FormatCallSites, !Counter,
+            !ConjMaps, !PredMap, !RelevantVars, ModuleInfo)
+    ;
+        GoalExpr = switch(_, _, Cases),
+        Disjuncts = list.map(project_case_goal, Cases),
+        traverse_disj(Disjuncts, CurId, !FormatCallSites, !Counter,
+            !ConjMaps, !PredMap, !RelevantVars, ModuleInfo)
+    ;
+        GoalExpr = if_then_else(_, Cond, Then, Else),
+
+        traverse_goal(Else, ElseId, !FormatCallSites, !Counter, !ConjMaps,
+            !PredMap, !RelevantVars, ModuleInfo),
+        svmap.det_insert(ElseId, CurId, !PredMap),
+
+        alloc_id(CondThenId, !Counter),
+        goal_to_conj_list(Then, ThenConj),
+        goal_to_conj_list(Cond, CondConj),
+        traverse_conj(CondConj ++ ThenConj, CondThenId, !FormatCallSites,
+            !Counter, !ConjMaps, !PredMap, !RelevantVars, ModuleInfo),
+        svmap.det_insert(CondThenId, CurId, !PredMap)
+    ;
+        GoalExpr = not(SubGoal),
+        traverse_goal(SubGoal, SubGoalId, !FormatCallSites,
+            !Counter, !ConjMaps, !PredMap, !RelevantVars, ModuleInfo),
+        svmap.det_insert(SubGoalId, CurId, !PredMap)
+    ;
+        GoalExpr = scope(_, SubGoal),
+        traverse_conj([SubGoal], CurId, !FormatCallSites, !Counter,
+            !ConjMaps, !PredMap, !RelevantVars, ModuleInfo)
+    ;
+        GoalExpr = generic_call(_, _, _, _)
+    ;
+        GoalExpr = foreign_proc(_, _, _, _, _, _)
+    ;
+        GoalExpr = call(PredId, _ProcId, Args, _, _, _),
+        module_info_pred_info(ModuleInfo, PredId, PredInfo),
+        ModuleName = pred_info_module(PredInfo),
+        Name = pred_info_name(PredInfo),
+        ( is_format_call(ModuleName, Name, Args, StringVar, ValuesVar) ->
+            Arity = pred_info_orig_arity(PredInfo),
+            goal_info_get_context(GoalInfo, Context),
+            FormatCallSite = format_call_site(StringVar, ValuesVar,
+                ModuleName, Name, Arity, Context, CurId),
+            !:FormatCallSites = [FormatCallSite | !.FormatCallSites],
+            svset.insert_list([StringVar, ValuesVar], !RelevantVars)
+        ;
+            true
+        )
+    ;
+        GoalExpr = unify(_, _, _, Unification, _),
+        traverse_unify(Unification, CurId, !ConjMaps, !PredMap, !RelevantVars)
+    ;
+        GoalExpr = shorthand(_),
+        % These should have been expanded by now.
+        unexpected(this_file, "traverse_conj: shorthand")
+    ).
+
+:- pred traverse_unify(unification::in, conj_id::in,
+    conj_maps::in, conj_maps::out, conj_pred_map::in, conj_pred_map::out,
+    set(prog_var)::in, set(prog_var)::out) is det.
+
+traverse_unify(Unification, CurId, !ConjMaps, !PredMap, !RelevantVars) :-
+    (
+        Unification = assign(TargetVar, SourceVar),
+        ( set.member(TargetVar, !.RelevantVars) ->
+            svset.delete(TargetVar, !RelevantVars),
+            svset.insert(SourceVar, !RelevantVars),
+            ConjMap0 = get_conj_map(!.ConjMaps, CurId),
+            ConjMap0 = conj_map(StringMap, ListMap, ElementMap, EqvMap0),
+            map.set(EqvMap0, TargetVar, SourceVar, EqvMap),
+            ConjMap = conj_map(StringMap, ListMap, ElementMap, EqvMap),
+            svmap.set(CurId, ConjMap, !ConjMaps)
+        ;
+            true
+        )
+    ;
+        Unification = construct(CellVar, ConsId, ArgVars, _, _, _, _),
+        ( set.member(CellVar, !.RelevantVars) ->
+            ConjMap0 = get_conj_map(!.ConjMaps, CurId),
+            ConjMap0 = conj_map(StringMap0, ListMap0, ElementMap0, EqvMap0),
+            (
+                ConsId = string_const(StringConst)
+            ->
+                svset.delete(CellVar, !RelevantVars),
+                map.set(StringMap0, CellVar, StringConst, StringMap),
+                ConjMap = conj_map(StringMap, ListMap0, ElementMap0, EqvMap0)
+            ;
+                ConsId = cons(SymName, _Arity),
+                StringModule = mercury_std_lib_module_name("list"),
+                SymName = qualified(StringModule, Functor),
+                (
+                    Functor = "[|]",
+                    ArgVars = [ArgVar1, ArgVar2],
+                    List = list_skeleton_cons(ArgVar1, ArgVar2)
+                ;
+                    Functor = "[]",
+                    ArgVars = [],
+                    List = list_skeleton_nil
+                )
+            ->
+                svset.delete(CellVar, !RelevantVars),
+                svset.insert_list(ArgVars, !RelevantVars),
+                map.set(ListMap0, CellVar, List, ListMap),
+                ConjMap = conj_map(StringMap0, ListMap, ElementMap0, EqvMap0)
+            ;
+                ConsId = cons(SymName, Arity),
+                Arity = 1,
+                StringModule = mercury_std_lib_module_name("string"),
+                SymName = qualified(StringModule, Functor),
+                (
+                    Functor = "f",
+                    PolyType = f(0.0)
+                ;
+                    Functor = "i",
+                    PolyType = i(0)
+                ;
+                    Functor = "s",
+                    PolyType = s("0")
+                ;
+                    Functor = "c",
+                    PolyType = c('0')
+                )
+            ->
+                svset.delete(CellVar, !RelevantVars),
+                map.set(ElementMap0, CellVar, PolyType, ElementMap),
+                ConjMap = conj_map(StringMap0, ListMap0, ElementMap, EqvMap0)
+            ;
+                ConjMap = ConjMap0
+            ),
+            svmap.set(CurId, ConjMap, !ConjMaps)
+        ;
+            true
+        )
+    ;
+        Unification = deconstruct(_, _, _, _, _, _)
+    ;
+        Unification = simple_test(_, _)
+    ;
+        Unification = complicated_unify(_, _, _)
+    ).
+
+:- func project_case_goal(case) = hlds_goal.
+
+project_case_goal(case(_, Goal)) = Goal.
+
+:- pred traverse_disj(list(hlds_goal)::in, conj_id::in,
+    list(format_call_site)::in, list(format_call_site)::out,
+    counter::in, counter::out, conj_maps::in, conj_maps::out,
+    conj_pred_map::in, conj_pred_map::out,
+    set(prog_var)::in, set(prog_var)::out, module_info::in) is det.
+
+traverse_disj(Disjuncts, CurId, !FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, !RelevantVars, ModuleInfo) :-
+    traverse_disj_arms(Disjuncts, CurId, DisjFormatCallSitesLists,
+        !Counter, !ConjMaps, !PredMap, DisjRelevantVarSets, ModuleInfo),
+    list.condense(DisjFormatCallSitesLists, DisjFormatCallSites),
+    !:FormatCallSites = !.FormatCallSites ++ DisjFormatCallSites,
+    DisjRelevantVars = set.union_list(DisjRelevantVarSets),
+    set.union(DisjRelevantVars, !RelevantVars).
+
+:- pred traverse_disj_arms(list(hlds_goal)::in, conj_id::in,
+    list(list(format_call_site))::out,
+    counter::in, counter::out, conj_maps::in, conj_maps::out,
+    conj_pred_map::in, conj_pred_map::out, list(set(prog_var))::out,
+    module_info::in) is det.
+
+traverse_disj_arms([], _, [], !Counter, !ConjMaps, !PredMap, [], _).
+traverse_disj_arms([Goal | Goals], ContainingId,
+        [FormatCallSites | FormatCallSitesTail], !Counter,
+        !ConjMaps, !PredMap, [RelevantVars | RelevantVarSets], ModuleInfo) :-
+    traverse_goal(Goal, DisjId, [], FormatCallSites, !Counter,
+        !ConjMaps, !PredMap, set.init, RelevantVars, ModuleInfo),
+    svmap.det_insert(DisjId, ContainingId, !PredMap),
+    traverse_disj_arms(Goals, ContainingId, FormatCallSitesTail, !Counter,
+        !ConjMaps, !PredMap, RelevantVarSets, ModuleInfo).
+
+:- func get_conj_map(conj_maps, conj_id) = conj_map.
+
+get_conj_map(ConjMaps, ConjId) = ConjMap :-
+    ( map.search(ConjMaps, ConjId, ConjMapPrime) ->
+        ConjMap = ConjMapPrime
+    ;
+        ConjMap = conj_map(map.init, map.init, map.init, map.init)
+    ).
+
+:- pred alloc_id(conj_id::out, counter::in, counter::out) is det.
+
+alloc_id(ConjId, !Counter) :-
+    counter.allocate(N, !Counter),
+    ConjId = conj_id(N).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "format_call.m".
+
+%-----------------------------------------------------------------------------%
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.249
diff -u -b -r1.249 handle_options.m
--- compiler/handle_options.m	13 Jan 2006 05:07:34 -0000	1.249
+++ compiler/handle_options.m	24 Jan 2006 07:43:35 -0000
@@ -496,7 +496,6 @@
                 true
             ),
 
-
             % On the .NET backend we will be using a language independent
             % debugger not mdb.  Thus --debug has to imply --target-debug.
             ( given_trace_level_is_none(TraceLevel) = no ->
@@ -649,11 +648,12 @@
         % set of all possible linkages.
         globals__lookup_accumulating_option(!.Globals, lib_linkages,
             LibLinkages0),
-        ( LibLinkages0 = [] ->
+        (
+            LibLinkages0 = [],
             globals__set_option(lib_linkages,
                 accumulating(["static", "shared"]), !Globals)
         ;
-            true
+            LibLinkages0 = [_ | _]
         ),
 
         % make.m controls generating object code and linking itself,
@@ -2013,10 +2013,8 @@
 	% NOTE: .picreg components are handled separately.
 	% (see compute_grade_components/3). 
 	%  
-
 :- pred grade_component_table(string, grade_component,
-    list(pair(option, option_data)), maybe(list(option_data)),
-    bool).
+    list(pair(option, option_data)), maybe(list(option_data)), bool).
 :- mode grade_component_table(in, out, out, out, out) is semidet.
 :- mode grade_component_table(out, in, out, out, out) is multi.
 :- mode grade_component_table(out, out, out, out, out) is multi.
Index: compiler/mlds_to_il.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mlds_to_il.m,v
retrieving revision 1.156
diff -u -b -r1.156 mlds_to_il.m
--- compiler/mlds_to_il.m	28 Nov 2005 04:11:48 -0000	1.156
+++ compiler/mlds_to_il.m	25 Jan 2006 02:59:32 -0000
@@ -1322,7 +1322,7 @@
 mangle_dataname(var(MLDSVarName))
     = mangle_mlds_var_name(MLDSVarName).
 mangle_dataname(common(Int))
-    = string__format("common_%s", [i(Int)]).
+    = string__format("common_%d", [i(Int)]).
 mangle_dataname(rtti(RttiId)) = MangledName :-
     rtti__id_to_c_identifier(RttiId, MangledName).
 mangle_dataname(module_layout) = _MangledName :-
@@ -3388,7 +3388,7 @@
 mangle_dataname(var(MLDSVarName), Name) :-
     Name = mangle_mlds_var_name(MLDSVarName).
 mangle_dataname(common(Int), MangledName) :-
-    string__format("common_%s", [i(Int)], MangledName).
+    string__format("common_%d", [i(Int)], MangledName).
 mangle_dataname(rtti(RttiId), MangledName) :-
     rtti__id_to_c_identifier(RttiId, MangledName).
 mangle_dataname(module_layout, _MangledName) :-
Index: compiler/options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.489
diff -u -b -r1.489 options.m
--- compiler/options.m	11 Jan 2006 07:11:01 -0000	1.489
+++ compiler/options.m	25 Jan 2006 02:01:10 -0000
@@ -106,6 +106,8 @@
     ;       warn_dead_procs
     ;       warn_table_with_inline
     ;       warn_non_term_special_preds
+    ;       warn_known_bad_format_calls
+    ;       warn_unknown_format_calls
 
     % Verbosity options
     ;       verbose
@@ -849,7 +851,9 @@
     warn_stubs                          -   bool(yes),
     warn_dead_procs                     -   bool(no),
     warn_table_with_inline              -   bool(yes),
-    warn_non_term_special_preds         -   bool(yes)
+    warn_non_term_special_preds         -   bool(yes),
+    warn_known_bad_format_calls         -   bool(yes),
+    warn_unknown_format_calls           -   bool(no)
 ]).
 option_defaults_2(verbosity_option, [
     % Verbosity Options
@@ -1547,6 +1551,8 @@
 long_option("warn-dead-procs",          warn_dead_procs).
 long_option("warn-table-with-inline",   warn_table_with_inline).
 long_option("warn-non-term-special-preds", warn_non_term_special_preds).
+long_option("warn-known-bad-format-calls", warn_known_bad_format_calls).
+long_option("warn-unknown-format-calls", warn_unknown_format_calls).
 
 % verbosity options
 long_option("verbose",                  verbose).
@@ -2818,7 +2824,15 @@
         "\tcomparison predicates, or solver type initialisation predicates",
         "\tthat cannot be proved to terminate.  This option is only",
         "\tenabled when termination analysis is enabled.",
-        "\t(See the ""Termination Analysis Options"" section below)."
+        "\t(See the ""Termination Analysis Options"" section below).",
+        "--no-warn-known-bad-format-call",
+        "\tDo not warn about calls to string.format or io.format that",
+        "\tthe compiler knows for sure contain mismatches between the format",
+        "\tstring and the supplied values.",
+        "--warn-unknown-format-call",
+        "\tWarn about calls to string.format or io.format for which",
+        "\tthe compiler cannot tell whether there are any mismatches between",
+        "\tthe format string and the supplied values."
     ]).
 
 :- pred options_help_verbosity(io::di, io::uo) is det.
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.161
diff -u -b -r1.161 simplify.m
--- compiler/simplify.m	17 Nov 2005 15:57:30 -0000	1.161
+++ compiler/simplify.m	24 Jan 2006 07:42:54 -0000
@@ -56,7 +56,7 @@
 
 :- pred simplify_proc_return_msgs(list(simplification)::in, pred_id::in,
     proc_id::in, module_info::in, module_info::out,
-    proc_info::in, proc_info::out, set(det_msg)::out) is det.
+    proc_info::in, proc_info::out, set(context_det_msg)::out) is det.
 
 :- pred process_goal(hlds_goal::in, hlds_goal::out,
     simplify_info::in, simplify_info::out) is det.
@@ -71,6 +71,8 @@
 :- type simplification
     --->    warn_simple_code        % --warn-simple-code
     ;       warn_duplicate_calls    % --warn-duplicate-calls
+    ;       warn_known_bad_format   % --warn-known-bad-format-calls
+    ;       warn_unknown_format     % --warn-unknown-format-calls
     ;       do_once                 % run things that should be done once
     ;       excess_assigns          % remove excess assignment unifications
     ;       duplicate_calls         % optimize duplicate calls
@@ -89,6 +91,7 @@
 :- implementation.
 
 :- import_module check_hlds.det_analysis.
+:- import_module check_hlds.format_call.
 :- import_module check_hlds.inst_match.
 :- import_module check_hlds.modes.
 :- import_module check_hlds.mode_util.
@@ -158,7 +161,8 @@
 :- pred simplify_procs(list(simplification)::in, pred_id::in,
     list(proc_id)::in, module_info::in, module_info::out,
     pred_info::in, pred_info::out,
-    maybe(pair(set(det_msg)))::in, maybe(pair(set(det_msg)))::out) is det.
+    maybe(pair(set(context_det_msg)))::in,
+    maybe(pair(set(context_det_msg)))::out) is det.
 
 simplify_procs(_, _, [], !ModuleInfo, !PredInfo, !Msgs).
 simplify_procs(Simplifications, PredId, [ProcId | ProcIds], !ModuleInfo,
@@ -170,7 +174,7 @@
     map__det_update(Procs0, ProcId, Proc, Procs),
     pred_info_set_procedures(Procs, !PredInfo),
     set__to_sorted_list(ProcMsgSet, ProcMsgs),
-    list__filter((pred(Msg::in) is semidet :-
+    list__filter((pred(context_det_msg(_, Msg)::in) is semidet :-
             det_msg_is_any_mode_msg(Msg, any_mode)
         ), ProcMsgs, ProcAnyModeMsgs, ProcAllModeMsgs),
     set__sorted_list_to_set(ProcAnyModeMsgs, ProcAnyModeMsgSet),
@@ -193,7 +197,7 @@
         !Proc, _).
 
 simplify_proc_return_msgs(Simplifications, PredId, ProcId, !ModuleInfo,
-        !ProcInfo, Msgs) :-
+        !ProcInfo, DetMsgs) :-
     module_info_get_globals(!.ModuleInfo, Globals),
     proc_info_vartypes(!.ProcInfo, VarTypes0),
     det_info_init(!.ModuleInfo, VarTypes0, PredId, ProcId, Globals,
@@ -227,7 +231,38 @@
     proc_info_set_goal(Goal, !ProcInfo),
     proc_info_set_rtti_varmaps(RttiVarMaps, !ProcInfo),
     simplify_info_get_module_info(Info, !:ModuleInfo),
-    simplify_info_get_msgs(Info, Msgs).
+    simplify_info_get_det_msgs(Info, DetMsgs0),
+    (
+        Info ^ format_calls = yes,
+        (
+            list.member(warn_known_bad_format, Simplifications)
+        ;
+            list.member(warn_unknown_format, Simplifications)
+        )
+    ->
+        % We must use the original goal, Goal0, here. This is because excess
+        % assignment optimization may delete some of the unifications that
+        % build the format strings or values, which means that the new version
+        % in Goal may not contain the information find_format_call_errors needs
+        % to avoid spurious messages about unknown format strings or values.
+        find_format_call_errors(!.ModuleInfo, Goal0, DetMsgs0, DetMsgs1)
+    ;
+        % Either there are no calls to check or we would ignore the added
+        % messages anyway.
+        DetMsgs1 = DetMsgs0
+    ),
+    pred_info_import_status(PredInfo, Status),
+    status_defined_in_this_module(Status, IsDefinedHere),
+    (
+        IsDefinedHere = no,
+        % Don't generate any warnings or even errors if the predicate isn't
+        % defined here; any such messages will be generated when we compile
+        % the module the predicate comes from.
+        set.init(DetMsgs)
+    ;
+        IsDefinedHere = yes,
+        DetMsgs = DetMsgs1
+    ).
 
 process_goal(Goal0, Goal, !Info) :-
     simplify_info_get_simplifications(!.Info, Simplifications0),
@@ -327,22 +362,26 @@
 find_simplifications_2(WarnThisPass, Globals, !Simps) :-
     (
         WarnThisPass = yes,
-        lookup_option(Globals, warn_duplicate_calls,
+        set_by_option(Globals, warn_duplicate_calls,
             warn_duplicate_calls, !Simps),
-        lookup_option(Globals, warn_simple_code,
-            warn_simple_code, !Simps)
+        set_by_option(Globals, warn_simple_code,
+            warn_simple_code, !Simps),
+        set_by_option(Globals, warn_known_bad_format_calls,
+            warn_known_bad_format, !Simps),
+        set_by_option(Globals, warn_unknown_format_calls,
+            warn_unknown_format, !Simps)
     ;
         WarnThisPass = no
     ),
-    lookup_option(Globals, excess_assign, excess_assigns, !Simps),
-    lookup_option(Globals, common_struct, common_struct, !Simps),
-    lookup_option(Globals, optimize_duplicate_calls, duplicate_calls, !Simps),
-    lookup_option(Globals, constant_propagation, constant_prop, !Simps).
+    set_by_option(Globals, excess_assign, excess_assigns, !Simps),
+    set_by_option(Globals, common_struct, common_struct, !Simps),
+    set_by_option(Globals, optimize_duplicate_calls, duplicate_calls, !Simps),
+    set_by_option(Globals, constant_propagation, constant_prop, !Simps).
 
-:- pred lookup_option(globals::in, option::in, simplification::in,
+:- pred set_by_option(globals::in, option::in, simplification::in,
     list(simplification)::in, list(simplification)::out) is det.
 
-lookup_option(Globals, Option, Simplification, !Simplifications) :-
+set_by_option(Globals, Option, Simplification, !Simplifications) :-
     globals__lookup_bool_option(Globals, Option, Result),
     (
         Result = yes,
@@ -383,7 +422,9 @@
                 SubGoal = disj([]) - _
             )
         ->
-            simplify_info_add_msg(goal_cannot_succeed(Context), !Info)
+            Msg = goal_cannot_succeed,
+            ContextMsg = context_det_msg(Context, Msg),
+            simplify_info_add_det_msg(ContextMsg, !Info)
         ;
             true
         ),
@@ -447,8 +488,9 @@
 %           \+ (Goal0 = unify(_, _, _, Unification, _) - _,
 %               Unification = deconstruct(_, _, _, _, _))
 %       ->
-%           simplify_info_add_msg(det_goal_has_no_outputs(Context),
-%               !Info)
+%           Msg = det_goal_has_no_outputs,
+%           ContextMsg = context_det_msg(Context, Msg),
+%           simplify_info_add_det_msg(ContextMsg, !Info)
 %       ;
 %           true
 %       ),
@@ -769,14 +811,20 @@
     Goal0 = call(PredId, ProcId, Args, IsBuiltin, _, _),
     simplify_info_get_module_info(!.Info, ModuleInfo),
     module_info_pred_info(ModuleInfo, PredId, PredInfo),
+    ModuleName = hlds_pred__pred_info_module(PredInfo),
+    Name = hlds_pred__pred_info_name(PredInfo),
+    ( is_format_call(ModuleName, Name, Args, _, _) ->
+        simplify_info_set_format_calls(yes, !Info)
+    ;
+        true
+    ),
     %
     % Convert calls to builtin @=<, @<, @>=, @> into the corresponding
     % calls to builtin__compare/3.
     %
     (
         Args = [TI, X, Y],
-        mercury_public_builtin_module = hlds_pred__pred_info_module(PredInfo),
-        Name = hlds_pred__pred_info_name(PredInfo),
+        ModuleName = mercury_public_builtin_module,
         ( Name =  "@<", Inequality = "<", Invert = no
         ; Name = "@=<", Inequality = ">", Invert = yes
         ; Name = "@>=", Inequality = "<", Invert = yes
@@ -896,7 +944,9 @@
         list__append(CondList, ThenList, List),
         simplify_goal(conj(List) - GoalInfo0, Goal - GoalInfo, !Info),
         goal_info_get_context(GoalInfo0, Context),
-        simplify_info_add_msg(ite_cond_cannot_fail(Context), !Info),
+        Msg = ite_cond_cannot_fail,
+        ContextMsg = context_det_msg(Context, Msg),
+        simplify_info_add_det_msg(ContextMsg, !Info),
         simplify_info_set_requantify(!Info),
         simplify_info_set_rerun_det(!Info)
     ; CondSolns0 = at_most_zero ->
@@ -937,7 +987,9 @@
         List = [Cond | ElseList],
         simplify_goal(conj(List) - GoalInfo0, Goal - GoalInfo, !Info),
         goal_info_get_context(GoalInfo0, Context),
-        simplify_info_add_msg(ite_cond_cannot_succeed(Context), !Info),
+        Msg = ite_cond_cannot_succeed,
+        ContextMsg = context_det_msg(Context, Msg),
+        simplify_info_add_det_msg(ContextMsg, !Info),
         simplify_info_set_requantify(!Info),
         simplify_info_set_rerun_det(!Info)
     ; Else0 = disj([]) - _ ->
@@ -1032,9 +1084,13 @@
     determinism_components(Detism, CanFail, MaxSoln),
     goal_info_get_context(GoalInfo0, Context),
     ( CanFail = cannot_fail ->
-        simplify_info_add_msg(negated_goal_cannot_fail(Context), !Info)
+        Msg = negated_goal_cannot_fail,
+        ContextMsg = context_det_msg(Context, Msg),
+        simplify_info_add_det_msg(ContextMsg, !Info)
     ; MaxSoln = at_most_zero ->
-        simplify_info_add_msg(negated_goal_cannot_succeed(Context), !Info)
+        Msg = negated_goal_cannot_succeed,
+        ContextMsg = context_det_msg(Context, Msg),
+        simplify_info_add_det_msg(ContextMsg, !Info)
     ;
         true
     ),
@@ -1221,9 +1277,10 @@
         det_info_get_pred_id(DetInfo0, ThisPredId),
         PredId \= ThisPredId
     ->
-
         goal_info_get_context(GoalInfo0, Context1),
-        simplify_info_add_msg(warn_obsolete(PredId, Context1), !Info)
+        ObsoleteMsg = warn_obsolete(PredId),
+        ObsoleteContextMsg = context_det_msg(Context1, ObsoleteMsg),
+        simplify_info_add_det_msg(ObsoleteContextMsg, !Info)
     ;
         true
     ),
@@ -1293,7 +1350,9 @@
         \+ hlds_pred__pred_info_is_aditi_relation(PredInfo1)
     ->
         goal_info_get_context(GoalInfo0, Context2),
-        simplify_info_add_msg(warn_infinite_recursion(Context2), !Info)
+        InfiniteRecMsg = warn_infinite_recursion,
+        InfiniteRecContextMsg = context_det_msg(Context2, InfiniteRecMsg),
+        simplify_info_add_det_msg(InfiniteRecContextMsg, !Info)
     ;
         true
     ),
@@ -2018,7 +2077,9 @@
             Goal0 \= disj([]) - _
         ->
             goal_info_get_context(GoalInfo, Context),
-            simplify_info_add_msg(zero_soln_disjunct(Context), !Info)
+            Msg = zero_soln_disjunct,
+            ContextMsg = context_det_msg(Context, Msg),
+            simplify_info_add_det_msg(ContextMsg, !Info)
         ;
             true
         ),
@@ -2159,10 +2220,10 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type simplify_info --->
-    simplify_info(
+:- type simplify_info
+    --->    simplify_info(
         det_info                :: det_info,
-        msgs                    :: set(det_msg),
+                msgs                    :: set(context_det_msg),
         simplifications         :: set(simplification),
         common_info             :: common_info,
                                 % Info about common subexpressions.
@@ -2183,9 +2244,12 @@
         lambdas                 :: int,
                                 % Count of the number of lambdas
                                 % which enclose the current goal.
-        rtti_varmaps            :: rtti_varmaps
+                rtti_varmaps            :: rtti_varmaps,
                                 % Information about type_infos and
                                 % typeclass_infos.
+                format_calls            :: bool
+                                        % Do we have any calls to
+                                        % string.format and io.format?
     ).
 
 simplify_info_init(DetInfo, Simplifications, InstMap, ProcInfo, Info) :-
@@ -2196,9 +2260,10 @@
     set__list_to_set(Simplifications, SimplificationsSet),
     Info = simplify_info(DetInfo, Msgs, SimplificationsSet,
         common_info_init, InstMap, VarSet, InstVarSet,
-        no, no, no, 0, 0, RttiVarMaps).
+        no, no, no, 0, 0, RttiVarMaps, no).
 
     % Reinitialise the simplify_info before reprocessing a goal.
+    %
 :- pred simplify_info_reinit(set(simplification)::in, instmap::in,
     simplify_info::in, simplify_info::out) is det.
 
@@ -2221,7 +2286,8 @@
     instmap::in, proc_info::in, simplify_info::out) is det.
 
 :- pred simplify_info_get_det_info(simplify_info::in, det_info::out) is det.
-:- pred simplify_info_get_msgs(simplify_info::in, set(det_msg)::out) is det.
+:- pred simplify_info_get_det_msgs(simplify_info::in,
+    set(context_det_msg)::out) is det.
 :- pred simplify_info_get_simplifications(simplify_info::in,
     set(simplification)::out) is det.
 :- pred simplify_info_get_common_info(simplify_info::in, common_info::out)
@@ -2240,10 +2306,29 @@
     is det.
 :- pred simplify_info_get_pred_info(simplify_info::in, pred_info::out) is det.
 
+:- pred simplify_info_set_common_info(common_info::in,
+    simplify_info::in, simplify_info::out) is det.
+:- pred simplify_info_set_requantify(
+    simplify_info::in, simplify_info::out) is det.
+:- pred simplify_info_set_rerun_det(
+    simplify_info::in, simplify_info::out) is det.
+:- pred simplify_info_set_rtti_varmaps(rtti_varmaps::in,
+    simplify_info::in, simplify_info::out) is det.
+:- pred simplify_info_do_add_det_msg(context_det_msg::in,
+    simplify_info::in, simplify_info::out) is det.
+
+:- pred simplify_info_incr_cost_delta(int::in,
+    simplify_info::in, simplify_info::out) is det.
+
+:- pred simplify_info_apply_type_substitution(tsubst::in,
+    simplify_info::in, simplify_info::out) is det.
+
 :- implementation.
 
+:- pred simplify_info_get_format_calls(simplify_info::in, bool::out) is det.
+
 simplify_info_get_det_info(Info, Info ^ det_info).
-simplify_info_get_msgs(Info, Info ^ msgs).
+simplify_info_get_det_msgs(Info, Info ^ msgs).
 simplify_info_get_simplifications(Info, Info ^ simplifications).
 simplify_info_get_common_info(Info, Info ^ common_info).
 simplify_info_get_instmap(Info, Info ^ instmap).
@@ -2258,6 +2343,7 @@
     Info ^ rerun_det = yes.
 simplify_info_get_cost_delta(Info, Info ^ cost_delta).
 simplify_info_get_rtti_varmaps(Info, Info ^ rtti_varmaps).
+simplify_info_get_format_calls(Info, Info ^ format_calls).
 
 simplify_info_get_module_info(Info, ModuleInfo) :-
     simplify_info_get_det_info(Info, DetInfo),
@@ -2269,39 +2355,27 @@
     det_info_get_pred_id(DetInfo, PredId),
     module_info_pred_info(ModuleInfo, PredId, PredInfo).
 
-:- interface.
-
 :- pred simplify_info_set_det_info(det_info::in,
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_msgs(set(det_msg)::in,
+:- pred simplify_info_set_det_msgs(set(context_det_msg)::in,
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_simplifications(set(simplification)::in,
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_instmap(instmap::in,
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_common_info(common_info::in,
-    simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_varset(prog_varset::in,
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_var_types(vartypes::in,
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_requantify(
-    simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_recompute_atomic(
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_rerun_det(
-    simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_rtti_varmaps(rtti_varmaps::in,
+:- pred simplify_info_set_format_calls(bool::in,
     simplify_info::in, simplify_info::out) is det.
 
-:- pred simplify_info_add_msg(det_msg::in,
-    simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_do_add_msg(det_msg::in,
+:- pred simplify_info_add_det_msg(context_det_msg::in,
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_cost_delta(int::in,
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_incr_cost_delta(int::in,
-    simplify_info::in, simplify_info::out) is det.
 
 :- pred simplify_info_enter_lambda(simplify_info::in, simplify_info::out)
     is det.
@@ -2312,13 +2386,8 @@
 :- pred simplify_info_set_module_info(module_info::in,
     simplify_info::in, simplify_info::out) is det.
 
-:- pred simplify_info_apply_type_substitution(tsubst::in,
-    simplify_info::in, simplify_info::out) is det.
-
-:- implementation.
-
 simplify_info_set_det_info(Det, Info, Info ^ det_info := Det).
-simplify_info_set_msgs(Msgs, Info, Info ^ msgs := Msgs).
+simplify_info_set_det_msgs(Msgs, Info, Info ^ msgs := Msgs).
 simplify_info_set_simplifications(Simp, Info, Info ^ simplifications := Simp).
 simplify_info_set_instmap(InstMap, Info, Info ^ instmap := InstMap).
 simplify_info_set_common_info(Common, Info, Info ^ common_info := Common).
@@ -2330,21 +2399,22 @@
 simplify_info_set_rerun_det(Info, Info ^ rerun_det := yes).
 simplify_info_set_cost_delta(Delta, Info, Info ^ cost_delta := Delta).
 simplify_info_set_rtti_varmaps(Rtti, Info, Info ^ rtti_varmaps := Rtti).
+simplify_info_set_format_calls(FC, Info, Info ^ format_calls := FC).
 
 simplify_info_incr_cost_delta(Incr, Info,
     Info ^ cost_delta := Info ^ cost_delta + Incr).
 
-simplify_info_add_msg(Msg, !Info) :-
+simplify_info_add_det_msg(Msg, !Info) :-
     ( simplify_do_warn(!.Info) ->
-        simplify_info_do_add_msg(Msg, !Info)
+        simplify_info_do_add_det_msg(Msg, !Info)
     ;
         true
     ).
 
-simplify_info_do_add_msg(Msg, !Info) :-
-    simplify_info_get_msgs(!.Info, Msgs0),
+simplify_info_do_add_det_msg(Msg, !Info) :-
+    simplify_info_get_det_msgs(!.Info, Msgs0),
     set__insert(Msgs0, Msg, Msgs),
-    simplify_info_set_msgs(Msgs, !Info).
+    simplify_info_set_det_msgs(Msgs, !Info).
 
 simplify_info_enter_lambda(Info, Info ^ lambdas := Info ^ lambdas + 1).
 simplify_info_leave_lambda(Info, Info ^ lambdas := LambdaCount) :-
@@ -2528,6 +2598,7 @@
     unexpected(this_file, "will_flush: unexpected shorthand").
 
     % Reset the instmap and seen calls for the next branch.
+    %
 :- pred simplify_info_post_branch_update(simplify_info::in, simplify_info::in,
     simplify_info::out) is det.
 
cvs diff: Diffing compiler/notes
Index: compiler/notes/compiler_design.html
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/notes/compiler_design.html,v
retrieving revision 1.110
diff -u -b -r1.110 compiler_design.html
--- compiler/notes/compiler_design.html	23 Nov 2005 04:44:10 -0000	1.110
+++ compiler/notes/compiler_design.html	25 Jan 2006 01:34:31 -0000
@@ -829,6 +829,8 @@
 	simplify.m also attempts to partially evaluate calls to builtin
 	procedures if the inputs are all constants (this is const_prop.m
 	in the transform_hlds.m package).
+	simplify.m also calls format_call.m to look for
+	(possibly) incorrect uses of string.format io.format.
 	<p>
 
 </dl>
cvs diff: Diffing debian
cvs diff: Diffing debian/patches
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
Index: doc/user_guide.texi
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/doc/user_guide.texi,v
retrieving revision 1.464
diff -u -b -r1.464 user_guide.texi
--- doc/user_guide.texi	6 Jan 2006 04:06:55 -0000	1.464
+++ doc/user_guide.texi	25 Jan 2006 01:08:59 -0000
@@ -5295,6 +5295,20 @@
 enabled when termination analysis is enabled.
 (See @ref{Termination analysis options} for further details).
 
+ at sp 1
+ at item --no-warn-known-bad-format-call
+ at findex --no-warn-known-bad-format-call
+Do not warn about calls to string.format or io.format that
+the compiler knows for sure contain mismatches between the format
+string and the supplied values.
+
+ at sp 1
+ at item --warn-unknown-format-call
+ at findex --warn-unknown-format-call
+Warn about calls to string.format or io.format for which
+the compiler cannot tell whether there are any mismatches between
+the format string and the supplied values.
+
 @end table
 
 @node Verbosity options
cvs diff: Diffing extras
cvs diff: Diffing extras/aditi
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/stream
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/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
Index: library/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/Mercury.options,v
retrieving revision 1.10
diff -u -b -r1.10 Mercury.options
--- library/Mercury.options	16 Aug 2005 05:17:05 -0000	1.10
+++ library/Mercury.options	25 Jan 2006 03:48:29 -0000
@@ -26,4 +26,10 @@
 # We need to pass --no-ansi to mgnuc to ensure that these are declared.
 MGNUCFLAGS-io =	--no-ansi
 
+# This is needed to avoid errors on the calls that implement e.g. io.format/3
+# in terms of io.format/4, and string.format/2 in terms of string.format/3.
+# varset.trans_opt includes the relevant part of string.opt.
+# MCFLAGS-io     = --no-warn-unknown-format-calls
+# MCFLAGS-string = --no-warn-unknown-format-calls
+
 MCFLAGS-mer_std = --no-warn-nothing-exported
Index: library/pprint.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/pprint.m,v
retrieving revision 1.17
diff -u -b -r1.17 pprint.m
--- library/pprint.m	16 Jun 2005 04:08:03 -0000	1.17
+++ library/pprint.m	24 Jan 2006 07:26:57 -0000
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% vim:ts=4 sw=4 expandtab tw=0 wm=0
+% vim:ts=4 sw=4 expandtab tw=0 wm=0 ft=mercury
 %-----------------------------------------------------------------------------%
 % Copyright (C) 2000-2005 The University of Melbourne
 % This file may only be copied under the terms of the GNU Library General
@@ -454,8 +454,8 @@
 
 %-----------------------------------------------------------------------------%
 
-    % This is a contraction of Wadler's pretty, layout and be
-    % functions, adapted to work with a strict evaluation order.
+    % This is a contraction of Wadler's pretty, layout and be functions,
+    % adapted to work with a strict evaluation order.
     %
 :- pred layout_best(pred(string, T, T), int, doc, T, T).
 :- mode layout_best(pred(in, di, uo) is det, in, in, di, uo) is det.
Index: library/rtti_implementation.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/rtti_implementation.m,v
retrieving revision 1.61
diff -u -b -r1.61 rtti_implementation.m
--- library/rtti_implementation.m	14 Oct 2005 01:42:51 -0000	1.61
+++ library/rtti_implementation.m	24 Jan 2006 06:15:17 -0000
@@ -67,7 +67,7 @@
 :- pred type_ctor_name_and_arity(type_ctor_info::in,
         string::out, string::out, int::out) is det.
 
-:- pred deconstruct(T, noncanon_handling, string, int, list(std_util__univ)).
+:- pred deconstruct(T, noncanon_handling, string, int, list(std_util.univ)).
 :- mode deconstruct(in, in(do_not_allow), out, out, out) is det.
 :- mode deconstruct(in, in(canonicalize), out, out, out) is det.
 :- mode deconstruct(in, in(include_details_cc), out, out, out) is cc_multi.
@@ -82,13 +82,13 @@
 %
 % Implementations for use from construct.
 
-:- func num_functors(type_desc__type_desc) = int.
+:- func num_functors(type_desc.type_desc) = int.
 
-:- pred get_functor(type_desc__type_desc::in, int::in, string::out, int::out,
-    list(type_desc__type_desc)::out) is semidet.
+:- pred get_functor(type_desc.type_desc::in, int::in, string::out, int::out,
+    list(type_desc.type_desc)::out) is semidet.
 
-:- pred get_functor_with_names(type_desc__type_desc::in, int::in, string::out,
-    int::out, list(type_desc__type_desc)::out, list(string)::out)
+:- pred get_functor_with_names(type_desc.type_desc::in, int::in, string::out,
+    int::out, list(type_desc.type_desc)::out, list(string)::out)
     is semidet.
 
 %-----------------------------------------------------------------------------%
@@ -328,8 +328,8 @@
     get_functor_impl(TypeDesc, FunctorNumber, FunctorName, Arity,
         TypeInfoList, Names).
 
-:- pred get_functor_impl(type_desc__type_desc::in, int::in,
-    string::out, int::out, list(type_desc__type_desc)::out,
+:- pred get_functor_impl(type_desc.type_desc::in, int::in,
+    string::out, int::out, list(type_desc.type_desc)::out,
     list(string)::out) is semidet.
 
 get_functor_impl(TypeDesc, FunctorNumber,
@@ -403,7 +403,7 @@
         TypeInfoList = iterate(1, Arity, (func(I) =
             unsafe_cast(TypeInfo ^ var_arity_type_info_index(I)))
         ),
-        Names = list__duplicate(Arity, null_string)
+        Names = list.duplicate(Arity, null_string)
     ;
         TypeCtorRep = int,
         fail
@@ -495,7 +495,7 @@
 
 :- pred get_functor_du(type_ctor_rep::in(du), type_info::in,
     type_ctor_info::in, int::in, string::out, int::out,
-    list(type_desc__type_desc)::out, list(string)::out) is semidet.
+    list(type_desc.type_desc)::out, list(string)::out) is semidet.
 
 get_functor_du(TypeCtorRep, TypeInfo, TypeCtorInfo, FunctorNumber,
         FunctorName, Arity, TypeDescList, Names) :-
@@ -523,11 +523,11 @@
     ( ArgNames = DuFunctorDesc ^ du_functor_arg_names ->
         Names = iterate(0, Arity - 1, (func(I) = ArgNames ^ unsafe_index(I)))
     ;
-        Names = list__duplicate(Arity, null_string)
+        Names = list.duplicate(Arity, null_string)
     ).
 
 :- pred get_functor_enum(type_ctor_rep::in(enum), type_ctor_info::in, int::in,
-    string::out, int::out, list(type_desc__type_desc)::out, list(string)::out)
+    string::out, int::out, list(type_desc.type_desc)::out, list(string)::out)
     is det.
 
 get_functor_enum(TypeCtorRep, TypeCtorInfo, FunctorNumber, FunctorName, Arity,
@@ -542,7 +542,7 @@
     Names = [].
 
 :- pred get_functor_notag(type_ctor_rep::in(notag), type_ctor_info::in,
-    int::in, string::out, int::out, list(type_desc__type_desc)::out,
+    int::in, string::out, int::out, list(type_desc.type_desc)::out,
     list(string)::out) is det.
 
 get_functor_notag(TypeCtorRep, TypeCtorInfo, FunctorNumber, FunctorName, Arity,
@@ -588,7 +588,7 @@
 get_type_info(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("get_type_info").
+    private_builtin.sorry("get_type_info").
 
 :- func get_var_arity_typeinfo_arity(type_info) = int.
 
@@ -607,7 +607,7 @@
 ").
 
 get_var_arity_typeinfo_arity(_) = _ :-
-    private_builtin__sorry("get_var_arity_typeinfo_arity").
+    private_builtin.sorry("get_var_arity_typeinfo_arity").
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -1082,7 +1082,7 @@
         Functor, Arity, Arguments).
 
 :- pred deconstruct(T, type_info, type_ctor_info, type_ctor_rep,
-    noncanon_handling, string, int, list(std_util__univ)).
+    noncanon_handling, string, int, list(std_util.univ)).
 :- mode deconstruct(in, in, in, in, in(do_not_allow), out, out, out) is det.
 :- mode deconstruct(in, in, in, in, in(canonicalize), out, out, out) is det.
 :- mode deconstruct(in, in, in, in,
@@ -1092,7 +1092,7 @@
     % Code to perform deconstructions (XXX not yet complete).
     %
     % There are many cases to implement here, only the ones that were
-    % immediately useful (e.g. called by io__write) have been implemented
+    % immediately useful (e.g. called by io.write) have been implemented
     % so far.
 
 deconstruct(Term, TypeInfo, TypeCtorInfo, TypeCtorRep, NonCanon,
@@ -1133,7 +1133,7 @@
             Functor = FunctorDesc ^ du_functor_name,
             Arity = FunctorDesc ^ du_functor_arity,
             Arguments = iterate(0, Arity - 1,
-                (func(X) = std_util__univ(
+                (func(X) = std_util.univ(
                     get_arg(Term, X, SecTagLocn, FunctorDesc, TypeInfo))
                 ))
         ;
@@ -1148,7 +1148,7 @@
             Functor = FunctorDesc ^ du_functor_name,
             Arity = FunctorDesc ^ du_functor_arity,
             Arguments = iterate(0, Arity - 1,
-                (func(X) = std_util__univ(
+                (func(X) = std_util.univ(
                     get_arg(Term, X, SecTagLocn, FunctorDesc, TypeInfo))
                 ))
         ;
@@ -1194,7 +1194,7 @@
     ;
         TypeCtorRep = int,
         det_dynamic_cast(Term, Int),
-        Functor = string__int_to_string(Int),
+        Functor = string.int_to_string(Int),
         Arity = 0,
         Arguments = []
     ;
@@ -1230,10 +1230,10 @@
         type_ctor_and_args(TypeInfo, _TypeCtorInfo, TypeArgs),
         Functor = "{}",
         Arity = get_var_arity_typeinfo_arity(TypeInfo),
-        list__map_foldl(
+        list.map_foldl(
             (pred(TI::in, U::out, Index::in, Next::out) is det :-
                 SubTerm = get_subterm(TI, Term, Index, 0),
-                U = std_util__univ(SubTerm),
+                U = std_util.univ(SubTerm),
                 Next = Index + 1
             ), TypeArgs, Arguments, 0, _)
     ;
@@ -1275,9 +1275,9 @@
         TypeCtorRep = array,
 
         % Constrain the T in array(T) to the correct element type.
-        std_util__type_ctor_and_args(std_util__type_of(Term), _, Args),
+        std_util.type_ctor_and_args(std_util.type_of(Term), _, Args),
         ( Args = [ElemType] ->
-            std_util__has_type(Elem, ElemType),
+            std_util.has_type(Elem, ElemType),
             same_array_elem_type(Array, Elem)
         ;
             error("An array which doesn't have a type_ctor arg")
@@ -1286,9 +1286,9 @@
         det_dynamic_cast(Term, Array),
 
         Functor = "<<array>>",
-        Arity = array__size(Array),
-        Arguments = array__foldr(
-            (func(Elem, List) = [std_util__univ(Elem) | List]),
+        Arity = array.size(Array),
+        Arguments = array.foldr(
+            (func(Elem, List) = [std_util.univ(Elem) | List]),
             Array, [])
     ;
         TypeCtorRep = succip,
@@ -1394,8 +1394,8 @@
 :- pred det_dynamic_cast(T::in, U::out) is det.
 
 det_dynamic_cast(Term, Actual) :-
-    std_util__type_to_univ(Term, Univ),
-    std_util__det_univ_to_type(Univ, Actual).
+    std_util.type_to_univ(Term, Univ),
+    std_util.det_univ_to_type(Univ, Actual).
 
 :- pred same_array_elem_type(array(T)::unused, T::unused) is det.
 
@@ -1405,7 +1405,7 @@
     notag_ground_usereq; reserved_addr_usereq).
 
 :- pred handle_usereq_type(T, type_info, type_ctor_info, type_ctor_rep,
-        noncanon_handling, string, int, list(std_util__univ)).
+        noncanon_handling, string, int, list(std_util.univ)).
 
 :- mode handle_usereq_type(in, in, in, in(usereq),
     in(do_not_allow), out, out, out) is erroneous.
@@ -1453,15 +1453,21 @@
 :- func expand_type_name(type_ctor_info, bool) = string.
 
 expand_type_name(TypeCtorInfo, Wrap) = Name :-
-    ( Wrap = yes ->
-        FmtStr = "<<%s.%s/%d>>"
-    ;
-        FmtStr = "%s.%s/%d"
+    (
+        Wrap = yes,
+        LeftWrapper = "<<",
+        RightWrapper = ">>"
+    ;
+        Wrap = no,
+        LeftWrapper = "",
+        RightWrapper = ""
     ),
-    Name = string__format(FmtStr,
-        [s(TypeCtorInfo ^ type_ctor_module_name),
+    Name = string.format("%s%s.%s/%d%s",
+        [s(LeftWrapper),
+        s(TypeCtorInfo ^ type_ctor_module_name),
         s(TypeCtorInfo ^ type_ctor_name),
-        i(TypeCtorInfo ^ type_ctor_arity)]).
+        i(TypeCtorInfo ^ type_ctor_arity),
+        s(RightWrapper)]).
 
     % Retrieve an argument number from a term, given the functor descriptor.
     %
@@ -1506,10 +1512,10 @@
 #endif
 ").
 high_level_data :-
-    ( std_util__semidet_succeed ->
-        private_builtin__sorry("high_level_data")
+    ( std_util.semidet_succeed ->
+        private_builtin.sorry("high_level_data")
     ;
-        std_util__semidet_succeed
+        std_util.semidet_succeed
     ).
 
 :- pred get_arg_type_info(type_info::in, P::in, T::in,
@@ -1539,7 +1545,7 @@
             Arity = TypeCtorInfo ^ type_ctor_arity,
             StartRegionSize = 1
         ),
-        ArgTypeInfo0 = std_util__no,
+        ArgTypeInfo0 = std_util.no,
         UpperBound = Arity + StartRegionSize - 1,
 
         iterate_foldl(StartRegionSize, UpperBound,
@@ -1552,23 +1558,23 @@
                 ->
                     TI = TI0
                 ;
-                    TI0 = std_util__yes(TypeInfo0)
+                    TI0 = std_util.yes(TypeInfo0)
                 ->
                     unsafe_promise_unique(TypeInfo0, TypeInfo1),
                     update_type_info_index(I, ETypeInfo, TypeInfo1, TypeInfo),
-                    TI = std_util__yes(TypeInfo)
+                    TI = std_util.yes(TypeInfo)
                 ;
                     NewTypeInfo0 = new_type_info(CastTypeInfo, UpperBound),
                     update_type_info_index(I, ETypeInfo, NewTypeInfo0,
                         NewTypeInfo),
-                    TI = std_util__yes(NewTypeInfo)
+                    TI = std_util.yes(NewTypeInfo)
                 )
             ), ArgTypeInfo0, MaybeArgTypeInfo),
         (
-            MaybeArgTypeInfo = std_util__yes(ArgTypeInfo1),
+            MaybeArgTypeInfo = std_util.yes(ArgTypeInfo1),
             ArgTypeInfo = ArgTypeInfo1
         ;
-            MaybeArgTypeInfo = std_util__no,
+            MaybeArgTypeInfo = std_util.no,
             ArgTypeInfo = CastTypeInfo
         )
     ).
@@ -1850,7 +1856,7 @@
 get_type_ctor_info(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("get_type_ctor_info").
+    private_builtin.sorry("get_type_ctor_info").
 
 :- pred same_pointer_value(T::in, T::in) is semidet.
 :- pred same_pointer_value_untyped(T::in, U::in) is semidet.
@@ -1874,7 +1880,7 @@
 same_pointer_value_untyped(_, _) :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("same_pointer_value_untyped").
+    private_builtin.sorry("same_pointer_value_untyped").
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -2109,9 +2115,9 @@
 :- func typeclass_info_type_info(type_info, int) = type_info.
 
 typeclass_info_type_info(TypeClassInfo, Index) = unsafe_cast(TypeInfo) :-
-    private_builtin__type_info_from_typeclass_info(
-        unsafe_cast(TypeClassInfo) `with_type` private_builtin__typeclass_info,
-        Index, TypeInfo `with_type` private_builtin__type_info).
+    private_builtin.type_info_from_typeclass_info(
+        unsafe_cast(TypeClassInfo) `with_type` private_builtin.typeclass_info,
+        Index, TypeInfo `with_type` private_builtin.type_info).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -2160,16 +2166,16 @@
 :- pred semidet_unimplemented(string::in) is semidet.
 
 semidet_unimplemented(S) :-
-    ( std_util__semidet_succeed ->
+    ( std_util.semidet_succeed ->
         error("rtti_implementation: unimplemented: " ++ S)
     ;
-        std_util__semidet_succeed
+        std_util.semidet_succeed
     ).
 
 :- pred det_unimplemented(string::in) is det.
 
 det_unimplemented(S) :-
-    ( std_util__semidet_succeed ->
+    ( std_util.semidet_succeed ->
         error("rtti_implementation: unimplemented: " ++ S)
     ;
         true
@@ -2202,7 +2208,7 @@
 type_ctor_arity(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_arity").
+    private_builtin.sorry("type_ctor_arity").
 
 :- some [P] func type_ctor_unify_pred(type_ctor_info) = P.
 :- pragma foreign_proc("C#",
@@ -2230,7 +2236,7 @@
 type_ctor_unify_pred(_) = "dummy value" :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_unify_pred").
+    private_builtin.sorry("type_ctor_unify_pred").
 
 :- some [P] func type_ctor_compare_pred(type_ctor_info) = P.
 :- pragma foreign_proc("C#",
@@ -2260,7 +2266,7 @@
 type_ctor_compare_pred(_) = "dummy value" :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_compare_pred").
+    private_builtin.sorry("type_ctor_compare_pred").
 
 :- func type_ctor_rep(type_ctor_info) = type_ctor_rep.
 :- pragma foreign_proc("C#",
@@ -2289,7 +2295,7 @@
 type_ctor_rep(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_rep").
+    private_builtin.sorry("type_ctor_rep").
 
 :- func type_ctor_module_name(type_ctor_info) = string.
 
@@ -2319,7 +2325,7 @@
 type_ctor_module_name(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_module_name").
+    private_builtin.sorry("type_ctor_module_name").
 
 :- func type_ctor_name(type_ctor_info) = string.
 
@@ -2347,7 +2353,7 @@
 type_ctor_name(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_name").
+    private_builtin.sorry("type_ctor_name").
 
 :- func type_ctor_functors(type_ctor_info) = type_functors.
 
@@ -2369,7 +2375,7 @@
 type_ctor_functors(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_functors").
+    private_builtin.sorry("type_ctor_functors").
 
 :- func type_layout(type_ctor_info) = type_layout.
 
@@ -2397,7 +2403,7 @@
 type_layout(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_layout").
+    private_builtin.sorry("type_layout").
 
 :- func type_ctor_num_functors(type_ctor_info) = int.
 
@@ -2412,7 +2418,7 @@
 type_ctor_num_functors(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("type_ctor_num_functors").
+    private_builtin.sorry("type_ctor_num_functors").
 
 :- pragma foreign_proc("C",
     unsafe_cast(VarIn::in) = (VarOut::out),
@@ -2436,7 +2442,7 @@
 unsafe_cast(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("unsafe_cast").
+    private_builtin.sorry("unsafe_cast").
 
 %-----------------------------------------------------------------------------%
 %
@@ -2703,7 +2709,7 @@
     Item = ((object []) Array)[Num];
 ").
 unsafe_index(_, _) = _ :-
-    private_builtin__sorry("rtti_implementation__unsafe_index").
+    private_builtin.sorry("rtti_implementation.unsafe_index").
 
  %--------------------------%
 
@@ -2715,7 +2721,7 @@
     Enum = mercury.runtime.LowLevelData.make_enum(Num);
 ").
 unsafe_make_enum(_) = _ :-
-    private_builtin__sorry("rtti_implementation__unsafe_make_enum").
+    private_builtin.sorry("rtti_implementation.unsafe_make_enum").
 
  %--------------------------%
 
@@ -2741,7 +2747,7 @@
 null(_) :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("rtti_implementation__null/1").
+    private_builtin.sorry("rtti_implementation.null/1").
 
  %--------------------------%
 
@@ -2767,7 +2773,7 @@
 null_string = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("rtti_implementation__null_string/0").
+    private_builtin.sorry("rtti_implementation.null_string/0").
 
  %--------------------------%
 
@@ -2790,6 +2796,6 @@
 unsafe_get_enum_value(_) = _ :-
     % This version is only used for back-ends for which there is no
     % matching foreign_proc version.
-    private_builtin__sorry("rtti_implementation__unsafe_get_enum_value/1").
+    private_builtin.sorry("rtti_implementation.unsafe_get_enum_value/1").
 
 %-----------------------------------------------------------------------------%
Index: library/string.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/string.m,v
retrieving revision 1.241
diff -u -b -r1.241 string.m
--- library/string.m	14 Dec 2005 10:33:56 -0000	1.241
+++ library/string.m	23 Jan 2006 02:05:21 -0000
@@ -29,64 +29,64 @@
     % Determine the length of a string.
     % An empty string has length zero.
     %
-:- func string__length(string) = int.
-:- mode string__length(in) = uo is det.
-:- pred string__length(string, int).
-:- mode string__length(in, uo) is det.
-:- mode string__length(ui, uo) is det.
+:- func string.length(string) = int.
+:- mode string.length(in) = uo is det.
+:- pred string.length(string, int).
+:- mode string.length(in, uo) is det.
+:- mode string.length(ui, uo) is det.
 
     % Append two strings together.
     %
-:- func string__append(string, string) = string.
-:- mode string__append(in, in) = uo is det.
+:- func string.append(string, string) = string.
+:- mode string.append(in, in) = uo is det.
 
-:- pred string__append(string, string, string).
-:- mode string__append(in, in, in) is semidet.  % implied
-:- mode string__append(in, uo, in) is semidet.
-:- mode string__append(in, in, uo) is det.
-:- mode string__append(out, out, in) is multi.
+:- pred string.append(string, string, string).
+:- mode string.append(in, in, in) is semidet.  % implied
+:- mode string.append(in, uo, in) is semidet.
+:- mode string.append(in, in, uo) is det.
+:- mode string.append(out, out, in) is multi.
 % The following mode is semidet in the sense that it doesn't succeed more
 % than once - but it does create a choice-point, which means it's inefficient
 % and that the compiler can't deduce that it is semidet.
-% Use string__remove_suffix instead.
-% :- mode string__append(out, in, in) is semidet.
+% Use string.remove_suffix instead.
+% :- mode string.append(out, in, in) is semidet.
 
-    % S1 ++ S2 = S :- string__append(S1, S2, S).
+    % S1 ++ S2 = S :- string.append(S1, S2, S).
     %
     % Nicer syntax.
 :- func string ++ string = string.
 :- mode in ++ in = uo is det.
 
-    % string__remove_suffix(String, Suffix, Prefix):
-    % The same as string__append(Prefix, Suffix, String) except that
-    % this is semidet whereas string__append(out, in, in) is nondet.
+    % string.remove_suffix(String, Suffix, Prefix):
+    % The same as string.append(Prefix, Suffix, String) except that
+    % this is semidet whereas string.append(out, in, in) is nondet.
     %
-:- pred string__remove_suffix(string::in, string::in, string::out) is semidet.
+:- pred string.remove_suffix(string::in, string::in, string::out) is semidet.
 
-    % string__prefix(String, Prefix) is true iff Prefix is a prefix of String.
-    % Same as string__append(Prefix, _, String).
+    % string.prefix(String, Prefix) is true iff Prefix is a prefix of String.
+    % Same as string.append(Prefix, _, String).
     %
-:- pred string__prefix(string, string).
-:- mode string__prefix(in, in) is semidet.
-:- mode string__prefix(in, out) is multi.
+:- pred string.prefix(string, string).
+:- mode string.prefix(in, in) is semidet.
+:- mode string.prefix(in, out) is multi.
 
-    % string__suffix(String, Suffix) is true iff Suffix is a suffix of String.
-    % Same as string__append(_, Suffix, String).
+    % string.suffix(String, Suffix) is true iff Suffix is a suffix of String.
+    % Same as string.append(_, Suffix, String).
     %
-:- pred string__suffix(string, string).
-:- mode string__suffix(in, in) is semidet.
-:- mode string__suffix(in, out) is multi.
+:- pred string.suffix(string, string).
+:- mode string.suffix(in, in) is semidet.
+:- mode string.suffix(in, out) is multi.
 
-    % string__string(X): Returns a canonicalized string representation
+    % string.string(X): Returns a canonicalized string representation
     % of the value X using the standard Mercury operators.
     %
-:- func string__string(T) = string.
+:- func string.string(T) = string.
 
     % As above, but using the supplied table of operators.
     %
-:- func string__string(ops__table, T) = string.
+:- func string.string(ops.table, T) = string.
 
-    % string__string(NonCanon, OpsTable, X, String)
+    % string.string(NonCanon, OpsTable, X, String)
     %
     % As above, but the caller specifies what behaviour should occur for
     % non-canonical terms (i.e. terms where multiple representations
@@ -99,51 +99,51 @@
     % - `include_details_cc' will show the structure of any non-canonical
     %   subterms, but can only be called from a committed choice context.
     %
-:- pred string__string(deconstruct__noncanon_handling, ops__table, T, string).
-:- mode string__string(in(do_not_allow), in, in, out) is det.
-:- mode string__string(in(canonicalize), in, in, out) is det.
-:- mode string__string(in(include_details_cc), in, in, out) is cc_multi.
-:- mode string__string(in, in, in, out) is cc_multi.
+:- pred string.string(deconstruct.noncanon_handling, ops.table, T, string).
+:- mode string.string(in(do_not_allow), in, in, out) is det.
+:- mode string.string(in(canonicalize), in, in, out) is det.
+:- mode string.string(in(include_details_cc), in, in, out) is cc_multi.
+:- mode string.string(in, in, in, out) is cc_multi.
 
-    % string__char_to_string(Char, String).
+    % string.char_to_string(Char, String).
     % Converts a character (single-character atom) to a string or vice versa.
     %
-:- func string__char_to_string(char) = string.
-:- mode string__char_to_string(in) = uo is det.
-:- pred string__char_to_string(char, string).
-:- mode string__char_to_string(in, uo) is det.
-:- mode string__char_to_string(out, in) is semidet.
+:- func string.char_to_string(char) = string.
+:- mode string.char_to_string(in) = uo is det.
+:- pred string.char_to_string(char, string).
+:- mode string.char_to_string(in, uo) is det.
+:- mode string.char_to_string(out, in) is semidet.
 
     % A synonym for string.int_to_char/1.
     %
-:- func string__from_char(char::in) = (string::uo) is det.
+:- func string.from_char(char::in) = (string::uo) is det.
 
     % Convert an integer to a string.
     %
-:- func string__int_to_string(int) = string.
-:- mode string__int_to_string(in) = uo is det.
-:- pred string__int_to_string(int, string).
-:- mode string__int_to_string(in, uo) is det.
+:- func string.int_to_string(int) = string.
+:- mode string.int_to_string(in) = uo is det.
+:- pred string.int_to_string(int, string).
+:- mode string.int_to_string(in, uo) is det.
 
     % A synonym for string.int_to_string/1.
     %
-:- func string__from_int(int::in) = (string::uo) is det.
+:- func string.from_int(int::in) = (string::uo) is det.
 
     % Convert an integer to a string with commas as thousand separators.
     %
-:- func string__int_to_string_thousands(int) = string.
-:- mode string__int_to_string_thousands(in) = uo is det.
+:- func string.int_to_string_thousands(int) = string.
+:- mode string.int_to_string_thousands(in) = uo is det.
 
-    % string__int_to_base_string(Int, Base, String):
+    % string.int_to_base_string(Int, Base, String):
     % Convert an integer to a string in a given Base.
     % An exception is thrown if Base is not between 2 and 36.
     %
-:- func string__int_to_base_string(int, int) = string.
-:- mode string__int_to_base_string(in, in) = uo is det.
-:- pred string__int_to_base_string(int, int, string).
-:- mode string__int_to_base_string(in, in, uo) is det.
+:- func string.int_to_base_string(int, int) = string.
+:- mode string.int_to_base_string(in, in) = uo is det.
+:- pred string.int_to_base_string(int, int, string).
+:- mode string.int_to_base_string(in, in, uo) is det.
 
-    % string__int_to_base_string_group(Int, Base, GroupLength, Separator,
+    % string.int_to_base_string_group(Int, Base, GroupLength, Separator,
     %   String):
     % Convert an integer to a string in a given Base (between 2 and 36)
     % and insert Separator between every GroupLength digits.
@@ -151,8 +151,8 @@
     % output.  An exception is thrown if Base is not between 2 and 36.
     % Useful for formatting numbers like "1,300,000".
     %
-:- func string__int_to_base_string_group(int, int, int, string) = string.
-:- mode string__int_to_base_string_group(in, in, in, in) = uo is det.
+:- func string.int_to_base_string_group(int, int, int, string) = string.
+:- mode string.int_to_base_string_group(in, in, in, in) = uo is det.
 
     % Convert a float to a string.
     % In the current implementation the resulting float will be in the form
@@ -162,106 +162,106 @@
     % The precision chosen from this range will be such to allow a successful
     % decimal -> binary conversion of the float.
     %
-:- func string__float_to_string(float) = string.
-:- mode string__float_to_string(in) = uo is det.
-:- pred string__float_to_string(float, string).
-:- mode string__float_to_string(in, uo) is det.
+:- func string.float_to_string(float) = string.
+:- mode string.float_to_string(in) = uo is det.
+:- pred string.float_to_string(float, string).
+:- mode string.float_to_string(in, uo) is det.
 
     % A synonym for string.float_to_string/1.
     %
-:- func string__from_float(float::in) = (string::uo) is det.
+:- func string.from_float(float::in) = (string::uo) is det.
 
-    % string__first_char(String, Char, Rest) is true iff Char is the first
+    % string.first_char(String, Char, Rest) is true iff Char is the first
     % character of String, and Rest is the remainder.
     %
-    % WARNING: string__first_char makes a copy of Rest because the garbage
+    % WARNING: string.first_char makes a copy of Rest because the garbage
     % collector doesn't handle references into the middle of an object,
-    % at least not the way we use it. Repeated use of string__first_char
+    % at least not the way we use it. Repeated use of string.first_char
     % to iterate over a string will result in very poor performance.
-    % Use string__foldl or string__to_char_list instead.
+    % Use string.foldl or string.to_char_list instead.
     %
-:- pred string__first_char(string, char, string).
-:- mode string__first_char(in, in, in) is semidet.  % implied
-:- mode string__first_char(in, uo, in) is semidet.  % implied
-:- mode string__first_char(in, in, uo) is semidet.  % implied
-:- mode string__first_char(in, uo, uo) is semidet.
-:- mode string__first_char(uo, in, in) is det.
+:- pred string.first_char(string, char, string).
+:- mode string.first_char(in, in, in) is semidet.  % implied
+:- mode string.first_char(in, uo, in) is semidet.  % implied
+:- mode string.first_char(in, in, uo) is semidet.  % implied
+:- mode string.first_char(in, uo, uo) is semidet.
+:- mode string.first_char(uo, in, in) is det.
 
-    % string__replace(String0, Search, Replace, String):
-    % string__replace replaces the first occurrence of Search in String0
+    % string.replace(String0, Search, Replace, String):
+    % string.replace replaces the first occurrence of Search in String0
     % with Replace to give String. It fails if Search does not occur
     % in String0.
     %
-:- pred string__replace(string::in, string::in, string::in, string::uo)
+:- pred string.replace(string::in, string::in, string::in, string::uo)
     is semidet.
 
-    % string__replace_all(String0, Search, Replace, String):
-    % string__replace_all replaces any occurrences of Search in String0
+    % string.replace_all(String0, Search, Replace, String):
+    % string.replace_all replaces any occurrences of Search in String0
     % with Replace to give String.
     %
-:- func string__replace_all(string, string, string) = string.
-:- mode string__replace_all(in, in, in) = uo is det.
-:- pred string__replace_all(string, string, string, string).
-:- mode string__replace_all(in, in, in, uo) is det.
+:- func string.replace_all(string, string, string) = string.
+:- mode string.replace_all(in, in, in) = uo is det.
+:- pred string.replace_all(string, string, string, string).
+:- mode string.replace_all(in, in, in, uo) is det.
 
     % Converts a string to lowercase.
     %
-:- func string__to_lower(string) = string.
-:- mode string__to_lower(in) = uo is det.
-:- pred string__to_lower(string, string).
-:- mode string__to_lower(in, uo) is det.
-:- mode string__to_lower(in, in) is semidet.        % implied
+:- func string.to_lower(string) = string.
+:- mode string.to_lower(in) = uo is det.
+:- pred string.to_lower(string, string).
+:- mode string.to_lower(in, uo) is det.
+:- mode string.to_lower(in, in) is semidet.        % implied
 
     % Converts a string to uppercase.
     %
-:- func string__to_upper(string) = string.
-:- mode string__to_upper(in) = uo is det.
-:- pred string__to_upper(string, string).
-:- mode string__to_upper(in, uo) is det.
-:- mode string__to_upper(in, in) is semidet.        % implied
+:- func string.to_upper(string) = string.
+:- mode string.to_upper(in) = uo is det.
+:- pred string.to_upper(string, string).
+:- mode string.to_upper(in, uo) is det.
+:- mode string.to_upper(in, in) is semidet.        % implied
 
     % Convert the first character (if any) of a string to uppercase.
     %
-:- func string__capitalize_first(string) = string.
-:- pred string__capitalize_first(string::in, string::out) is det.
+:- func string.capitalize_first(string) = string.
+:- pred string.capitalize_first(string::in, string::out) is det.
 
     % Convert the first character (if any) of a string to lowercase.
     %
-:- func string__uncapitalize_first(string) = string.
-:- pred string__uncapitalize_first(string::in, string::out) is det.
+:- func string.uncapitalize_first(string) = string.
+:- pred string.uncapitalize_first(string::in, string::out) is det.
 
     % Convert the string to a list of characters.
     %
-:- func string__to_char_list(string) = list(char).
-:- pred string__to_char_list(string, list(char)).
-:- mode string__to_char_list(in, out) is det.
-:- mode string__to_char_list(uo, in) is det.
+:- func string.to_char_list(string) = list(char).
+:- pred string.to_char_list(string, list(char)).
+:- mode string.to_char_list(in, out) is det.
+:- mode string.to_char_list(uo, in) is det.
 
     % Convert a list of characters to a string.
     %
-:- func string__from_char_list(list(char)) = string.
-:- mode string__from_char_list(in) = uo is det.
-:- pred string__from_char_list(list(char), string).
-:- mode string__from_char_list(in, uo) is det.
-:- mode string__from_char_list(out, in) is det.
+:- func string.from_char_list(list(char)) = string.
+:- mode string.from_char_list(in) = uo is det.
+:- pred string.from_char_list(list(char), string).
+:- mode string.from_char_list(in, uo) is det.
+:- mode string.from_char_list(out, in) is det.
 
-    % Same as string__from_char_list, except that it reverses the order
+    % Same as string.from_char_list, except that it reverses the order
     % of the characters.
     %
-:- func string__from_rev_char_list(list(char)) = string.
-:- mode string__from_rev_char_list(in) = uo is det.
-:- pred string__from_rev_char_list(list(char), string).
-:- mode string__from_rev_char_list(in, uo) is det.
+:- func string.from_rev_char_list(list(char)) = string.
+:- mode string.from_rev_char_list(in) = uo is det.
+:- pred string.from_rev_char_list(list(char), string).
+:- mode string.from_rev_char_list(in, uo) is det.
 
     % Converts a signed base 10 string to an int; throws an exception
     % if the string argument does not match the regexp [+-]?[0-9]+
     %
-:- func string__det_to_int(string) = int.
+:- func string.det_to_int(string) = int.
 
     % Convert a string to an int. The string must contain only digits,
     % optionally preceded by a plus or minus sign. If the string does
-    % not match this syntax, string__to_int fails.
-:- pred string__to_int(string::in, int::out) is semidet.
+    % not match this syntax, string.to_int fails.
+:- pred string.to_int(string::in, int::out) is semidet.
 
     % Convert a string in the specified base (2-36) to an int. The string
     % must contain one or more digits in the specified base, optionally
@@ -269,322 +269,322 @@
     % are represented by the letters A-Z or a-z. If the string does not match
     % this syntax, the predicate fails.
     %
-:- pred string__base_string_to_int(int::in, string::in, int::out) is semidet.
+:- pred string.base_string_to_int(int::in, string::in, int::out) is semidet.
 
     % Converts a signed base N string to an int; throws an exception
     % if the string argument is not precisely an optional sign followed by
     % a non-empty string of base N digits.
     %
-:- func string__det_base_string_to_int(int, string) = int.
+:- func string.det_base_string_to_int(int, string) = int.
 
     % Convert a string to a float. Throws an exception if the string is not
     % a syntactically correct float literal.
     %
-:- func string__det_to_float(string) = float.
+:- func string.det_to_float(string) = float.
 
     % Convert a string to a float. If the string is not a syntactically correct
-    % float literal, string__to_float fails.
+    % float literal, string.to_float fails.
     %
-:- pred string__to_float(string::in, float::out) is semidet.
+:- pred string.to_float(string::in, float::out) is semidet.
 
     % True if string contains only alphabetic characters (letters).
     %
-:- pred string__is_alpha(string::in) is semidet.
+:- pred string.is_alpha(string::in) is semidet.
 
     % True if string contains only alphabetic characters and underscores.
     %
-:- pred string__is_alpha_or_underscore(string::in) is semidet.
+:- pred string.is_alpha_or_underscore(string::in) is semidet.
 
     % True if string contains only letters, digits, and underscores.
     %
-:- pred string__is_alnum_or_underscore(string::in) is semidet.
+:- pred string.is_alnum_or_underscore(string::in) is semidet.
 
-    % string__pad_left(String0, PadChar, Width, String):
+    % string.pad_left(String0, PadChar, Width, String):
     % Insert `PadChar's at the left of `String0' until it is at least as long
     % as `Width', giving `String'.
     %
-:- func string__pad_left(string, char, int) = string.
-:- pred string__pad_left(string::in, char::in, int::in, string::out) is det.
+:- func string.pad_left(string, char, int) = string.
+:- pred string.pad_left(string::in, char::in, int::in, string::out) is det.
 
-    % string__pad_right(String0, PadChar, Width, String):
+    % string.pad_right(String0, PadChar, Width, String):
     % Insert `PadChar's at the right of `String0' until it is at least as long
     % as `Width', giving `String'.
     %
-:- func string__pad_right(string, char, int) = string.
-:- pred string__pad_right(string::in, char::in, int::in, string::out) is det.
+:- func string.pad_right(string, char, int) = string.
+:- pred string.pad_right(string::in, char::in, int::in, string::out) is det.
 
-    % string__duplicate_char(Char, Count, String):
+    % string.duplicate_char(Char, Count, String):
     % Construct a string consisting of `Count' occurrences of `Char'
     % in sequence.
     %
-:- func string__duplicate_char(char::in, int::in) = (string::uo) is det.
-:- pred string__duplicate_char(char::in, int::in, string::uo) is det.
+:- func string.duplicate_char(char::in, int::in) = (string::uo) is det.
+:- pred string.duplicate_char(char::in, int::in, string::uo) is det.
 
-    % string__contains_char(String, Char):
+    % string.contains_char(String, Char):
     % Succeed if `Char' occurs in `String'.
     %
-:- pred string__contains_char(string::in, char::in) is semidet.
+:- pred string.contains_char(string::in, char::in) is semidet.
 
-    % string__index(String, Index, Char):
+    % string.index(String, Index, Char):
     % `Char' is the (`Index' + 1)-th character of `String'.
     % Fails if `Index' is out of range (negative, or greater than or equal to
     % the length of `String').
     %
-:- pred string__index(string::in, int::in, char::uo) is semidet.
+:- pred string.index(string::in, int::in, char::uo) is semidet.
 
-    % string__index_det(String, Index, Char):
+    % string.index_det(String, Index, Char):
     % `Char' is the (`Index' + 1)-th character of `String'.
     % Calls error/1 if `Index' is out of range (negative, or greater than
     % or equal to the length of `String').
     %
-:- func string__index_det(string, int) = char.
-:- pred string__index_det(string::in, int::in, char::uo) is det.
+:- func string.index_det(string, int) = char.
+:- pred string.index_det(string::in, int::in, char::uo) is det.
 
     % A synonym for index_det/2:
-    % String ^ elem(Index) = string__index_det(String, Index).
+    % String ^ elem(Index) = string.index_det(String, Index).
     %
 :- func string ^ elem(int) = char.
 
-    % string__unsafe_index(String, Index, Char):
+    % string.unsafe_index(String, Index, Char):
     % `Char' is the (`Index' + 1)-th character of `String'.
     % WARNING: behavior is UNDEFINED if `Index' is out of range
     % (negative, or greater than or equal to the length of `String').
-    % This version is constant time, whereas string__index_det
+    % This version is constant time, whereas string.index_det
     % may be linear in the length of the string. Use with care!
     %
-:- func string__unsafe_index(string, int) = char.
-:- pred string__unsafe_index(string::in, int::in, char::uo) is det.
+:- func string.unsafe_index(string, int) = char.
+:- pred string.unsafe_index(string::in, int::in, char::uo) is det.
 
     % A synonym for unsafe_index/2:
-    % String ^ unsafe_elem(Index) = string__unsafe_index(String, Index).
+    % String ^ unsafe_elem(Index) = string.unsafe_index(String, Index).
     %
 :- func string ^ unsafe_elem(int) = char.
 
-    % string__chomp(String):
+    % string.chomp(String):
     % `String' minus any single trailing newline character.
     %
-:- func string__chomp(string) = string.
+:- func string.chomp(string) = string.
 
-    % string__lstrip(String):
+    % string.lstrip(String):
     % `String' minus any initial whitespace characters.
     %
-:- func string__lstrip(string) = string.
+:- func string.lstrip(string) = string.
 
-    % string__rstrip(String):
+    % string.rstrip(String):
     % `String' minus any trailing whitespace characters.
     %
-:- func string__rstrip(string) = string.
+:- func string.rstrip(string) = string.
 
-    % string__strip(String):
+    % string.strip(String):
     % `String' minus any initial and trailing whitespace characters.
     %
-:- func string__strip(string) = string.
+:- func string.strip(string) = string.
 
-    % string__lstrip(Pred, String):
+    % string.lstrip(Pred, String):
     % `String' minus the maximal prefix consisting entirely of chars
     % satisfying `Pred'.
     %
-:- func string__lstrip(pred(char)::in(pred(in) is semidet), string::in)
+:- func string.lstrip(pred(char)::in(pred(in) is semidet), string::in)
     = (string::out) is det.
 
-    % string__rstrip(Pred, String):
+    % string.rstrip(Pred, String):
     % `String' minus the maximal suffix consisting entirely of chars
     % satisfying `Pred'.
     %
-:- func string__rstrip(pred(char)::in(pred(in) is semidet), string::in)
+:- func string.rstrip(pred(char)::in(pred(in) is semidet), string::in)
     = (string::out) is det.
 
-    % string__prefix_length(Pred, String):
+    % string.prefix_length(Pred, String):
     % The length of the maximal prefix of `String' consisting entirely of
     % chars satisfying Pred.
     %
-:- func string__prefix_length(pred(char)::in(pred(in) is semidet), string::in)
+:- func string.prefix_length(pred(char)::in(pred(in) is semidet), string::in)
     = (int::out) is det.
 
-    % string__suffix_length(Pred, String):
+    % string.suffix_length(Pred, String):
     % The length of the maximal suffix of `String' consisting entirely of chars
     % satisfying Pred.
     %
 :- func suffix_length(pred(char)::in(pred(in) is semidet), string::in)
     = (int::out) is det.
 
-    % string__set_char(Char, Index, String0, String):
+    % string.set_char(Char, Index, String0, String):
     % `String' is `String0' with the (`Index' + 1)-th character set to `Char'.
     % Fails if `Index' is out of range (negative, or greater than or equal to
     % the length of `String0').
     %
-:- pred string__set_char(char, int, string, string).
-:- mode string__set_char(in, in, in, out) is semidet.
+:- pred string.set_char(char, int, string, string).
+:- mode string.set_char(in, in, in, out) is semidet.
 % XXX This mode is disabled because the compiler puts constant
 % strings into static data even when they might be updated.
-%:- mode string__set_char(in, in, di, uo) is semidet.
+%:- mode string.set_char(in, in, di, uo) is semidet.
 
-    % string__set_char_det(Char, Index, String0, String):
+    % string.set_char_det(Char, Index, String0, String):
     % `String' is `String0' with the (`Index' + 1)-th character set to `Char'.
     % Calls error/1 if `Index' is out of range (negative, or greater than
     % or equal to the length of `String0').
     %
-:- func string__set_char_det(char, int, string) = string.
-:- pred string__set_char_det(char, int, string, string).
-:- mode string__set_char_det(in, in, in, out) is det.
+:- func string.set_char_det(char, int, string) = string.
+:- pred string.set_char_det(char, int, string, string).
+:- mode string.set_char_det(in, in, in, out) is det.
 % XXX This mode is disabled because the compiler puts constant
 % strings into static data even when they might be updated.
-%:- mode string__set_char_det(in, in, di, uo) is det.
+%:- mode string.set_char_det(in, in, di, uo) is det.
 
-    % string__unsafe_set_char(Char, Index, String0, String):
+    % string.unsafe_set_char(Char, Index, String0, String):
     % `String' is `String0' with the (`Index' + 1)-th character set to `Char'.
     % WARNING: behavior is UNDEFINED if `Index' is out of range
     % (negative, or greater than or equal to the length of `String0').
-    % This version is constant time, whereas string__set_char_det
+    % This version is constant time, whereas string.set_char_det
     % may be linear in the length of the string. Use with care!
     %
-:- func string__unsafe_set_char(char, int, string) = string.
-:- mode string__unsafe_set_char(in, in, in) = out is det.
+:- func string.unsafe_set_char(char, int, string) = string.
+:- mode string.unsafe_set_char(in, in, in) = out is det.
 % XXX This mode is disabled because the compiler puts constant
 % strings into static data even when they might be updated.
-%:- mode string__unsafe_set_char(in, in, di) = uo is det.
-:- pred string__unsafe_set_char(char, int, string, string).
-:- mode string__unsafe_set_char(in, in, in, out) is det.
+%:- mode string.unsafe_set_char(in, in, di) = uo is det.
+:- pred string.unsafe_set_char(char, int, string, string).
+:- mode string.unsafe_set_char(in, in, in, out) is det.
 % XXX This mode is disabled because the compiler puts constant
 % strings into static data even when they might be updated.
-%:- mode string__unsafe_set_char(in, in, di, uo) is det.
+%:- mode string.unsafe_set_char(in, in, di, uo) is det.
 
-    % string__foldl(Closure, String, !Acc):
+    % string.foldl(Closure, String, !Acc):
     % `Closure' is an accumulator predicate which is to be called for each
     % character of the string `String' in turn. The initial value of the
     % accumulator is `!.Acc' and the final value is `!:Acc'.
-    % (string__foldl is equivalent to
-    %   string__to_char_list(String, Chars),
-    %   list__foldl(Closure, Chars, !Acc)
+    % (string.foldl is equivalent to
+    %   string.to_char_list(String, Chars),
+    %   list.foldl(Closure, Chars, !Acc)
     % but is implemented more efficiently.)
     %
-:- func string__foldl(func(char, A) = A, string, A) = A.
-:- pred string__foldl(pred(char, A, A), string, A, A).
-:- mode string__foldl(pred(in, di, uo) is det, in, di, uo) is det.
-:- mode string__foldl(pred(in, in, out) is det, in, in, out) is det.
-:- mode string__foldl(pred(in, in, out) is semidet, in, in, out) is semidet.
-:- mode string__foldl(pred(in, in, out) is nondet, in, in, out) is nondet.
-:- mode string__foldl(pred(in, in, out) is multi, in, in, out) is multi.
+:- func string.foldl(func(char, A) = A, string, A) = A.
+:- pred string.foldl(pred(char, A, A), string, A, A).
+:- mode string.foldl(pred(in, di, uo) is det, in, di, uo) is det.
+:- mode string.foldl(pred(in, in, out) is det, in, in, out) is det.
+:- mode string.foldl(pred(in, in, out) is semidet, in, in, out) is semidet.
+:- mode string.foldl(pred(in, in, out) is nondet, in, in, out) is nondet.
+:- mode string.foldl(pred(in, in, out) is multi, in, in, out) is multi.
 
-    % string__foldl2(Closure, String, !Acc1, !Acc2):
-    % A variant of string__foldl with two accumulators.
+    % string.foldl2(Closure, String, !Acc1, !Acc2):
+    % A variant of string.foldl with two accumulators.
     %
-:- pred string__foldl2(pred(char, A, A, B, B), string, A, A, B, B).
-:- mode string__foldl2(pred(in, di, uo, di, uo) is det,
+:- pred string.foldl2(pred(char, A, A, B, B), string, A, A, B, B).
+:- mode string.foldl2(pred(in, di, uo, di, uo) is det,
     in, di, uo, di, uo) is det.
-:- mode string__foldl2(pred(in, in, out, di, uo) is det,
+:- mode string.foldl2(pred(in, in, out, di, uo) is det,
     in, in, out, di, uo) is det.
-:- mode string__foldl2(pred(in, in, out, in, out) is det,
+:- mode string.foldl2(pred(in, in, out, in, out) is det,
     in, in, out, in, out) is det.
-:- mode string__foldl2(pred(in, in, out, in, out) is semidet,
+:- mode string.foldl2(pred(in, in, out, in, out) is semidet,
     in, in, out, in, out) is semidet.
-:- mode string__foldl2(pred(in, in, out, in, out) is nondet,
+:- mode string.foldl2(pred(in, in, out, in, out) is nondet,
     in, in, out, in, out) is nondet.
-:- mode string__foldl2(pred(in, in, out, in, out) is multi,
+:- mode string.foldl2(pred(in, in, out, in, out) is multi,
     in, in, out, in, out) is multi.
 
-    % string__foldl_substring(Closure, String, Start, Count, !Acc)
-    % is equivalent to string__foldl(Closure, SubString, !Acc)
-    % where SubString = string__substring(String, Start, Count).
-    %
-:- func string__foldl_substring(func(char, A) = A, string, int, int, A) = A.
-:- pred string__foldl_substring(pred(char, A, A), string, int, int, A, A).
-:- mode string__foldl_substring(pred(in, in, out) is det, in, in, in,
+    % string.foldl_substring(Closure, String, Start, Count, !Acc)
+    % is equivalent to string.foldl(Closure, SubString, !Acc)
+    % where SubString = string.substring(String, Start, Count).
+    %
+:- func string.foldl_substring(func(char, A) = A, string, int, int, A) = A.
+:- pred string.foldl_substring(pred(char, A, A), string, int, int, A, A).
+:- mode string.foldl_substring(pred(in, in, out) is det, in, in, in,
     in, out) is det.
-:- mode string__foldl_substring(pred(in, di, uo) is det, in, in, in,
+:- mode string.foldl_substring(pred(in, di, uo) is det, in, in, in,
     di, uo) is det.
-:- mode string__foldl_substring(pred(in, in, out) is semidet, in, in, in,
+:- mode string.foldl_substring(pred(in, in, out) is semidet, in, in, in,
     in, out) is semidet.
-:- mode string__foldl_substring(pred(in, in, out) is nondet, in, in, in,
+:- mode string.foldl_substring(pred(in, in, out) is nondet, in, in, in,
     in, out) is nondet.
-:- mode string__foldl_substring(pred(in, in, out) is multi, in, in, in,
+:- mode string.foldl_substring(pred(in, in, out) is multi, in, in, in,
     in, out) is multi.
 
-    % string__foldl_substring2(Closure, String, Start, Count, !Acc1, !Acc2)
-    % A variant of string__foldl_substring with two accumulators.
+    % string.foldl_substring2(Closure, String, Start, Count, !Acc1, !Acc2)
+    % A variant of string.foldl_substring with two accumulators.
     %
-:- pred string__foldl2_substring(pred(char, A, A, B, B),
+:- pred string.foldl2_substring(pred(char, A, A, B, B),
     string, int, int, A, A, B, B).
-:- mode string__foldl2_substring(pred(in, di, uo, di, uo) is det,
+:- mode string.foldl2_substring(pred(in, di, uo, di, uo) is det,
     in, in, in, di, uo, di, uo) is det.
-:- mode string__foldl2_substring(pred(in, in, out, di, uo) is det,
+:- mode string.foldl2_substring(pred(in, in, out, di, uo) is det,
     in, in, in, in, out, di, uo) is det.
-:- mode string__foldl2_substring(pred(in, in, out, in, out) is det,
+:- mode string.foldl2_substring(pred(in, in, out, in, out) is det,
     in, in, in, in, out, in, out) is det.
-:- mode string__foldl2_substring(pred(in, in, out, in, out) is semidet,
+:- mode string.foldl2_substring(pred(in, in, out, in, out) is semidet,
     in, in, in, in, out, in, out) is semidet.
-:- mode string__foldl2_substring(pred(in, in, out, in, out) is nondet,
+:- mode string.foldl2_substring(pred(in, in, out, in, out) is nondet,
     in, in, in, in, out, in, out) is nondet.
-:- mode string__foldl2_substring(pred(in, in, out, in, out) is multi,
+:- mode string.foldl2_substring(pred(in, in, out, in, out) is multi,
     in, in, in, in, out, in, out) is multi.
 
-    % string__foldr(Closure, String, !Acc):
-    % As string__foldl/4, except that processing proceeds right-to-left.
+    % string.foldr(Closure, String, !Acc):
+    % As string.foldl/4, except that processing proceeds right-to-left.
     %
-:- func string__foldr(func(char, T) = T, string, T) = T.
-:- pred string__foldr(pred(char, T, T), string, T, T).
-:- mode string__foldr(pred(in, in, out) is det, in, in, out) is det.
-:- mode string__foldr(pred(in, di, uo) is det, in, di, uo) is det.
-:- mode string__foldr(pred(in, in, out) is semidet, in, in, out) is semidet.
-:- mode string__foldr(pred(in, in, out) is nondet, in, in, out) is nondet.
-:- mode string__foldr(pred(in, in, out) is multi, in, in, out) is multi.
-
-    % string__foldr_substring(Closure, String, Start, Count, !Acc)
-    % is equivalent to string__foldr(Closure, SubString, !Acc)
-    % where SubString = string__substring(String, Start, Count).
-    %
-:- func string__foldr_substring(func(char, T) = T, string, int, int, T) = T.
-:- pred string__foldr_substring(pred(char, T, T), string, int, int, T, T).
-:- mode string__foldr_substring(pred(in, in, out) is det, in, in, in,
+:- func string.foldr(func(char, T) = T, string, T) = T.
+:- pred string.foldr(pred(char, T, T), string, T, T).
+:- mode string.foldr(pred(in, in, out) is det, in, in, out) is det.
+:- mode string.foldr(pred(in, di, uo) is det, in, di, uo) is det.
+:- mode string.foldr(pred(in, in, out) is semidet, in, in, out) is semidet.
+:- mode string.foldr(pred(in, in, out) is nondet, in, in, out) is nondet.
+:- mode string.foldr(pred(in, in, out) is multi, in, in, out) is multi.
+
+    % string.foldr_substring(Closure, String, Start, Count, !Acc)
+    % is equivalent to string.foldr(Closure, SubString, !Acc)
+    % where SubString = string.substring(String, Start, Count).
+    %
+:- func string.foldr_substring(func(char, T) = T, string, int, int, T) = T.
+:- pred string.foldr_substring(pred(char, T, T), string, int, int, T, T).
+:- mode string.foldr_substring(pred(in, in, out) is det, in, in, in,
     in, out) is det.
-:- mode string__foldr_substring(pred(in, di, uo) is det, in, in, in,
+:- mode string.foldr_substring(pred(in, di, uo) is det, in, in, in,
     di, uo) is det.
-:- mode string__foldr_substring(pred(in, in, out) is semidet, in, in, in,
+:- mode string.foldr_substring(pred(in, in, out) is semidet, in, in, in,
     in, out) is semidet.
-:- mode string__foldr_substring(pred(in, in, out) is nondet, in, in, in,
+:- mode string.foldr_substring(pred(in, in, out) is nondet, in, in, in,
     in, out) is nondet.
-:- mode string__foldr_substring(pred(in, in, out) is multi, in, in, in,
+:- mode string.foldr_substring(pred(in, in, out) is multi, in, in, in,
     in, out) is multi.
 
-    % string__words(SepP, String) returns the list of non-empty substrings
+    % string.words(SepP, String) returns the list of non-empty substrings
     % of String (in first to last order) that are delimited by non-empty
     % sequences of chars matched by SepP. For example,
     %
-    % string__words(char__is_whitespace, " the cat  sat on the  mat") =
+    % string.words(char.is_whitespace, " the cat  sat on the  mat") =
     %   ["the", "cat", "sat", "on", "the", "mat"]
     %
-:- func string__words(pred(char), string) = list(string).
-:- mode string__words(pred(in) is semidet, in) = out is det.
+:- func string.words(pred(char), string) = list(string).
+:- mode string.words(pred(in) is semidet, in) = out is det.
 
-    % string__words(String) = string__words(char__is_whitespace, String).
+    % string.words(String) = string.words(char.is_whitespace, String).
     %
-:- func string__words(string) = list(string).
+:- func string.words(string) = list(string).
 
-    % string__split(String, Count, LeftSubstring, RightSubstring):
+    % string.split(String, Count, LeftSubstring, RightSubstring):
     % `LeftSubstring' is the left-most `Count' characters of `String',
     % and `RightSubstring' is the remainder of `String'.
     % (If `Count' is out of the range [0, length of `String'], it is treated
     % as if it were the nearest end-point of that range.)
     %
-:- pred string__split(string::in, int::in, string::uo, string::uo) is det.
+:- pred string.split(string::in, int::in, string::uo, string::uo) is det.
 
-    % string__left(String, Count, LeftSubstring):
+    % string.left(String, Count, LeftSubstring):
     % `LeftSubstring' is the left-most `Count' characters of `String'.
     % (If `Count' is out of the range [0, length of `String'], it is treated
     % as if it were the nearest end-point of that range.)
     %
-:- func string__left(string::in, int::in) = (string::uo) is det.
-:- pred string__left(string::in, int::in, string::uo) is det.
+:- func string.left(string::in, int::in) = (string::uo) is det.
+:- pred string.left(string::in, int::in, string::uo) is det.
 
-    % string__right(String, Count, RightSubstring):
+    % string.right(String, Count, RightSubstring):
     % `RightSubstring' is the right-most `Count' characters of `String'.
     % (If `Count' is out of the range [0, length of `String'], it is treated
     % as if it were the nearest end-point of that range.)
     %
-:- func string__right(string::in, int::in) = (string::uo) is det.
-:- pred string__right(string::in, int::in, string::uo) is det.
+:- func string.right(string::in, int::in) = (string::uo) is det.
+:- pred string.right(string::in, int::in, string::uo) is det.
 
-    % string__substring(String, Start, Count, Substring):
+    % string.substring(String, Start, Count, Substring):
     % `Substring' is first the `Count' characters in what would remain
     % of `String' after the first `Start' characters were removed.
     % (If `Start' is out of the range [0, length of `String'], it is treated
@@ -592,61 +592,61 @@
     % If `Count' is out of the range [0, length of `String' - `Start'],
     % it is treated as if it were the nearest end-point of that range.)
     %
-:- func string__substring(string, int, int) = string.
-:- mode string__substring(in, in, in) = uo is det.
-:- pred string__substring(string, int, int, string).
-:- mode string__substring(in, in, in, uo) is det.
+:- func string.substring(string, int, int) = string.
+:- mode string.substring(in, in, in) = uo is det.
+:- pred string.substring(string, int, int, string).
+:- mode string.substring(in, in, in, uo) is det.
 
-    % string__unsafe_substring(String, Start, Count, Substring):
+    % string.unsafe_substring(String, Start, Count, Substring):
     % `Substring' is first the `Count' characters in what would remain
     % of `String' after the first `Start' characters were removed.
     % WARNING: if `Start' is out of the range [0, length of `String'],
     % or if `Count' is out of the range [0, length of `String' - `Start'],
     % then the behaviour is UNDEFINED. Use with care!
     % This version takes time proportional to the length of the substring,
-    % whereas string__substring may take time proportional to the length
+    % whereas string.substring may take time proportional to the length
     %% of the whole string.
     %
-:- func string__unsafe_substring(string, int, int) = string.
-:- mode string__unsafe_substring(in, in, in) = uo is det.
-:- pred string__unsafe_substring(string, int, int, string).
-:- mode string__unsafe_substring(in, in, in, uo) is det.
+:- func string.unsafe_substring(string, int, int) = string.
+:- mode string.unsafe_substring(in, in, in) = uo is det.
+:- pred string.unsafe_substring(string, int, int, string).
+:- mode string.unsafe_substring(in, in, in, uo) is det.
 
     % Append a list of strings together.
     %
-:- func string__append_list(list(string)::in) = (string::uo) is det.
-:- pred string__append_list(list(string)::in, string::uo) is det.
+:- func string.append_list(list(string)::in) = (string::uo) is det.
+:- pred string.append_list(list(string)::in, string::uo) is det.
 
-    % string__join_list(Separator, Strings) = JoinedString:
+    % string.join_list(Separator, Strings) = JoinedString:
     % Appends together the strings in Strings, putting Separator between
     % adjacent strings. If Strings is the empty list, returns the empty string.
     %
-:- func string__join_list(string::in, list(string)::in) = (string::uo) is det.
+:- func string.join_list(string::in, list(string)::in) = (string::uo) is det.
 
     % Compute a hash value for a string.
     %
-:- func string__hash(string) = int.
-:- pred string__hash(string::in, int::out) is det.
+:- func string.hash(string) = int.
+:- pred string.hash(string::in, int::out) is det.
 
-    % string__sub_string_search(String, SubString, Index).
+    % string.sub_string_search(String, SubString, Index).
     % `Index' is the position in `String' where the first occurrence of
     % `SubString' begins. Indices start at zero, so if `SubString' is a prefix
     % of `String', this will return Index = 0.
     %
-:- pred string__sub_string_search(string::in, string::in, int::out) is semidet.
+:- pred string.sub_string_search(string::in, string::in, int::out) is semidet.
 
-    % string__sub_string_search(String, SubString, BeginAt, Index).
+    % string.sub_string_search(String, SubString, BeginAt, Index).
     % `Index' is the position in `String' where the first occurrence of
     % `SubString' occurs such that 'Index' is greater than or equal to
     % `BeginAt'.  Indices start at zero,
     %
-:- pred string__sub_string_search(string::in, string::in, int::in, int::out)
+:- pred string.sub_string_search(string::in, string::in, int::in, int::out)
     is semidet.
 
     % A function similar to sprintf() in C.
     %
     % For example,
-    %   string__format("%s %i %c %f\n",
+    %   string.format("%s %i %c %f\n",
     %       [s("Square-root of"), i(2), c('='), f(1.41)], String)
     % will return
     %   String = "Square-root of 2 = 1.41\n".
@@ -655,7 +655,7 @@
     % a field width (or *), and a precision (could be a ".*").
     %
     % Valid conversion character types are {dioxXucsfeEgGp%}. %n is not
-    % supported. string__format will not return the length of the string.
+    % supported. string.format will not return the length of the string.
     %
     % conv  var     output form.        effect of '#'.
     % char. type.
@@ -693,11 +693,11 @@
     % The implementation uses the sprintf() function, so the actual output
     % will depend on the C standard library.
     %
-:- func string__format(string, list(string__poly_type)) = string.
-:- pred string__format(string::in, list(string__poly_type)::in, string::out)
+:- func string.format(string, list(string.poly_type)) = string.
+:- pred string.format(string::in, list(string.poly_type)::in, string::out)
     is det.
 
-:- type string__poly_type
+:- type string.poly_type
     --->    f(float)
     ;       i(int)
     ;       s(string)
@@ -719,7 +719,7 @@
     %  bb * 22
     % ccc * 333
     %
-:- func string__format_table(list(justified_column), string) = string.
+:- func string.format_table(list(justified_column), string) = string.
 
 :- type justified_column
     --->    left(list(string))
@@ -732,7 +732,7 @@
     % be broken over two (or more) lines. Sequences of whitespace characters
     % are replaced by a single space.
     %
-:- func string__word_wrap(string, int) = string.
+:- func string.word_wrap(string, int) = string.
 
     % word_wrap(Str, N, WordSeperator) = Wrapped.
     % word_wrap/3 is like word_wrap/2, except that words that need to be broken
@@ -740,7 +740,7 @@
     % If the length of WordSeperator is greater that or equal to N, then
     % no separator is used.
     %
-:- func string__word_wrap(string, int, string) = string.
+:- func string.word_wrap(string, int, string) = string.
 
 %-----------------------------------------------------------------------------%
 
@@ -758,51 +758,51 @@
 :- use_module term_io.
 :- use_module type_desc.
 
-string__replace(Str, Pat, Subst, Result) :-
+string.replace(Str, Pat, Subst, Result) :-
     sub_string_search(Str, Pat, Index),
 
-    Initial = string__unsafe_substring(Str, 0, Index),
+    Initial = string.unsafe_substring(Str, 0, Index),
 
-    BeginAt = Index + string__length(Pat),
-    Length = string__length(Str) - BeginAt,
-    Final = string__unsafe_substring(Str, BeginAt, Length),
+    BeginAt = Index + string.length(Pat),
+    Length = string.length(Str) - BeginAt,
+    Final = string.unsafe_substring(Str, BeginAt, Length),
 
-    Result = string__append_list([Initial, Subst, Final]).
+    Result = string.append_list([Initial, Subst, Final]).
 
-string__replace_all(Str, Pat, Subst, Result) :-
+string.replace_all(Str, Pat, Subst, Result) :-
     ( Pat = "" ->
         F = (func(C, L) = [char_to_string(C) ++ Subst | L]),
-        Foldl = string__foldl(F, Str, []),
-        Result = append_list([Subst | list__reverse(Foldl)])
+        Foldl = string.foldl(F, Str, []),
+        Result = append_list([Subst | list.reverse(Foldl)])
     ;
-        PatLength = string__length(Pat),
+        PatLength = string.length(Pat),
         ReversedChunks = replace_all(Str, Pat, Subst, PatLength, 0, []),
-        Chunks = list__reverse(ReversedChunks),
-        Result = string__append_list(Chunks)
+        Chunks = list.reverse(ReversedChunks),
+        Result = string.append_list(Chunks)
     ).
 
-:- func string__replace_all(string, string, string, int, int, list(string))
+:- func string.replace_all(string, string, string, int, int, list(string))
     = list(string).
 
-string__replace_all(Str, Pat, Subst, PatLength, BeginAt, Result0) = Result :-
+string.replace_all(Str, Pat, Subst, PatLength, BeginAt, Result0) = Result :-
     ( sub_string_search(Str, Pat, BeginAt, Index) ->
         Length = Index - BeginAt,
-        Initial = string__unsafe_substring(Str, BeginAt, Length),
+        Initial = string.unsafe_substring(Str, BeginAt, Length),
         Start = Index + PatLength,
-        Result = string__replace_all(Str, Pat, Subst, PatLength, Start,
+        Result = string.replace_all(Str, Pat, Subst, PatLength, Start,
             [Subst, Initial | Result0])
     ;
-        Length = string__length(Str) - BeginAt,
-        EndString = string__unsafe_substring(Str, BeginAt, Length),
+        Length = string.length(Str) - BeginAt,
+        EndString = string.unsafe_substring(Str, BeginAt, Length),
         Result = [EndString | Result0]
     ).
 
-string__to_int(String, Int) :-
-    string__base_string_to_int(10, String, Int).
+string.to_int(String, Int) :-
+    string.base_string_to_int(10, String, Int).
 
-string__base_string_to_int(Base, String, Int) :-
-    string__index(String, 0, Char),
-    Len = string__length(String),
+string.base_string_to_int(Base, String, Int) :-
+    string.index(String, 0, Char),
+    Len = string.length(String),
     ( Char = ('-') ->
         Len > 1,
         foldl_substring(accumulate_int(Base), String, 1, Len - 1, 0, N),
@@ -819,145 +819,145 @@
 :- pred accumulate_int(int::in, char::in, int::in, int::out) is semidet.
 
 accumulate_int(Base, Char, N, (Base * N) + M) :-
-    char__digit_to_int(Char, M),
+    char.digit_to_int(Char, M),
     M < Base.
 
-% It is important to inline string__index and string__index_det.
+% It is important to inline string.index and string.index_det.
 % so that the compiler can do loop invariant hoisting
-% on calls to string__length that occur in loops.
-:- pragma inline(string__index_det/3).
+% on calls to string.length that occur in loops.
+:- pragma inline(string.index_det/3).
 
-string__index_det(String, Int, Char) :-
-    ( string__index(String, Int, Char0) ->
+string.index_det(String, Int, Char) :-
+    ( string.index(String, Int, Char0) ->
         Char = Char0
     ;
-        error("string__index_det: index out of range")
+        error("string.index_det: index out of range")
     ).
 
 String ^ elem(Index) = index_det(String, Index).
 
-string__set_char_det(Char, Int, String0, String) :-
-    ( string__set_char(Char, Int, String0, String1) ->
+string.set_char_det(Char, Int, String0, String) :-
+    ( string.set_char(Char, Int, String0, String1) ->
         String = String1
     ;
-        error("string__set_char_det: index out of range")
+        error("string.set_char_det: index out of range")
     ).
 
-string__foldl(Closure, String, !Acc) :-
-    string__length(String, Length),
-    string__foldl_substring(Closure, String, 0, Length, !Acc).
+string.foldl(Closure, String, !Acc) :-
+    string.length(String, Length),
+    string.foldl_substring(Closure, String, 0, Length, !Acc).
 
-string__foldl2(Closure, String, !Acc1, !Acc2) :-
-    string__length(String, Length),
-    string__foldl2_substring(Closure, String, 0, Length, !Acc1, !Acc2).
+string.foldl2(Closure, String, !Acc1, !Acc2) :-
+    string.length(String, Length),
+    string.foldl2_substring(Closure, String, 0, Length, !Acc1, !Acc2).
 
-string__foldl_substring(Closure, String, Start0, Count0, !Acc) :-
+string.foldl_substring(Closure, String, Start0, Count0, !Acc) :-
     Start = max(0, Start0),
     Count = min(Count0, length(String) - Start),
-    string__foldl_substring_2(Closure, String, Start, Count, !Acc).
+    string.foldl_substring_2(Closure, String, Start, Count, !Acc).
 
-string__foldl2_substring(Closure, String, Start0, Count0, !Acc1, !Acc2) :-
+string.foldl2_substring(Closure, String, Start0, Count0, !Acc1, !Acc2) :-
     Start = max(0, Start0),
     Count = min(Count0, length(String) - Start),
-    string__foldl2_substring_2(Closure, String, Start, Count, !Acc1, !Acc2).
+    string.foldl2_substring_2(Closure, String, Start, Count, !Acc1, !Acc2).
 
-:- pred string__foldl_substring_2(pred(char, A, A), string, int, int, A, A).
-:- mode string__foldl_substring_2(pred(in, di, uo) is det, in, in, in,
+:- pred string.foldl_substring_2(pred(char, A, A), string, int, int, A, A).
+:- mode string.foldl_substring_2(pred(in, di, uo) is det, in, in, in,
     di, uo) is det.
-:- mode string__foldl_substring_2(pred(in, in, out) is det, in, in, in,
+:- mode string.foldl_substring_2(pred(in, in, out) is det, in, in, in,
     in, out) is det.
-:- mode string__foldl_substring_2(pred(in, in, out) is semidet, in, in, in,
+:- mode string.foldl_substring_2(pred(in, in, out) is semidet, in, in, in,
     in, out) is semidet.
-:- mode string__foldl_substring_2(pred(in, in, out) is nondet, in, in, in,
+:- mode string.foldl_substring_2(pred(in, in, out) is nondet, in, in, in,
     in, out) is nondet.
-:- mode string__foldl_substring_2(pred(in, in, out) is multi, in, in, in,
+:- mode string.foldl_substring_2(pred(in, in, out) is multi, in, in, in,
     in, out) is multi.
 
-string__foldl_substring_2(Closure, String, I, Count, !Acc) :-
+string.foldl_substring_2(Closure, String, I, Count, !Acc) :-
     ( 0 < Count ->
-        Closure(string__unsafe_index(String, I), !Acc),
-        string__foldl_substring_2(Closure, String, I + 1, Count - 1, !Acc)
+        Closure(string.unsafe_index(String, I), !Acc),
+        string.foldl_substring_2(Closure, String, I + 1, Count - 1, !Acc)
     ;
         true
     ).
 
-:- pred string__foldl2_substring_2(pred(char, A, A, B, B), string, int, int,
+:- pred string.foldl2_substring_2(pred(char, A, A, B, B), string, int, int,
     A, A, B, B).
-:- mode string__foldl2_substring_2(pred(in, di, uo, di, uo) is det,
+:- mode string.foldl2_substring_2(pred(in, di, uo, di, uo) is det,
     in, in, in, di, uo, di, uo) is det.
-:- mode string__foldl2_substring_2(pred(in, in, out, di, uo) is det,
+:- mode string.foldl2_substring_2(pred(in, in, out, di, uo) is det,
     in, in, in, in, out, di, uo) is det.
-:- mode string__foldl2_substring_2(pred(in, in, out, in, out) is det,
+:- mode string.foldl2_substring_2(pred(in, in, out, in, out) is det,
     in, in, in, in, out, in, out) is det.
-:- mode string__foldl2_substring_2(pred(in, in, out, in, out) is semidet,
+:- mode string.foldl2_substring_2(pred(in, in, out, in, out) is semidet,
     in, in, in, in, out, in, out) is semidet.
-:- mode string__foldl2_substring_2(pred(in, in, out, in, out) is nondet,
+:- mode string.foldl2_substring_2(pred(in, in, out, in, out) is nondet,
     in, in, in, in, out, in, out) is nondet.
-:- mode string__foldl2_substring_2(pred(in, in, out, in, out) is multi,
+:- mode string.foldl2_substring_2(pred(in, in, out, in, out) is multi,
     in, in, in, in, out, in, out) is multi.
 
-string__foldl2_substring_2(Closure, String, I, Count, !Acc1, !Acc2) :-
+string.foldl2_substring_2(Closure, String, I, Count, !Acc1, !Acc2) :-
     ( 0 < Count ->
-        Closure(string__unsafe_index(String, I), !Acc1, !Acc2),
-        string__foldl2_substring_2(Closure, String, I + 1, Count - 1,
+        Closure(string.unsafe_index(String, I), !Acc1, !Acc2),
+        string.foldl2_substring_2(Closure, String, I + 1, Count - 1,
             !Acc1, !Acc2)
     ;
         true
     ).
 
-string__foldr(F, String, Acc0) = Acc :-
+string.foldr(F, String, Acc0) = Acc :-
     Closure = ( pred(X::in, Y::in, Z::out) is det :- Z = F(X, Y)),
-    string__foldr(Closure, String, Acc0, Acc).
+    string.foldr(Closure, String, Acc0, Acc).
 
-string__foldr_substring(F, String, Start, Count, Acc0) = Acc :-
+string.foldr_substring(F, String, Start, Count, Acc0) = Acc :-
     Closure = ( pred(X::in, Y::in, Z::out) is det :- Z = F(X, Y) ),
-    string__foldr_substring(Closure, String, Start, Count, Acc0, Acc).
+    string.foldr_substring(Closure, String, Start, Count, Acc0, Acc).
 
-string__foldr(Closure, String, Acc0, Acc) :-
-    string__foldr_substring(Closure, String, 0, length(String), Acc0, Acc).
+string.foldr(Closure, String, Acc0, Acc) :-
+    string.foldr_substring(Closure, String, 0, length(String), Acc0, Acc).
 
-string__foldr_substring(Closure, String, Start0, Count0, Acc0, Acc) :-
+string.foldr_substring(Closure, String, Start0, Count0, Acc0, Acc) :-
     Start = max(0, Start0),
     Count = min(Count0, length(String) - Start),
-    string__foldr_substring_2(Closure, String, Start, Count, Acc0, Acc).
+    string.foldr_substring_2(Closure, String, Start, Count, Acc0, Acc).
 
-:- pred string__foldr_substring_2(pred(char, T, T), string, int, int, T, T).
-:- mode string__foldr_substring_2(pred(in, in, out) is det, in, in, in,
+:- pred string.foldr_substring_2(pred(char, T, T), string, int, int, T, T).
+:- mode string.foldr_substring_2(pred(in, in, out) is det, in, in, in,
     in, out) is det.
-:- mode string__foldr_substring_2(pred(in, di, uo) is det, in, in, in,
+:- mode string.foldr_substring_2(pred(in, di, uo) is det, in, in, in,
     di, uo) is det.
-:- mode string__foldr_substring_2(pred(in, in, out) is semidet, in, in, in,
+:- mode string.foldr_substring_2(pred(in, in, out) is semidet, in, in, in,
     in, out) is semidet.
-:- mode string__foldr_substring_2(pred(in, in, out) is nondet, in, in, in,
+:- mode string.foldr_substring_2(pred(in, in, out) is nondet, in, in, in,
     in, out) is nondet.
-:- mode string__foldr_substring_2(pred(in, in, out) is multi, in, in, in,
+:- mode string.foldr_substring_2(pred(in, in, out) is multi, in, in, in,
     in, out) is multi.
 
-string__foldr_substring_2(Closure, String, I, Count, !Acc) :-
+string.foldr_substring_2(Closure, String, I, Count, !Acc) :-
     ( 0 < Count ->
-        Closure(string__unsafe_index(String, I + Count - 1), !Acc),
-        string__foldr_substring_2(Closure, String, I, Count - 1, !Acc)
+        Closure(string.unsafe_index(String, I + Count - 1), !Acc),
+        string.foldr_substring_2(Closure, String, I, Count - 1, !Acc)
     ;
         true
     ).
 
-string__left(String, Count, LeftString) :-
-    string__split(String, Count, LeftString, _RightString).
+string.left(String, Count, LeftString) :-
+    string.split(String, Count, LeftString, _RightString).
 
-string__right(String, RightCount, RightString) :-
-    string__length(String, Length),
+string.right(String, RightCount, RightString) :-
+    string.length(String, Length),
     LeftCount = Length - RightCount,
-    string__split(String, LeftCount, _LeftString, RightString).
+    string.split(String, LeftCount, _LeftString, RightString).
 
-string__remove_suffix(A, B, C) :-
-    string__to_char_list(A, LA),
-    string__to_char_list(B, LB),
-    string__to_char_list(C, LC),
+string.remove_suffix(A, B, C) :-
+    string.to_char_list(A, LA),
+    string.to_char_list(B, LB),
+    string.to_char_list(C, LC),
     char_list_remove_suffix(LA, LB, LC).
 
-:- pragma promise_pure(string__prefix/2).
+:- pragma promise_pure(string.prefix/2).
 
-string__prefix(String::in, Prefix::in) :-
+string.prefix(String::in, Prefix::in) :-
     Len    = length(String),
     PreLen = length(Prefix),
     PreLen =< Len,
@@ -973,7 +973,7 @@
         true
     ).
 
-string__prefix(String::in, Prefix::out) :-
+string.prefix(String::in, Prefix::out) :-
     Len = length(String),
     prefix_2_ioii(String, Prefix, 0, Len).
 
@@ -986,9 +986,9 @@
     PreLen < Len,
     prefix_2_ioii(String, Prefix, PreLen + 1, Len).
 
-:- pragma promise_pure(string__suffix/2).
+:- pragma promise_pure(string.suffix/2).
 
-string__suffix(String::in, Suffix::in) :-
+string.suffix(String::in, Suffix::in) :-
     Len    = length(String),
     PreLen = length(Suffix),
     PreLen =< Len,
@@ -1006,7 +1006,7 @@
         true
     ).
 
-string__suffix(String::in, Suffix::out) :-
+string.suffix(String::in, Suffix::out) :-
     Len = length(String),
     suffix_2_ioii(String, Suffix, 0, Len).
 
@@ -1019,138 +1019,138 @@
     SufLen < Len,
     suffix_2_ioii(String, Suffix, SufLen + 1, Len).
 
-string__char_to_string(Char, String) :-
-    string__to_char_list(String, [Char]).
+string.char_to_string(Char, String) :-
+    string.to_char_list(String, [Char]).
 
-string__from_char(Char) = string__char_to_string(Char).
+string.from_char(Char) = string.char_to_string(Char).
 
-string__int_to_string(N, Str) :-
-    string__int_to_base_string(N, 10, Str).
+string.int_to_string(N, Str) :-
+    string.int_to_base_string(N, 10, Str).
 
-string__from_int(N) = string__int_to_string(N).
+string.from_int(N) = string.int_to_string(N).
 
-string__int_to_base_string(N, Base, Str) :-
+string.int_to_base_string(N, Base, Str) :-
     (
         Base >= 2,
         Base =< 36
     ->
         true
     ;
-        error("string__int_to_base_string: invalid base")
+        error("string.int_to_base_string: invalid base")
     ),
-    string__int_to_base_string_1(N, Base, Str).
+    string.int_to_base_string_1(N, Base, Str).
 
-:- pred string__int_to_base_string_1(int::in, int::in, string::uo) is det.
+:- pred string.int_to_base_string_1(int::in, int::in, string::uo) is det.
 
-string__int_to_base_string_1(N, Base, Str) :-
+string.int_to_base_string_1(N, Base, Str) :-
     % Note that in order to handle MININT correctly, we need to do the
     % conversion of the absolute number into digits using negative numbers
     % (we can't use positive numbers, since -MININT overflows)
     ( N < 0 ->
-        string__int_to_base_string_2(N, Base, Str1),
-        string__append("-", Str1, Str)
+        string.int_to_base_string_2(N, Base, Str1),
+        string.append("-", Str1, Str)
     ;
         N1 = 0 - N,
-        string__int_to_base_string_2(N1, Base, Str)
+        string.int_to_base_string_2(N1, Base, Str)
     ).
 
-:- pred string__int_to_base_string_2(int::in, int::in, string::uo) is det.
+:- pred string.int_to_base_string_2(int::in, int::in, string::uo) is det.
 
-    % string__int_to_base_string_2/3 is almost identical to
-    % string__int_to_base_string_group_2/6 below so any changes here might
-    % also need to be applied to string__int_to_base_string_group_2/3.
+    % string.int_to_base_string_2/3 is almost identical to
+    % string.int_to_base_string_group_2/6 below so any changes here might
+    % also need to be applied to string.int_to_base_string_group_2/3.
     %
-string__int_to_base_string_2(NegN, Base, Str) :-
+string.int_to_base_string_2(NegN, Base, Str) :-
     ( NegN > -Base ->
         N = -NegN,
-        char__det_int_to_digit(N, DigitChar),
-        string__char_to_string(DigitChar, Str)
+        char.det_int_to_digit(N, DigitChar),
+        string.char_to_string(DigitChar, Str)
     ;
         NegN1 = NegN // Base,
         N10 = (NegN1 * Base) - NegN,
-        char__det_int_to_digit(N10, DigitChar),
-        string__char_to_string(DigitChar, DigitString),
-        string__int_to_base_string_2(NegN1, Base, Str1),
-        string__append(Str1, DigitString, Str)
+        char.det_int_to_digit(N10, DigitChar),
+        string.char_to_string(DigitChar, DigitString),
+        string.int_to_base_string_2(NegN1, Base, Str1),
+        string.append(Str1, DigitString, Str)
     ).
 
-string__from_char_list(CharList, Str) :-
-    string__to_char_list(Str, CharList).
+string.from_char_list(CharList, Str) :-
+    string.to_char_list(Str, CharList).
 
-string__int_to_string_thousands(N) =
-    string__int_to_base_string_group(N, 10, 3, ",").
+string.int_to_string_thousands(N) =
+    string.int_to_base_string_group(N, 10, 3, ",").
 
     % Period is how many digits should be between each separator.
     %
-string__int_to_base_string_group(N, Base, Period, Sep) = Str :-
+string.int_to_base_string_group(N, Base, Period, Sep) = Str :-
     (
         Base >= 2,
         Base =< 36
     ->
         true
     ;
-        error("string__int_to_base_string_group: invalid base")
+        error("string.int_to_base_string_group: invalid base")
     ),
-    string__int_to_base_string_group_1(N, Base, Period, Sep, Str).
+    string.int_to_base_string_group_1(N, Base, Period, Sep, Str).
 
-:- pred string__int_to_base_string_group_1(int::in, int::in, int::in,
+:- pred string.int_to_base_string_group_1(int::in, int::in, int::in,
     string::in, string::uo) is det.
 
     % Period is how many digits should be between each separator.
     %
-string__int_to_base_string_group_1(N, Base, Period, Sep, Str) :-
+string.int_to_base_string_group_1(N, Base, Period, Sep, Str) :-
     % Note that in order to handle MININT correctly, we need to do
     % the conversion of the absolute number into digits using negative numbers
     % (we can't use positive numbers, since -MININT overflows)
     ( N < 0 ->
-        string__int_to_base_string_group_2(N, Base, 0, Period, Sep, Str1),
-        string__append("-", Str1, Str)
+        string.int_to_base_string_group_2(N, Base, 0, Period, Sep, Str1),
+        string.append("-", Str1, Str)
     ;
         N1 = 0 - N,
-        string__int_to_base_string_group_2(N1, Base, 0, Period, Sep, Str)
+        string.int_to_base_string_group_2(N1, Base, 0, Period, Sep, Str)
     ).
 
-:- pred string__int_to_base_string_group_2(int::in, int::in, int::in, int::in,
+:- pred string.int_to_base_string_group_2(int::in, int::in, int::in, int::in,
     string::in, string::uo) is det.
 
     % Period is how many digits should be between each separator.
     % Curr is how many digits have been processed since the last separator
     % was inserted.
-    % string__int_to_base_string_group_2/6 is almost identical to
-    % string__int_to_base_string_2/3 above so any changes here might also
-    % need to be applied to string__int_to_base_string_2/3.
+    % string.int_to_base_string_group_2/6 is almost identical to
+    % string.int_to_base_string_2/3 above so any changes here might also
+    % need to be applied to string.int_to_base_string_2/3.
     %
-string__int_to_base_string_group_2(NegN, Base, Curr, Period, Sep, Str) :-
+string.int_to_base_string_group_2(NegN, Base, Curr, Period, Sep, Str) :-
     (
         Curr = Period,
         Period > 0
     ->
-        string__int_to_base_string_group_2(NegN, Base, 0, Period, Sep, Str1),
-        string__append(Str1, Sep, Str)
+        string.int_to_base_string_group_2(NegN, Base, 0, Period, Sep, Str1),
+        string.append(Str1, Sep, Str)
     ;
         ( NegN > -Base ->
             N = -NegN,
-            char__det_int_to_digit(N, DigitChar),
-            string__char_to_string(DigitChar, Str)
+            char.det_int_to_digit(N, DigitChar),
+            string.char_to_string(DigitChar, Str)
         ;
             NegN1 = NegN // Base,
             N10 = (NegN1 * Base) - NegN,
-            char__det_int_to_digit(N10, DigitChar),
-            string__char_to_string(DigitChar, DigitString),
-            string__int_to_base_string_group_2(NegN1, Base, Curr + 1, Period,
+            char.det_int_to_digit(N10, DigitChar),
+            string.char_to_string(DigitChar, DigitString),
+            string.int_to_base_string_group_2(NegN1, Base, Curr + 1, Period,
                 Sep, Str1),
-            string__append(Str1, DigitString, Str)
+            string.append(Str1, DigitString, Str)
         )
     ).
 
 /*-----------------------------------------------------------------------*/
 
-% :- pred string__to_char_list(string, list(char)).
-% :- mode string__to_char_list(in, uo) is det.
-% :- mode string__to_char_list(uo, in) is det.
+% :- pred string.to_char_list(string, list(char)).
+% :- mode string.to_char_list(in, uo) is det.
+% :- mode string.to_char_list(uo, in) is det.
 
 :- pragma foreign_proc("C",
-    string__to_char_list(Str::in, CharList::out),
+    string.to_char_list(Str::in, CharList::out),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_ConstString p = Str + strlen(Str);
@@ -1163,7 +1163,7 @@
 }").
 
 :- pragma foreign_proc("C",
-    string__to_char_list(Str::uo, CharList::in),
+    string.to_char_list(Str::uo, CharList::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     /* mode (uo, in) is det */
@@ -1200,25 +1200,25 @@
     Str[size] = '\\0';
 }").
 
-:- pragma promise_pure(string__to_char_list/2).
+:- pragma promise_pure(string.to_char_list/2).
 
-string__to_char_list(Str::in, CharList::out) :-
-    string__to_char_list_2(Str, 0, CharList).
-string__to_char_list(Str::uo, CharList::in) :-
+string.to_char_list(Str::in, CharList::out) :-
+    string.to_char_list_2(Str, 0, CharList).
+string.to_char_list(Str::uo, CharList::in) :-
     (
         CharList = [],
         Str = ""
     ;
         CharList = [C | Cs],
-        string__to_char_list(Str0, Cs),
-        string__first_char(Str, C, Str0)
+        string.to_char_list(Str0, Cs),
+        string.first_char(Str, C, Str0)
     ).
 
-:- pred string__to_char_list_2(string::in, int::in, list(char)::uo) is det.
+:- pred string.to_char_list_2(string::in, int::in, list(char)::uo) is det.
 
-string__to_char_list_2(Str, Index, CharList) :-
-    ( string__index(Str, Index, Char) ->
-        string__to_char_list_2(Str, Index + 1, CharList0),
+string.to_char_list_2(Str, Index, CharList) :-
+    ( string.index(Str, Index, Char) ->
+        string.to_char_list_2(Str, Index + 1, CharList0),
         CharList = [Char | CharList0]
     ;
         CharList = []
@@ -1226,12 +1226,12 @@
 
 %---------------------------------------------------------------------------%
 
-% We could implement from_rev_char_list using list__reverse and from_char_list,
+% We could implement from_rev_char_list using list.reverse and from_char_list,
 % but the optimized implementation in C below is there for efficiency since
 % it improves the overall speed of parsing by about 7%.
 
 :- pragma foreign_proc("C",
-    string__from_rev_char_list(Chars::in, Str::uo),
+    string.from_rev_char_list(Chars::in, Str::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Word list_ptr;
@@ -1273,106 +1273,106 @@
     }
 }").
 
-string__from_rev_char_list(Chars::in, Str::uo) :-
-    Str = string__from_char_list(list__reverse(Chars)).
+string.from_rev_char_list(Chars::in, Str::uo) :-
+    Str = string.from_char_list(list.reverse(Chars)).
 
-string__to_upper(StrIn, StrOut) :-
-    string__to_char_list(StrIn, List),
-    string__char_list_to_upper(List, ListUpp),
-    string__from_char_list(ListUpp, StrOut).
-
-:- pred string__char_list_to_upper(list(char)::in, list(char)::out) is det.
-
-string__char_list_to_upper([], []).
-string__char_list_to_upper([X | Xs], [Y | Ys]) :-
-    char__to_upper(X, Y),
-    string__char_list_to_upper(Xs, Ys).
-
-string__to_lower(StrIn, StrOut) :-
-    string__to_char_list(StrIn, List),
-    string__char_list_to_lower(List, ListLow),
-    string__from_char_list(ListLow, StrOut).
-
-:- pred string__char_list_to_lower(list(char)::in, list(char)::out) is det.
-
-string__char_list_to_lower([], []).
-string__char_list_to_lower([X | Xs], [Y | Ys]) :-
-    char__to_lower(X, Y),
-    string__char_list_to_lower(Xs, Ys).
-
-string__capitalize_first(S0, S) :-
-    ( string__first_char(S0, C, S1) ->
-        char__to_upper(C, UpperC),
-        string__first_char(S, UpperC, S1)
+string.to_upper(StrIn, StrOut) :-
+    string.to_char_list(StrIn, List),
+    string.char_list_to_upper(List, ListUpp),
+    string.from_char_list(ListUpp, StrOut).
+
+:- pred string.char_list_to_upper(list(char)::in, list(char)::out) is det.
+
+string.char_list_to_upper([], []).
+string.char_list_to_upper([X | Xs], [Y | Ys]) :-
+    char.to_upper(X, Y),
+    string.char_list_to_upper(Xs, Ys).
+
+string.to_lower(StrIn, StrOut) :-
+    string.to_char_list(StrIn, List),
+    string.char_list_to_lower(List, ListLow),
+    string.from_char_list(ListLow, StrOut).
+
+:- pred string.char_list_to_lower(list(char)::in, list(char)::out) is det.
+
+string.char_list_to_lower([], []).
+string.char_list_to_lower([X | Xs], [Y | Ys]) :-
+    char.to_lower(X, Y),
+    string.char_list_to_lower(Xs, Ys).
+
+string.capitalize_first(S0, S) :-
+    ( string.first_char(S0, C, S1) ->
+        char.to_upper(C, UpperC),
+        string.first_char(S, UpperC, S1)
     ;
         S = S0
     ).
 
-string__uncapitalize_first(S0, S) :-
-    ( string__first_char(S0, C, S1) ->
-        char__to_lower(C, LowerC),
-        string__first_char(S, LowerC, S1)
+string.uncapitalize_first(S0, S) :-
+    ( string.first_char(S0, C, S1) ->
+        char.to_lower(C, LowerC),
+        string.first_char(S, LowerC, S1)
     ;
         S = S0
     ).
 
-:- pred string__all_match(pred(char)::in(pred(in) is semidet), string::in)
+:- pred string.all_match(pred(char)::in(pred(in) is semidet), string::in)
     is semidet.
 
-string__all_match(P, String) :-
-    all_match_2(string__length(String) - 1, P, String).
+string.all_match(P, String) :-
+    all_match_2(string.length(String) - 1, P, String).
 
 :- pred all_match_2(int::in, pred(char)::in(pred(in) is semidet), string::in)
     is semidet.
 
-string__all_match_2(I, P, String) :-
+string.all_match_2(I, P, String) :-
     ( I >= 0 ->
-        P(string__unsafe_index(String, I)),
-        string__all_match_2(I - 1, P, String)
+        P(string.unsafe_index(String, I)),
+        string.all_match_2(I - 1, P, String)
     ;
         true
     ).
 
-string__is_alpha(S) :-
-    string__all_match(char__is_alpha, S).
+string.is_alpha(S) :-
+    string.all_match(char.is_alpha, S).
 
-string__is_alpha_or_underscore(S) :-
-    string__all_match(char__is_alpha_or_underscore, S).
+string.is_alpha_or_underscore(S) :-
+    string.all_match(char.is_alpha_or_underscore, S).
 
-string__is_alnum_or_underscore(S) :-
-    string__all_match(char__is_alnum_or_underscore, S).
+string.is_alnum_or_underscore(S) :-
+    string.all_match(char.is_alnum_or_underscore, S).
 
-string__pad_left(String0, PadChar, Width, String) :-
-    string__length(String0, Length),
+string.pad_left(String0, PadChar, Width, String) :-
+    string.length(String0, Length),
     ( Length < Width ->
         Count = Width - Length,
-        string__duplicate_char(PadChar, Count, PadString),
-        string__append(PadString, String0, String)
+        string.duplicate_char(PadChar, Count, PadString),
+        string.append(PadString, String0, String)
     ;
         String = String0
     ).
 
-string__pad_right(String0, PadChar, Width, String) :-
-    string__length(String0, Length),
+string.pad_right(String0, PadChar, Width, String) :-
+    string.length(String0, Length),
     ( Length < Width ->
         Count = Width - Length,
-        string__duplicate_char(PadChar, Count, PadString),
-        string__append(String0, PadString, String)
+        string.duplicate_char(PadChar, Count, PadString),
+        string.append(String0, PadString, String)
     ;
         String = String0
     ).
 
-string__duplicate_char(Char, Count, String) :-
-    String = string__from_char_list(list__duplicate(Count, Char)).
+string.duplicate_char(Char, Count, String) :-
+    String = string.from_char_list(list.duplicate(Count, Char)).
 
 %-----------------------------------------------------------------------------%
 
-string__append_list(Lists, string__append_list(Lists)).
+string.append_list(Lists, string.append_list(Lists)).
 
-    % We implement string__append_list in C as this minimises
+    % We implement string.append_list in C as this minimises
     % the amount of garbage created.
 :- pragma foreign_proc("C",
-    string__append_list(Strs::in) = (Str::uo),
+    string.append_list(Strs::in) = (Str::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Word list = Strs;
@@ -1401,10 +1401,10 @@
     Str[len] = '\\0';
 }").
 
-    % We implement string__join_list in C as this minimises the amount of
+    % We implement string.join_list in C as this minimises the amount of
     % garbage created.
 :- pragma foreign_proc("C",
-    string__join_list(Sep::in, Strs::in) = (Str::uo),
+    string.join_list(Sep::in, Strs::in) = (Str::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Word list;
@@ -1451,7 +1451,7 @@
     Str[len] = '\\0';
 }").
 
-string__append_list(Strs::in) = (Str::uo) :-
+string.append_list(Strs::in) = (Str::uo) :-
     (
         Strs = [X | Xs],
         Str = X ++ append_list(Xs)
@@ -1460,8 +1460,8 @@
         Str = ""
     ).
 
-string__join_list(_, []) = "".
-string__join_list(Sep, [H | T]) = H ++ string__join_list_2(Sep, T).
+string.join_list(_, []) = "".
+string.join_list(Sep, [H | T]) = H ++ string.join_list_2(Sep, T).
 
 :- func join_list_2(string::in, list(string)::in) = (string::uo) is det.
 
@@ -1474,31 +1474,31 @@
     %       runtime/mercury_string.h.  The two definitions must be kept
     %       identical.
     %
-string__hash(String, HashVal) :-
-    string__length(String, Length),
-    string__hash_2(String, 0, Length, 0, HashVal0),
+string.hash(String, HashVal) :-
+    string.length(String, Length),
+    string.hash_2(String, 0, Length, 0, HashVal0),
     HashVal = HashVal0 `xor` Length.
 
-:- pred string__hash_2(string::in, int::in, int::in, int::in, int::out) is det.
+:- pred string.hash_2(string::in, int::in, int::in, int::in, int::out) is det.
 
-string__hash_2(String, Index, Length, !HashVal) :-
+string.hash_2(String, Index, Length, !HashVal) :-
     ( Index < Length ->
-        string__combine_hash(char__to_int(string__unsafe_index(String, Index)),
+        string.combine_hash(char.to_int(string.unsafe_index(String, Index)),
             !HashVal),
-        string__hash_2(String, Index + 1, Length, !HashVal)
+        string.hash_2(String, Index + 1, Length, !HashVal)
     ;
         true
     ).
 
-:- pred string__combine_hash(int::in, int::in, int::out) is det.
+:- pred string.combine_hash(int::in, int::in, int::out) is det.
 
-string__combine_hash(X, H0, H) :-
+string.combine_hash(X, H0, H) :-
     H1 = H0 `xor` (H0 << 5),
     H = H1 `xor` X.
 
 %-----------------------------------------------------------------------------%
 
-string__sub_string_search(WholeString, Pattern, Index) :-
+string.sub_string_search(WholeString, Pattern, Index) :-
     sub_string_search(WholeString, Pattern, 0, Index).
 
 :- pragma foreign_proc("C",
@@ -1550,20 +1550,21 @@
 
 %-----------------------------------------------------------------------------%
 
-string__format(FormatString, PolyList, String) :-
+string.format(FormatString, PolyList, String) :-
     % This predicate has been optimised to produce the least memory possible
     % -- memory usage is a significant problem for programs which do a lot of
     % formatted IO.
     (
-        format_string(Specifiers, PolyList, [], to_char_list(FormatString), [])
+        format_string_to_specifiers(Specifiers, PolyList, [],
+            to_char_list(FormatString), [])
     ->
-        String = string__append_list(
-            list__map(specifier_to_string, Specifiers))
+        String = string.append_list(
+            list.map(specifier_to_string, Specifiers))
     ;
-        error("string__format: format string invalid.")
+        error("string.format: format string invalid.")
     ).
 
-:- type string__specifier
+:- type string.specifier
     --->    conv(
                 flags       :: list(char),
                 width       :: maybe(list(char)),
@@ -1576,17 +1577,18 @@
     % the list of characters which don't represent a conversion specifier
     % and those that do.
     %
-:- pred format_string(list(string__specifier)::out,
-    list(string__poly_type)::in, list(string__poly_type)::out,
+:- pred format_string_to_specifiers(list(string.specifier)::out,
+    list(string.poly_type)::in, list(string.poly_type)::out,
     list(char)::in, list(char)::out) is det.
 
-format_string(Results, !PolyTypes, !Chars) :-
+format_string_to_specifiers(Specifiers, !PolyTypes, !Chars) :-
     other(NonConversionSpecChars, !Chars),
     ( conversion_specification(ConversionSpec, !PolyTypes, !Chars) ->
-        format_string(Results0, !PolyTypes, !Chars),
-        Results = [string(NonConversionSpecChars), ConversionSpec | Results0]
+        format_string_to_specifiers(Specifiers0, !PolyTypes, !Chars),
+        Specifiers = [string(NonConversionSpecChars), ConversionSpec
+            | Specifiers0]
     ;
-        Results = [string(NonConversionSpecChars)]
+        Specifiers = [string(NonConversionSpecChars)]
     ).
 
     % Parse a string which doesn't contain any conversion specifications.
@@ -1609,8 +1611,8 @@
     % (in this order) zero or more flags, an optional minimum field width,
     % and an optional precision.
     %
-:- pred conversion_specification(string__specifier::out,
-    list(string__poly_type)::in, list(string__poly_type)::out,
+:- pred conversion_specification(string.specifier::out,
+    list(string.poly_type)::in, list(string.poly_type)::out,
     list(char)::in, list(char)::out) is semidet.
 
 conversion_specification(Specificier, !PolyTypes, !Chars) :-
@@ -1621,7 +1623,7 @@
     ( spec(Spec, !PolyTypes, !Chars) ->
         Specificier = conv(Flags, MaybeWidth, MaybePrec, Spec)
     ;
-        error("string__format: invalid conversion specifier.")
+        error("string.format: invalid conversion specifier.")
     ).
 
 :- pred optional(
@@ -1663,7 +1665,7 @@
     % Do we have a minimum field width?
     %
 :- pred width(list(char)::out,
-    list(string__poly_type)::in, list(string__poly_type)::out,
+    list(string.poly_type)::in, list(string.poly_type)::out,
     list(char)::in, list(char)::out) is semidet.
 
 width(Width, !PolyTypes, !Chars) :-
@@ -1672,7 +1674,7 @@
             % XXX may be better done in C.
             Width = to_char_list(int_to_string(Width0))
         ;
-            error("string__format: " ++
+            error("string.format: " ++
                 "`*' width modifier not associated with an integer.")
         )
     ;
@@ -1687,7 +1689,7 @@
     % Do we have a precision?
     %
 :- pred prec(list(char)::out,
-    list(string__poly_type)::in, list(string__poly_type)::out,
+    list(string.poly_type)::in, list(string.poly_type)::out,
     list(char)::in, list(char)::out) is semidet.
 
 prec(Prec, !PolyTypes, !Chars) :-
@@ -1697,7 +1699,7 @@
             % XXX Best done in C
             Prec = to_char_list(int_to_string(Prec0))
         ;
-            error("string__format: " ++
+            error("string.format: " ++
                 "`*' precision modifier not associated with an integer.")
         )
     ;
@@ -1745,7 +1747,7 @@
     % from the input list.
     %
 :- pred spec(spec::out,
-    list(string__poly_type)::in, list(string__poly_type)::out,
+    list(string.poly_type)::in, list(string.poly_type)::out,
     list(char)::in, list(char)::out) is semidet.
 
 % Valid integer conversion specifiers.
@@ -1780,7 +1782,7 @@
 
 non_zero_digit(!Chars) :-
     !.Chars = [Char | !:Chars],
-    char__is_digit(Char),
+    char.is_digit(Char),
     Char \= '0'.
 
     % A digit in the range [0-9].
@@ -1789,7 +1791,7 @@
 
 digit(!Chars) :-
     !.Chars = [Char | !:Chars],
-    char__is_digit(Char).
+    char.is_digit(Char).
 
     % Zero or more occurences of the string parsed by the given pred.
     %
@@ -1804,7 +1806,7 @@
         true
     ).
 
-:- func specifier_to_string(string__specifier) = string.
+:- func specifier_to_string(string.specifier) = string.
 
 specifier_to_string(conv(Flags, Width, Prec, Spec)) = String :-
     (
@@ -1957,7 +1959,7 @@
 :- func conv(maybe(list(character))) = maybe(int).
 
 conv(no) = no.
-conv(yes(X)) = yes(string__det_to_int(from_char_list(X))).
+conv(yes(X)) = yes(string.det_to_int(from_char_list(X))).
 
 %-----------------------------------------------------------------------------%
 
@@ -2020,7 +2022,7 @@
         MaybePrec = no,
         Prec = []
     ),
-    String = string__append_list(["%", from_char_list(Flags),
+    String = string.append_list(["%", from_char_list(Flags),
         from_char_list(Width), from_char_list(Prec), LengthMod, Spec]).
 
     % Construct a format string suitable to passing to .NET's formatting
@@ -2049,7 +2051,7 @@
     ;   Spec0 = "f" -> Spec = "e"
     ;   Spec = Spec0
     ),
-    String = string__append_list([
+    String = string.append_list([
         "{0",
         from_char_list(Width),
         ":",
@@ -2160,7 +2162,7 @@
 :- func format_char(flags, maybe_width, char) = string.
 
 format_char(Flags, Width, Char) = String :-
-    CharStr = string__char_to_string(Char),
+    CharStr = string.char_to_string(Char),
     String = justify_string(Flags, Width, CharStr).
 
     % Format a string (s).
@@ -2170,7 +2172,7 @@
 format_string(Flags, Width, Prec, OldStr) = NewStr :-
     (
         Prec = yes(NumChars),
-        PrecStr = string__substring(OldStr, 0, NumChars)
+        PrecStr = string.substring(OldStr, 0, NumChars)
     ;
         Prec = no,
         PrecStr = OldStr
@@ -2189,17 +2191,17 @@
         AbsIntStr = ""
     ;
         Integer = integer(Int),
-        AbsInteger = integer__abs(Integer),
-        AbsIntStr = integer__to_string(AbsInteger)
+        AbsInteger = integer.abs(Integer),
+        AbsIntStr = integer.to_string(AbsInteger)
     ),
-    AbsIntStrLength = string__length(AbsIntStr),
+    AbsIntStrLength = string.length(AbsIntStr),
 
     % Do we need to increase precision?
     (
         Prec = yes(Precision),
         Precision > AbsIntStrLength
     ->
-        PrecStr = string__pad_left(AbsIntStr, '0', Precision)
+        PrecStr = string.pad_left(AbsIntStr, '0', Precision)
     ;
         PrecStr = AbsIntStr
     ),
@@ -2207,12 +2209,12 @@
     % Do we need to pad to the field width?
     (
         Width = yes(FieldWidth),
-        FieldWidth > string__length(PrecStr),
+        FieldWidth > string.length(PrecStr),
         member('0', Flags),
         \+ member('-', Flags),
         Prec = no
     ->
-        FieldStr = string__pad_left(PrecStr, '0', FieldWidth - 1),
+        FieldStr = string.pad_left(PrecStr, '0', FieldWidth - 1),
         ZeroPadded = yes
     ;
         FieldStr = PrecStr,
@@ -2250,10 +2252,10 @@
     ->
         AbsIntStr = ""
     ;
-        Div = integer__pow(integer(2), integer(int__bits_per_int)),
+        Div = integer.pow(integer(2), integer(int.bits_per_int)),
         UnsignedInteger = integer(Int) mod Div,
         ( Base = 10 ->
-            AbsIntStr0 = integer__to_string(UnsignedInteger)
+            AbsIntStr0 = integer.to_string(UnsignedInteger)
         ; Base = 8 ->
             AbsIntStr0 = to_octal(UnsignedInteger)
         ; Prefix = "0x" ->
@@ -2269,14 +2271,14 @@
             AbsIntStr = AbsIntStr0
         )
     ),
-    AbsIntStrLength = string__length(AbsIntStr),
+    AbsIntStrLength = string.length(AbsIntStr),
 
     % Do we need to increase precision?
     (
         Prec = yes(Precision),
         Precision > AbsIntStrLength
     ->
-        PrecStr = string__pad_left(AbsIntStr, '0', Precision)
+        PrecStr = string.pad_left(AbsIntStr, '0', Precision)
     ;
         PrecStr = AbsIntStr
     ),
@@ -2285,7 +2287,7 @@
     (
         Base = 8,
         member('#', Flags),
-        \+ string__prefix(PrecStr, "0")
+        \+ string.prefix(PrecStr, "0")
     ->
         PrecModStr = append("0", PrecStr)
     ;
@@ -2295,7 +2297,7 @@
     % Do we need to pad to the field width?
     (
         Width = yes(FieldWidth),
-        FieldWidth > string__length(PrecModStr),
+        FieldWidth > string.length(PrecModStr),
         member('0', Flags),
         \+ member('-', Flags),
         Prec = no
@@ -2308,9 +2310,9 @@
             ; IsTypeP = yes
             )
         ->
-            FieldStr = string__pad_left(PrecModStr, '0', FieldWidth - 2)
+            FieldStr = string.pad_left(PrecModStr, '0', FieldWidth - 2)
         ;
-            FieldStr = string__pad_left(PrecModStr, '0', FieldWidth)
+            FieldStr = string.pad_left(PrecModStr, '0', FieldWidth)
         )
     ;
         FieldStr = PrecModStr
@@ -2357,8 +2359,8 @@
             \+ member('#', Flags),
             Prec = yes(0)
         ->
-            PrecStrLen = string__length(PrecStr),
-            PrecModStr = string__substring(PrecStr, 0, PrecStrLen - 1)
+            PrecStrLen = string.length(PrecStr),
+            PrecModStr = string.substring(PrecStr, 0, PrecStrLen - 1)
         ;
             PrecModStr = PrecStr
         )
@@ -2367,11 +2369,11 @@
     % Do we need to change field width?
     (
         Width = yes(FieldWidth),
-        FieldWidth > string__length(PrecModStr),
+        FieldWidth > string.length(PrecModStr),
         member('0', Flags),
         \+ member('-', Flags)
     ->
-        FieldStr = string__pad_left(PrecModStr, '0', FieldWidth - 1),
+        FieldStr = string.pad_left(PrecModStr, '0', FieldWidth - 1),
         ZeroPadded = yes
     ;
         FieldStr = PrecModStr,
@@ -2426,11 +2428,11 @@
         %
     (
         Width = yes(FieldWidth),
-        FieldWidth > string__length(PrecStr),
+        FieldWidth > string.length(PrecStr),
         member('0', Flags),
         \+ member('-', Flags)
     ->
-        FieldStr = string__pad_left(PrecStr, '0', FieldWidth - 1),
+        FieldStr = string.pad_left(PrecStr, '0', FieldWidth - 1),
         ZeroPadded = yes
     ;
         FieldStr = PrecStr,
@@ -2489,11 +2491,11 @@
     % Do we need to change field width?
     (
         Width = yes(FieldWidth),
-        FieldWidth > string__length(PrecModStr),
+        FieldWidth > string.length(PrecModStr),
         member('0', Flags),
         \+ member('-', Flags)
     ->
-        FieldStr = string__pad_left(PrecModStr, '0', FieldWidth - 1),
+        FieldStr = string.pad_left(PrecModStr, '0', FieldWidth - 1),
         ZeroPadded = yes
     ;
         FieldStr = PrecModStr,
@@ -2520,12 +2522,12 @@
 justify_string(Flags, Width, Str) =
     (
         Width = yes(FWidth),
-        FWidth > string__length(Str)
+        FWidth > string.length(Str)
     ->
         ( member('-', Flags) ->
-            string__pad_right(Str, ' ', FWidth)
+            string.pad_right(Str, ' ', FWidth)
         ;
-            string__pad_left(Str, ' ', FWidth)
+            string.pad_left(Str, ' ', FWidth)
         )
     ;
         Str
@@ -2539,7 +2541,7 @@
     ( Num > integer(0) ->
         Rest = to_octal(Num // integer(8)),
         Rem = Num rem integer(8),
-        RemStr = integer__to_string(Rem),
+        RemStr = integer.to_string(Rem),
         NumStr = append(Rest, RemStr)
     ;
         NumStr = ""
@@ -2579,7 +2581,7 @@
 
 get_hex_int(Int) = HexStr :-
     ( Int < integer(10) ->
-        HexStr = integer__to_string(Int)
+        HexStr = integer.to_string(Int)
     ; Int = integer(10) ->
         HexStr = "a"
     ; Int = integer(11) ->
@@ -2600,7 +2602,7 @@
 
 get_capital_hex_int(Int) = HexStr :-
     ( Int < integer(10) ->
-        HexStr = integer__to_string(Int)
+        HexStr = integer.to_string(Int)
     ; Int = integer(10) ->
         HexStr = "A"
     ; Int = integer(11) ->
@@ -2618,30 +2620,30 @@
     % Unlike the standard library function, this function converts a float
     % to a string without resorting to scientific notation.
     %
-    % This predicate relies on the fact that string__float_to_string returns
+    % This predicate relies on the fact that string.float_to_string returns
     % a float which is round-trippable, ie to the full precision needed.
     %
 :- func convert_float_to_string(float) = string.
 
 convert_float_to_string(Float) = String :-
-    string__lowlevel_float_to_string(Float, FloatStr),
+    string.lowlevel_float_to_string(Float, FloatStr),
 
     % Check for scientific representation.
     (
-        ( string__contains_char(FloatStr, 'e')
-        ; string__contains_char(FloatStr, 'E')
+        ( string.contains_char(FloatStr, 'e')
+        ; string.contains_char(FloatStr, 'E')
         )
     ->
         split_at_exponent(FloatStr, FloatPtStr, ExpStr),
         split_at_decimal_point(FloatPtStr, MantissaStr, FractionStr),
 
         % What is the exponent?
-        ExpInt = string__det_to_int(ExpStr),
+        ExpInt = string.det_to_int(ExpStr),
         ( ExpInt >= 0 ->
             % Move decimal pt to the right.
             ExtraDigits = ExpInt,
-            PaddedFracStr = string__pad_right(FractionStr, '0', ExtraDigits),
-            string__split(PaddedFracStr, ExtraDigits, MantissaRest,
+            PaddedFracStr = string.pad_right(FractionStr, '0', ExtraDigits),
+            string.split(PaddedFracStr, ExtraDigits, MantissaRest,
                 NewFraction),
 
             NewMantissa = MantissaStr ++ MantissaRest,
@@ -2654,9 +2656,9 @@
         ;
             % Move decimal pt to the left.
             ExtraDigits = abs(ExpInt),
-            PaddedMantissaStr = string__pad_left(MantissaStr, '0',
+            PaddedMantissaStr = string.pad_left(MantissaStr, '0',
                 ExtraDigits),
-            string__split(PaddedMantissaStr,
+            string.split(PaddedMantissaStr,
                 length(PaddedMantissaStr) - ExtraDigits,
                 NewMantissa, FractionRest),
 
@@ -2704,7 +2706,7 @@
             % Deal with floats such as ddddddd.mmmmmmmm.
             ScientificFloat = change_to_e_notation(Float, Prec - 1, "e"),
             split_at_exponent(ScientificFloat, BaseStr, ExponentStr),
-            Exp = string__det_to_int(ExponentStr),
+            Exp = string.det_to_int(ExponentStr),
             split_at_decimal_point(BaseStr, MantissaStr, FractionStr),
             RestMantissaStr = substring(FractionStr, 0, Exp),
             NewFraction = substring(FractionStr, Exp, Prec - Exp - 1),
@@ -2743,10 +2745,10 @@
 
     % Is mantissa greater than one digit long?
     split_at_decimal_point(UnsafeBase, MantissaStr, _FractionStr),
-    ( string__length(MantissaStr) > 1 ->
+    ( string.length(MantissaStr) > 1 ->
         % Need to append 0, to fix the problem of having no numbers
         % after the decimal point.
-        SafeBase = calculate_base_unsafe(string__append(UnsafeBase, "0"),
+        SafeBase = calculate_base_unsafe(string.append(UnsafeBase, "0"),
             Prec),
         SafeExponent = UnsafeExponent + 1
     ;
@@ -2756,18 +2758,18 @@
     % Creating exponent.
     ( SafeExponent >= 0 ->
         ( SafeExponent < 10 ->
-            ExponentStr = string__append_list(
-                [E, "+0", string__int_to_string(SafeExponent)])
+            ExponentStr = string.append_list(
+                [E, "+0", string.int_to_string(SafeExponent)])
         ;
-            ExponentStr = string__append_list(
-                [E, "+", string__int_to_string(SafeExponent)])
+            ExponentStr = string.append_list(
+                [E, "+", string.int_to_string(SafeExponent)])
         )
     ;
         ( SafeExponent > -10 ->
-            ExponentStr = string__append_list(
-                [E, "-0", string__int_to_string(int__abs(SafeExponent))])
+            ExponentStr = string.append_list(
+                [E, "-0", string.int_to_string(int.abs(SafeExponent))])
         ;
-            ExponentStr = E ++ string__int_to_string(SafeExponent)
+            ExponentStr = E ++ string.int_to_string(SafeExponent)
         )
     ),
     ScientificFloat = SafeBase ++ ExponentStr.
@@ -2783,7 +2785,7 @@
 
     % Is mantissa one digit long?
     split_at_decimal_point(UnsafeBase, MantissaStr, _FractionStr),
-    ( string__length(MantissaStr) > 1 ->
+    ( string.length(MantissaStr) > 1 ->
         % We will need need to move decimal pt one place to the left:
         % therefore, increment exponent.
         Exponent = UnsafeExponent + 1
@@ -2797,11 +2799,11 @@
 :- func remove_trailing_zeros(string) = string.
 
 remove_trailing_zeros(Float) = TrimmedFloat :-
-    FloatCharList = string__to_char_list(Float),
-    FloatCharListRev = list__reverse(FloatCharList),
+    FloatCharList = string.to_char_list(Float),
+    FloatCharListRev = list.reverse(FloatCharList),
     TrimmedFloatRevCharList = remove_zeros(FloatCharListRev),
-    TrimmedFloatCharList = list__reverse(TrimmedFloatRevCharList),
-    TrimmedFloat = string__from_char_list(TrimmedFloatCharList).
+    TrimmedFloatCharList = list.reverse(TrimmedFloatRevCharList),
+    TrimmedFloat = string.from_char_list(TrimmedFloatCharList).
 
     % Given a char list, this function removes all leading zeros, including
     % decimal point, if need be.
@@ -2824,8 +2826,8 @@
 
 decimal_pos(Float) = Pos :-
     split_at_decimal_point(Float, MantissaStr, _FractionStr),
-    NumZeros = string__length(MantissaStr) - 1,
-    Pos = find_non_zero_pos(string__to_char_list(Float), NumZeros).
+    NumZeros = string.length(MantissaStr) - 1,
+    Pos = find_non_zero_pos(string.to_char_list(Float), NumZeros).
 
     % Given a list of chars representing a floating point number, this
     % function determines the the first position containing a non-zero digit.
@@ -2862,19 +2864,19 @@
     split_at_decimal_point(Float, MantissaStr, FractionStr),
     ( Place < 0 ->
         DecimalPos = abs(Place),
-        PaddedMantissaStr = string__substring(FractionStr, 0, DecimalPos),
+        PaddedMantissaStr = string.substring(FractionStr, 0, DecimalPos),
 
         % Get rid of superfluous zeros.
-        MantissaInt = string__det_to_int(PaddedMantissaStr),
-        ExpMantissaStr = string__int_to_string(MantissaInt),
+        MantissaInt = string.det_to_int(PaddedMantissaStr),
+        ExpMantissaStr = string.int_to_string(MantissaInt),
 
         % Create fractional part.
         PaddedFractionStr = pad_right(FractionStr, '0', Prec + 1),
-        ExpFractionStr = string__substring(PaddedFractionStr, DecimalPos,
+        ExpFractionStr = string.substring(PaddedFractionStr, DecimalPos,
             Prec + 1)
     ; Place > 0 ->
-        ExpMantissaStr = string__substring(MantissaStr, 0, 1),
-        FirstHalfOfFractionStr = string__substring(MantissaStr, 1, Place),
+        ExpMantissaStr = string.substring(MantissaStr, 0, 1),
+        FirstHalfOfFractionStr = string.substring(MantissaStr, 1, Place),
         ExpFractionStr = FirstHalfOfFractionStr ++ FractionStr
     ;
         ExpMantissaStr = MantissaStr,
@@ -2892,21 +2894,21 @@
 
 change_precision(Prec, OldFloat) = NewFloat :-
     split_at_decimal_point(OldFloat, MantissaStr, FractionStr),
-    FracStrLen = string__length(FractionStr),
+    FracStrLen = string.length(FractionStr),
     ( Prec > FracStrLen ->
-        PrecFracStr = string__pad_right(FractionStr, '0', Prec),
+        PrecFracStr = string.pad_right(FractionStr, '0', Prec),
         PrecMantissaStr = MantissaStr
     ; Prec < FracStrLen ->
-        UnroundedFrac = string__substring(FractionStr, 0, Prec),
-        NextDigit = string__index_det(FractionStr, Prec),
+        UnroundedFrac = string.substring(FractionStr, 0, Prec),
+        NextDigit = string.index_det(FractionStr, Prec),
         (
             UnroundedFrac \= "",
-            (char__to_int(NextDigit) - char__to_int('0')) >= 5
+            (char.to_int(NextDigit) - char.to_int('0')) >= 5
         ->
-            NewPrecFrac = string__det_to_int(UnroundedFrac) + 1,
-            NewPrecFracStrNotOK = string__int_to_string( NewPrecFrac),
-            NewPrecFracStr = string__pad_left(NewPrecFracStrNotOK, '0', Prec),
-            ( string__length(NewPrecFracStr) > string__length(UnroundedFrac) ->
+            NewPrecFrac = string.det_to_int(UnroundedFrac) + 1,
+            NewPrecFracStrNotOK = string.int_to_string( NewPrecFrac),
+            NewPrecFracStr = string.pad_left(NewPrecFracStrNotOK, '0', Prec),
+            ( string.length(NewPrecFracStr) > string.length(UnroundedFrac) ->
                 PrecFracStr = substring(NewPrecFracStr, 1, Prec),
                 PrecMantissaInt = det_to_int(MantissaStr) + 1,
                 PrecMantissaStr = int_to_string(PrecMantissaInt)
@@ -2916,7 +2918,7 @@
             )
         ;
             UnroundedFrac = "",
-            (char__to_int(NextDigit) - char__to_int('0')) >= 5
+            (char.to_int(NextDigit) - char.to_int('0')) >= 5
         ->
             PrecMantissaInt = det_to_int(MantissaStr) + 1,
             PrecMantissaStr = int_to_string(PrecMantissaInt),
@@ -2935,16 +2937,16 @@
 :- pred split_at_exponent(string::in, string::out, string::out) is det.
 
 split_at_exponent(Str, Float, Exponent) :-
-    FloatAndExponent = string__words(is_exponent, Str),
-    list__index0_det(FloatAndExponent, 0, Float),
-    list__index0_det(FloatAndExponent, 1, Exponent).
+    FloatAndExponent = string.words(is_exponent, Str),
+    list.index0_det(FloatAndExponent, 0, Float),
+    list.index0_det(FloatAndExponent, 1, Exponent).
 
 :- pred split_at_decimal_point(string::in, string::out, string::out) is det.
 
 split_at_decimal_point(Str, Mantissa, Fraction) :-
-    MantAndFrac = string__words(is_decimal_point, Str),
-    list__index0_det(MantAndFrac, 0, Mantissa),
-    ( list__index0(MantAndFrac, 1, Fraction0) ->
+    MantAndFrac = string.words(is_decimal_point, Str),
+    list.index0_det(MantAndFrac, 0, Mantissa),
+    ( list.index0(MantAndFrac, 1, Fraction0) ->
         Fraction = Fraction0
     ;
         Fraction = ""
@@ -2975,36 +2977,36 @@
 
 %-----------------------------------------------------------------------------%
 
-string__from_float(Flt) = string__float_to_string(Flt).
+string.from_float(Flt) = string.float_to_string(Flt).
 
 :- pragma foreign_proc("C",
-    string__float_to_string(Flt::in, Str::uo),
+    string.float_to_string(Flt::in, Str::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     /*
     ** For efficiency reasons we duplicate the C implementation
-    ** of string__lowlevel_float_to_string.
+    ** of string.lowlevel_float_to_string.
     */
     MR_float_to_string(Flt, Str);
 }").
 
-string__float_to_string(Float, unsafe_promise_unique(String)) :-
+string.float_to_string(Float, unsafe_promise_unique(String)) :-
     % XXX The unsafe_promise_unique is needed because in
-    % string__float_to_string_2 the call to string__to_float doesn't
+    % string.float_to_string_2 the call to string.to_float doesn't
     % have a (ui, out) mode hence the output string cannot be unique.
-    String = string__float_to_string_2(min_precision, Float).
+    String = string.float_to_string_2(min_precision, Float).
 
-:- func string__float_to_string_2(int, float) = (string) is det.
+:- func string.float_to_string_2(int, float) = (string) is det.
 
-string__float_to_string_2(Prec, Float) = String :-
-    string__format("%#." ++ int_to_string(Prec) ++ "g", [f(Float)], Tmp),
+string.float_to_string_2(Prec, Float) = String :-
+    string.format("%#." ++ int_to_string(Prec) ++ "g", [f(Float)], Tmp),
     ( Prec = max_precision ->
         String = Tmp
     ;
-        ( string__to_float(Tmp, Float) ->
+        ( string.to_float(Tmp, Float) ->
             String = Tmp
         ;
-            String = string__float_to_string_2(Prec + 1, Float)
+            String = string.float_to_string_2(Prec + 1, Float)
         )
     ).
 
@@ -3021,10 +3023,10 @@
 :- func max_precision = int.
 max_precision = min_precision + 2.
 
-% string__lowlevel_float_to_string differs from string__float_to_string in that
-% it must be implemented without calling string__format (e.g. by invoking some
+% string.lowlevel_float_to_string differs from string.float_to_string in that
+% it must be implemented without calling string.format (e.g. by invoking some
 % foreign language routine to do the conversion) as this is the predicate
-% string__format uses to get the initial string representation of a float.
+% string.format uses to get the initial string representation of a float.
 %
 % The string returned must match one of the following regular expression:
 %   ^[+-]?[0-9]*\.?[0-9]+((e|E)[0-9]+)?$
@@ -3034,21 +3036,21 @@
 % and the string returned must have sufficient precision for representing
 % the float.
 %
-:- pred string__lowlevel_float_to_string(float::in, string::uo) is det.
+:- pred string.lowlevel_float_to_string(float::in, string::uo) is det.
 
 :- pragma foreign_proc("C",
-    string__lowlevel_float_to_string(Flt::in, Str::uo),
+    string.lowlevel_float_to_string(Flt::in, Str::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     /*
     ** Note any changes here will require the same changes in
-    ** string__float_to_string.
+    ** string.float_to_string.
     */
     MR_float_to_string(Flt, Str);
 }").
 
 :- pragma foreign_proc("C#",
-    string__lowlevel_float_to_string(FloatVal::in, FloatString::uo),
+    string.lowlevel_float_to_string(FloatVal::in, FloatString::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     // The R format string prints the double out such that it can be
@@ -3060,23 +3062,23 @@
 ").
 
 :- pragma foreign_proc("Java",
-    string__lowlevel_float_to_string(FloatVal::in, FloatString::uo),
+    string.lowlevel_float_to_string(FloatVal::in, FloatString::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     FloatString = java.lang.Double.toString(FloatVal);
 ").
 
-string__det_to_float(FloatString) =
-    ( string__to_float(FloatString, FloatVal) ->
+string.det_to_float(FloatString) =
+    ( string.to_float(FloatString, FloatVal) ->
       FloatVal
     ;
       func_error("string.det_to_float/1 - conversion failed.")
     ).
 
-:- pragma export(string__to_float(in, out), "ML_string_to_float").
+:- pragma export(string.to_float(in, out), "ML_string_to_float").
 
 :- pragma foreign_proc("C",
-    string__to_float(FloatString::in, FloatVal::out),
+    string.to_float(FloatString::in, FloatVal::out),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     /*
@@ -3091,7 +3093,7 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__to_float(FloatString::in, FloatVal::out),
+    string.to_float(FloatString::in, FloatVal::out),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     // leading or trailing whitespace is not allowed
@@ -3114,7 +3116,7 @@
 }").
 
 :- pragma foreign_proc("Java",
-    string__to_float(FloatString::in, FloatVal::out),
+    string.to_float(FloatString::in, FloatVal::out),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     FloatVal = 0.0;     // FloatVal must be initialized to suppress
@@ -3166,30 +3168,30 @@
     % but the '\0' is an implementation detail which really
     % shouldn't be considered to be part of the string itself.
 :- pragma foreign_proc("C",
-    string__contains_char(Str::in, Ch::in),
+    string.contains_char(Str::in, Ch::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     SUCCESS_INDICATOR = (strchr(Str, Ch) != NULL) && Ch != '\\0';
 ").
 :- pragma foreign_proc("C#",
-    string__contains_char(Str::in, Ch::in),
+    string.contains_char(Str::in, Ch::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     SUCCESS_INDICATOR = (Str.IndexOf(Ch) != -1);
 ").
-string__contains_char(String, Char) :-
-    string__contains_char(String, Char, 0, string__length(String)).
+string.contains_char(String, Char) :-
+    string.contains_char(String, Char, 0, string.length(String)).
 
-:- pred string__contains_char(string::in, char::in, int::in, int::in)
+:- pred string.contains_char(string::in, char::in, int::in, int::in)
     is semidet.
 
-string__contains_char(Str, Char, Index, Length) :-
+string.contains_char(Str, Char, Index, Length) :-
     ( Index < Length ->
-        string__unsafe_index(Str, Index, IndexChar),
+        string.unsafe_index(Str, Index, IndexChar),
         ( IndexChar = Char ->
             true
         ;
-            string__contains_char(Str, Char, Index + 1, Length)
+            string.contains_char(Str, Char, Index + 1, Length)
         )
     ;
         fail
@@ -3197,24 +3199,24 @@
 
 /*-----------------------------------------------------------------------*/
 
-% It's important to inline string__index and string__index_det.
+% It's important to inline string.index and string.index_det.
 % so that the compiler can do loop invariant hoisting
-% on calls to string__length that occur in loops.
-:- pragma inline(string__index/3).
+% on calls to string.length that occur in loops.
+:- pragma inline(string.index/3).
 
-string__index(Str, Index, Char) :-
-    Len = string__length(Str),
-    ( string__index_check(Index, Len) ->
-        string__unsafe_index(Str, Index, Char)
+string.index(Str, Index, Char) :-
+    Len = string.length(Str),
+    ( string.index_check(Index, Len) ->
+        string.unsafe_index(Str, Index, Char)
     ;
         fail
     ).
 
-:- pred string__index_check(int::in, int::in) is semidet.
+:- pred string.index_check(int::in, int::in) is semidet.
 
 % We should consider making this routine a compiler built-in.
 :- pragma foreign_proc("C",
-    string__index_check(Index::in, Length::in),
+    string.index_check(Index::in, Length::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     /*
@@ -3227,44 +3229,44 @@
     SUCCESS_INDICATOR = ((MR_Unsigned) Index < (MR_Unsigned) Length);
 ").
 :- pragma foreign_proc("C#",
-    string__index_check(Index::in, Length::in),
+    string.index_check(Index::in, Length::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     SUCCESS_INDICATOR = ((uint) Index < (uint) Length);
 ").
-string__index_check(Index, Length) :-
+string.index_check(Index, Length) :-
     Index >= 0,
     Index < Length.
 
 /*-----------------------------------------------------------------------*/
 
 :- pragma foreign_proc("C",
-    string__unsafe_index(Str::in, Index::in, Ch::uo),
+    string.unsafe_index(Str::in, Index::in, Ch::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     Ch = Str[Index];
 ").
 :- pragma foreign_proc("C#",
-    string__unsafe_index(Str::in, Index::in, Ch::uo),
+    string.unsafe_index(Str::in, Index::in, Ch::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Ch = Str[Index];
 ").
 :- pragma foreign_proc("Java",
-    string__unsafe_index(Str::in, Index::in, Ch::uo),
+    string.unsafe_index(Str::in, Index::in, Ch::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Ch = Str.charAt(Index);
 ").
-string__unsafe_index(Str, Index, Char) :-
-    ( string__first_char(Str, First, Rest) ->
+string.unsafe_index(Str, Index, Char) :-
+    ( string.first_char(Str, First, Rest) ->
         ( Index = 0 ->
             Char = First
         ;
-            string__unsafe_index(Rest, Index - 1, Char)
+            string.unsafe_index(Rest, Index - 1, Char)
         )
     ;
-        error("string__unsafe_index: out of bounds")
+        error("string.unsafe_index: out of bounds")
     ).
 
 String ^ unsafe_elem(Index) = unsafe_index(String, Index).
@@ -3300,7 +3302,7 @@
 ").
 
 :- pragma foreign_proc("C",
-    string__set_char(Ch::in, Index::in, Str0::in, Str::out),
+    string.set_char(Ch::in, Index::in, Str0::in, Str::out),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     size_t len = strlen(Str0);
@@ -3314,7 +3316,7 @@
     }
 ").
 :- pragma foreign_proc("C#",
-    string__set_char(Ch::in, Index::in, Str0::in, Str::out),
+    string.set_char(Ch::in, Index::in, Str0::in, Str::out),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     if (Index >= Str0.Length) {
@@ -3326,13 +3328,13 @@
         SUCCESS_INDICATOR = true;
     }
 ").
-string__set_char(Ch, Index, Str0, Str) :-
-    string__to_char_list(Str0, List0),
-    list__replace_nth(List0, Index + 1, Ch, List),
-    string__to_char_list(Str, List).
+string.set_char(Ch, Index, Str0, Str) :-
+    string.to_char_list(Str0, List0),
+    list.replace_nth(List0, Index + 1, Ch, List),
+    string.to_char_list(Str, List).
 
 % :- pragma foreign_proc("C",
-%   string__set_char(Ch::in, Index::in, Str0::di, Str::uo),
+%   string.set_char(Ch::in, Index::in, Str0::di, Str::uo),
 %   [will_not_call_mercury, promise_pure, thread_safe],
 % "
 %   if ((MR_Unsigned) Index >= strlen(Str0)) {
@@ -3345,7 +3347,7 @@
 % ").
 %
 % :- pragma foreign_proc("C#",
-%   string__set_char(Ch::in, Index::in, Str0::di, Str::uo),
+%   string.set_char(Ch::in, Index::in, Str0::di, Str::uo),
 %   [will_not_call_mercury, promise_pure, thread_safe],
 % "
 %   if (Index >= Str0.Length) {
@@ -3361,7 +3363,7 @@
 /*-----------------------------------------------------------------------*/
 
 :- pragma foreign_proc("C",
-    string__unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
+    string.unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     size_t len = strlen(Str0);
@@ -3370,7 +3372,7 @@
     MR_set_char(Str, Index, Ch);
 ").
 :- pragma foreign_proc("C#",
-    string__unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
+    string.unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Str = System.String.Concat(Str0.Substring(0, Index),
@@ -3378,21 +3380,21 @@
         Str0.Substring(Index + 1));
 ").
 :- pragma foreign_proc("Java",
-    string__unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
+    string.unsafe_set_char(Ch::in, Index::in, Str0::in, Str::out),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Str = Str0.substring(0, Index) + Ch + Str0.substring(Index + 1);
 ").
 
 % :- pragma foreign_proc("C",
-%   string__unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
+%   string.unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
 %   [will_not_call_mercury, promise_pure, thread_safe],
 % "
 %   Str = Str0;
 %   MR_set_char(Str, Index, Ch);
 % ").
 % :- pragma foreign_proc("C#",
-%   string__unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
+%   string.unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
 %   [will_not_call_mercury, promise_pure, thread_safe],
 % "
 %   Str = System.String.Concat(Str0.Substring(0, Index),
@@ -3400,7 +3402,7 @@
 %       Str0.Substring(Index + 1));
 % ").
 % :- pragma foreign_proc("Java",
-%   string__unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
+%   string.unsafe_set_char(Ch::in, Index::in, Str0::di, Str::uo),
 %   [will_not_call_mercury, promise_pure, thread_safe],
 % "
 %   Str = Str0.substring(0, Index) + Ch + Str0.substring(Index + 1);
@@ -3409,75 +3411,75 @@
 /*-----------------------------------------------------------------------*/
 
 :- pragma foreign_proc("C",
-    string__length(Str::in, Length::uo),
+    string.length(Str::in, Length::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     Length = strlen(Str);
 ").
 :- pragma foreign_proc("C#",
-    string__length(Str::in, Length::uo),
+    string.length(Str::in, Length::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Length = Str.Length;
 ").
 :- pragma foreign_proc("Java",
-    string__length(Str::in, Length::uo),
+    string.length(Str::in, Length::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Length = Str.length();
 ").
 
 :- pragma foreign_proc("C",
-    string__length(Str::ui, Length::uo),
+    string.length(Str::ui, Length::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     Length = strlen(Str);
 ").
 :- pragma foreign_proc("C#",
-    string__length(Str::ui, Length::uo),
+    string.length(Str::ui, Length::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     Length = Str.Length;
 ").
 :- pragma foreign_proc("Java",
-    string__length(Str::ui, Length::uo),
+    string.length(Str::ui, Length::uo),
         [will_not_call_mercury, promise_pure, thread_safe], "
     Length = Str.length();
 ").
 
-:- pragma promise_pure(string__length/2).
+:- pragma promise_pure(string.length/2).
 
-string__length(Str0, Len) :-
+string.length(Str0, Len) :-
     % XXX This copy is only necessary because of the ui.
     copy(Str0, Str),
-    string__length_2(Str, 0, Len).
+    string.length_2(Str, 0, Len).
 
-:- pred string__length_2(string::in, int::in, int::out) is det.
+:- pred string.length_2(string::in, int::in, int::out) is det.
 
-string__length_2(Str, Index, Length) :-
-    ( string__index(Str, Index, _) ->
-        string__length_2(Str, Index + 1, Length)
+string.length_2(Str, Index, Length) :-
+    ( string.index(Str, Index, _) ->
+        string.length_2(Str, Index + 1, Length)
     ;
         Length = Index
     ).
 
 /*-----------------------------------------------------------------------*/
 
-:- pragma promise_pure(string__append/3).
+:- pragma promise_pure(string.append/3).
 
-string__append(S1::in, S2::in, S3::in) :-
-    string__append_iii(S1, S2, S3).
-string__append(S1::in, S2::uo, S3::in) :-
-    string__append_ioi(S1, S2, S3).
-string__append(S1::in, S2::in, S3::uo) :-
-    string__append_iio(S1, S2, S3).
-string__append(S1::out, S2::out, S3::in) :-
-    string__append_ooi(S1, S2, S3).
+string.append(S1::in, S2::in, S3::in) :-
+    string.append_iii(S1, S2, S3).
+string.append(S1::in, S2::uo, S3::in) :-
+    string.append_ioi(S1, S2, S3).
+string.append(S1::in, S2::in, S3::uo) :-
+    string.append_iio(S1, S2, S3).
+string.append(S1::out, S2::out, S3::in) :-
+    string.append_ooi(S1, S2, S3).
 
-:- pred string__append_iii(string::in, string::in, string::in) is semidet.
+:- pred string.append_iii(string::in, string::in, string::in) is semidet.
 
 :- pragma foreign_proc("C",
-    string__append_iii(S1::in, S2::in, S3::in),
+    string.append_iii(S1::in, S2::in, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     size_t len_1 = strlen(S1);
@@ -3488,19 +3490,19 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__append_iii(S1::in, S2::in, S3::in),
+    string.append_iii(S1::in, S2::in, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     SUCCESS_INDICATOR = S3.Equals(System.String.Concat(S1, S2));
 }").
 
-string__append_iii(X, Y, Z) :-
-    string__mercury_append(X, Y, Z).
+string.append_iii(X, Y, Z) :-
+    string.mercury_append(X, Y, Z).
 
-:- pred string__append_ioi(string::in, string::uo, string::in) is semidet.
+:- pred string.append_ioi(string::in, string::uo, string::in) is semidet.
 
 :- pragma foreign_proc("C",
-    string__append_ioi(S1::in, S2::uo, S3::in),
+    string.append_ioi(S1::in, S2::uo, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     size_t len_1, len_2, len_3;
@@ -3521,7 +3523,7 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__append_ioi(S1::in, S2::uo, S3::in),
+    string.append_ioi(S1::in, S2::uo, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     if (S3.StartsWith(S1)) {
@@ -3532,13 +3534,13 @@
     }
 }").
 
-string__append_ioi(X, Y, Z) :-
-    string__mercury_append(X, Y, Z).
+string.append_ioi(X, Y, Z) :-
+    string.mercury_append(X, Y, Z).
 
-:- pred string__append_iio(string::in, string::in, string::uo) is det.
+:- pred string.append_iio(string::in, string::in, string::uo) is det.
 
 :- pragma foreign_proc("C",
-    string__append_iio(S1::in, S2::in, S3::uo),
+    string.append_iio(S1::in, S2::in, S3::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     size_t len_1, len_2;
@@ -3550,40 +3552,40 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__append_iio(S1::in, S2::in, S3::uo),
+    string.append_iio(S1::in, S2::in, S3::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     S3 = System.String.Concat(S1, S2);
 }").
 
-string__append_iio(X, Y, Z) :-
-    string__mercury_append(X, Y, Z).
+string.append_iio(X, Y, Z) :-
+    string.mercury_append(X, Y, Z).
 
-:- pred string__append_ooi(string::out, string::out, string::in) is multi.
+:- pred string.append_ooi(string::out, string::out, string::in) is multi.
 
-string__append_ooi(S1, S2, S3) :-
-    S3Len = string__length(S3),
-    string__append_ooi_2(0, S3Len, S1, S2, S3).
+string.append_ooi(S1, S2, S3) :-
+    S3Len = string.length(S3),
+    string.append_ooi_2(0, S3Len, S1, S2, S3).
 
-:- pred string__append_ooi_2(int::in, int::in, string::out, string::out,
+:- pred string.append_ooi_2(int::in, int::in, string::out, string::out,
     string::in) is multi.
 
-string__append_ooi_2(NextS1Len, S3Len, S1, S2, S3) :-
+string.append_ooi_2(NextS1Len, S3Len, S1, S2, S3) :-
     ( NextS1Len = S3Len ->
-        string__append_ooi_3(NextS1Len, S3Len, S1, S2, S3)
+        string.append_ooi_3(NextS1Len, S3Len, S1, S2, S3)
     ;
         (
-            string__append_ooi_3(NextS1Len, S3Len, S1, S2, S3)
+            string.append_ooi_3(NextS1Len, S3Len, S1, S2, S3)
         ;
-            string__append_ooi_2(NextS1Len + 1, S3Len, S1, S2, S3)
+            string.append_ooi_2(NextS1Len + 1, S3Len, S1, S2, S3)
         )
     ).
 
-:- pred string__append_ooi_3(int::in, int::in, string::out,
+:- pred string.append_ooi_3(int::in, int::in, string::out,
     string::out, string::in) is det.
 
 :- pragma foreign_proc("C",
-    string__append_ooi_3(S1Len::in, S3Len::in, S1::out, S2::out, S3::in),
+    string.append_ooi_3(S1Len::in, S3Len::in, S1::out, S2::out, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_allocate_aligned_string_msg(S1, S1Len, MR_PROC_LABEL);
@@ -3594,33 +3596,33 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__append_ooi_3(S1Len::in, _S3Len::in, S1::out, S2::out, S3::in),
+    string.append_ooi_3(S1Len::in, _S3Len::in, S1::out, S2::out, S3::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     S1 = S3.Substring(0, S1Len);
     S2 = S3.Substring(S1Len);
 ").
 
-string__append_ooi_3(S1Len, _S3Len, S1, S2, S3) :-
-    string__split(S3, S1Len, S1, S2).
+string.append_ooi_3(S1Len, _S3Len, S1, S2, S3) :-
+    string.split(S3, S1Len, S1, S2).
 
-:- pred string__mercury_append(string, string, string).
-:- mode string__mercury_append(in, in, in) is semidet.  % implied
-:- mode string__mercury_append(in, uo, in) is semidet.
-:- mode string__mercury_append(in, in, uo) is det.
-:- mode string__mercury_append(uo, uo, in) is multi.
-
-string__mercury_append(X, Y, Z) :-
-    string__to_char_list(X, XList),
-    string__to_char_list(Y, YList),
-    string__to_char_list(Z, ZList),
-    list__append(XList, YList, ZList).
+:- pred string.mercury_append(string, string, string).
+:- mode string.mercury_append(in, in, in) is semidet.  % implied
+:- mode string.mercury_append(in, uo, in) is semidet.
+:- mode string.mercury_append(in, in, uo) is det.
+:- mode string.mercury_append(uo, uo, in) is multi.
+
+string.mercury_append(X, Y, Z) :-
+    string.to_char_list(X, XList),
+    string.to_char_list(Y, YList),
+    string.to_char_list(Z, ZList),
+    list.append(XList, YList, ZList).
 
 /*-----------------------------------------------------------------------*/
 
-string__substring(Str::in, Start::in, Count::in, SubStr::uo) :-
-    End = min(Start + Count, string__length(Str)),
-    SubStr = string__from_char_list(strchars(Start, End, Str)).
+string.substring(Str::in, Start::in, Count::in, SubStr::uo) :-
+    End = min(Start + Count, string.length(Str)),
+    SubStr = string.from_char_list(strchars(Start, End, Str)).
 
 :- func strchars(int, int, string) = list(char).
 
@@ -3632,11 +3634,11 @@
     ->
         []
     ;
-        [string__index_det(Str, I) | strchars(I + 1, End, Str)]
+        [string.index_det(Str, I) | strchars(I + 1, End, Str)]
     ).
 
 :- pragma foreign_proc("C",
-    string__substring(Str::in, Start::in, Count::in, SubString::uo),
+    string.substring(Str::in, Start::in, Count::in, SubString::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Integer  len;
@@ -3656,7 +3658,7 @@
 }").
 
 :- pragma foreign_proc("C",
-    string__unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
+    string.unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Integer len;
@@ -3666,20 +3668,20 @@
     SubString[Count] = '\\0';
 }").
 :- pragma foreign_proc("C#",
-    string__unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
+    string.unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     SubString = Str.Substring(Start, Count);
 }").
 :- pragma foreign_proc("Java",
-    string__unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
+    string.unsafe_substring(Str::in, Start::in, Count::in, SubString::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     SubString = Str.substring(Start, Start + Count);
 ").
 
 :- pragma foreign_proc("C",
-    string__split(Str::in, Count::in, Left::uo, Right::uo),
+    string.split(Str::in, Count::in, Left::uo, Right::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     MR_Integer  len;
@@ -3707,7 +3709,7 @@
 }").
 
 :- pragma foreign_proc("C#",
-    string__split(Str::in, Count::in, Left::uo, Right::uo),
+    string.split(Str::in, Count::in, Left::uo, Right::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     int len;
@@ -3725,30 +3727,30 @@
     }
 }").
 
-string__split(Str, Count, Left, Right) :-
+string.split(Str, Count, Left, Right) :-
     ( Count =< 0 ->
         Left = "",
         copy(Str, Right)
     ;
-        string__to_char_list(Str, List),
-        Len = string__length(Str),
+        string.to_char_list(Str, List),
+        Len = string.length(Str),
         ( Count > Len ->
             Num = Len
         ;
             Num = Count
         ),
-        ( list__split_list(Num, List, LeftList, RightList) ->
-            string__to_char_list(Left, LeftList),
-            string__to_char_list(Right, RightList)
+        ( list.split_list(Num, List, LeftList, RightList) ->
+            string.to_char_list(Left, LeftList),
+            string.to_char_list(Right, RightList)
         ;
-            error("string__split")
+            error("string.split")
         )
     ).
 
 /*-----------------------------------------------------------------------*/
 
 :- pragma foreign_proc("C",
-    string__first_char(Str::in, First::in, Rest::in),
+    string.first_char(Str::in, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     SUCCESS_INDICATOR = (
@@ -3758,7 +3760,7 @@
     );
 ").
 :- pragma foreign_proc("C#",
-    string__first_char(Str::in, First::in, Rest::in),
+    string.first_char(Str::in, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     int len = Str.Length;
@@ -3769,7 +3771,7 @@
     );
 ").
 :- pragma foreign_proc("Java",
-    string__first_char(Str::in, First::in, Rest::in),
+    string.first_char(Str::in, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     succeeded = (Str.length() == Rest.length() + 1 &&
@@ -3778,14 +3780,14 @@
 ").
 
 :- pragma foreign_proc("C",
-    string__first_char(Str::in, First::uo, Rest::in),
+    string.first_char(Str::in, First::uo, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "
     First = Str[0];
     SUCCESS_INDICATOR = (First != '\\0' && strcmp(Str + 1, Rest) == 0);
 ").
 :- pragma foreign_proc("C#",
-    string__first_char(Str::in, First::uo, Rest::in),
+    string.first_char(Str::in, First::uo, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     int len = Str.Length;
@@ -3797,7 +3799,7 @@
     }
 ").
 :- pragma foreign_proc("Java",
-    string__first_char(Str::in, First::uo, Rest::in),
+    string.first_char(Str::in, First::uo, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "
     if (Str.length() == Rest.length() + 1 && Str.endsWith(Rest)) {
@@ -3811,7 +3813,7 @@
 ").
 
 :- pragma foreign_proc("C",
-    string__first_char(Str::in, First::in, Rest::uo),
+    string.first_char(Str::in, First::in, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     if (Str[0] != First || First == '\\0') {
@@ -3827,7 +3829,7 @@
     }
 }").
 :- pragma foreign_proc("C#",
-    string__first_char(Str::in, First::in, Rest::uo),
+    string.first_char(Str::in, First::in, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     int len = Str.Length;
@@ -3840,7 +3842,7 @@
     }
 }").
 :- pragma foreign_proc("Java",
-    string__first_char(Str::in, First::in, Rest::uo),
+    string.first_char(Str::in, First::in, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     int len = Str.length();
@@ -3856,7 +3858,7 @@
 }").
 
 :- pragma foreign_proc("C",
-    string__first_char(Str::in, First::uo, Rest::uo),
+    string.first_char(Str::in, First::uo, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     First = Str[0];
@@ -3873,7 +3875,7 @@
     }
 }").
 :- pragma foreign_proc("C#",
-    string__first_char(Str::in, First::uo, Rest::uo),
+    string.first_char(Str::in, First::uo, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     if (Str.Length == 0) {
@@ -3885,7 +3887,7 @@
     }
 }").
 :- pragma foreign_proc("Java",
-    string__first_char(Str::in, First::uo, Rest::uo),
+    string.first_char(Str::in, First::uo, Rest::uo),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     if (Str.length() == 0) {
@@ -3901,7 +3903,7 @@
 }").
 
 :- pragma foreign_proc("C",
-    string__first_char(Str::uo, First::in, Rest::in),
+    string.first_char(Str::uo, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe, will_not_modify_trail],
 "{
     size_t len = strlen(Rest) + 1;
@@ -3910,7 +3912,7 @@
     strcpy(Str + 1, Rest);
 }").
 :- pragma foreign_proc("C#",
-    string__first_char(Str::uo, First::in, Rest::in),
+    string.first_char(Str::uo, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     string FirstStr;
@@ -3918,7 +3920,7 @@
     Str = System.String.Concat(FirstStr, Rest);
 }").
 :- pragma foreign_proc("Java",
-    string__first_char(Str::uo, First::in, Rest::in),
+    string.first_char(Str::uo, First::in, Rest::in),
     [will_not_call_mercury, promise_pure, thread_safe],
 "{
     java.lang.String FirstStr = java.lang.String.valueOf(First);
@@ -3930,99 +3932,99 @@
 % Ralph Becket <rwab1 at cl.cam.ac.uk> 27/04/99
 % Functional forms added.
 
-string__length(S) = L :-
-    string__length(S, L).
+string.length(S) = L :-
+    string.length(S, L).
 
-string__append(S1, S2) = S3 :-
-    string__append(S1, S2, S3).
+string.append(S1, S2) = S3 :-
+    string.append(S1, S2, S3).
 
-string__char_to_string(C) = S1 :-
-    string__char_to_string(C, S1).
+string.char_to_string(C) = S1 :-
+    string.char_to_string(C, S1).
 
-string__int_to_string(N) = S1 :-
-    string__int_to_string(N, S1).
+string.int_to_string(N) = S1 :-
+    string.int_to_string(N, S1).
 
-string__int_to_base_string(N1, N2) = S2 :-
-    string__int_to_base_string(N1, N2, S2).
+string.int_to_base_string(N1, N2) = S2 :-
+    string.int_to_base_string(N1, N2, S2).
 
-string__float_to_string(R) = S2 :-
-    string__float_to_string(R, S2).
+string.float_to_string(R) = S2 :-
+    string.float_to_string(R, S2).
 
-string__replace_all(S1, S2, S3) = S4 :-
-    string__replace_all(S1, S2, S3, S4).
+string.replace_all(S1, S2, S3) = S4 :-
+    string.replace_all(S1, S2, S3, S4).
 
-string__to_lower(S1) = S2 :-
-    string__to_lower(S1, S2).
+string.to_lower(S1) = S2 :-
+    string.to_lower(S1, S2).
 
-string__to_upper(S1) = S2 :-
-    string__to_upper(S1, S2).
+string.to_upper(S1) = S2 :-
+    string.to_upper(S1, S2).
 
-string__capitalize_first(S1) = S2 :-
-    string__capitalize_first(S1, S2).
+string.capitalize_first(S1) = S2 :-
+    string.capitalize_first(S1, S2).
 
-string__uncapitalize_first(S1) = S2 :-
-    string__uncapitalize_first(S1, S2).
+string.uncapitalize_first(S1) = S2 :-
+    string.uncapitalize_first(S1, S2).
 
-string__to_char_list(S) = Cs :-
-    string__to_char_list(S, Cs).
+string.to_char_list(S) = Cs :-
+    string.to_char_list(S, Cs).
 
-string__from_char_list(Cs) = S :-
-    string__from_char_list(Cs, S).
+string.from_char_list(Cs) = S :-
+    string.from_char_list(Cs, S).
 
-string__from_rev_char_list(Cs) = S :-
-    string__from_rev_char_list(Cs, S).
+string.from_rev_char_list(Cs) = S :-
+    string.from_rev_char_list(Cs, S).
 
-string__pad_left(S1, C, N) = S2 :-
-    string__pad_left(S1, C, N, S2).
+string.pad_left(S1, C, N) = S2 :-
+    string.pad_left(S1, C, N, S2).
 
-string__pad_right(S1, C, N) = S2 :-
-    string__pad_right(S1, C, N, S2).
+string.pad_right(S1, C, N) = S2 :-
+    string.pad_right(S1, C, N, S2).
 
-string__duplicate_char(C, N) = S :-
-    string__duplicate_char(C, N, S).
+string.duplicate_char(C, N) = S :-
+    string.duplicate_char(C, N, S).
 
-string__index_det(S, N) = C :-
-    string__index_det(S, N, C).
+string.index_det(S, N) = C :-
+    string.index_det(S, N, C).
 
-string__unsafe_index(S, N) = C :-
-    string__unsafe_index(S, N, C).
+string.unsafe_index(S, N) = C :-
+    string.unsafe_index(S, N, C).
 
-string__set_char_det(C, N, S0) = S :-
-    string__set_char_det(C, N, S0, S).
+string.set_char_det(C, N, S0) = S :-
+    string.set_char_det(C, N, S0, S).
 
-string__unsafe_set_char(C, N, S0) = S :-
-    string__unsafe_set_char(C, N, S0, S).
+string.unsafe_set_char(C, N, S0) = S :-
+    string.unsafe_set_char(C, N, S0, S).
 
-string__foldl(F, S, A) = B :-
+string.foldl(F, S, A) = B :-
     P = ( pred(X::in, Y::in, Z::out) is det :- Z = F(X, Y) ),
-    string__foldl(P, S, A, B).
+    string.foldl(P, S, A, B).
 
-string__foldl_substring(F, S, Start, Count, A) = B :-
+string.foldl_substring(F, S, Start, Count, A) = B :-
     P = ( pred(X::in, Y::in, Z::out) is det :- Z = F(X, Y) ),
-    string__foldl_substring(P, S, Start, Count, A, B).
+    string.foldl_substring(P, S, Start, Count, A, B).
 
-string__left(S1, N) = S2 :-
-    string__left(S1, N, S2).
+string.left(S1, N) = S2 :-
+    string.left(S1, N, S2).
 
-string__right(S1, N) = S2 :-
-    string__right(S1, N, S2).
+string.right(S1, N) = S2 :-
+    string.right(S1, N, S2).
 
-string__substring(S1, N1, N2) = S2 :-
-    string__substring(S1, N1, N2, S2).
+string.substring(S1, N1, N2) = S2 :-
+    string.substring(S1, N1, N2, S2).
 
-string__unsafe_substring(S1, N1, N2) = S2 :-
-    string__unsafe_substring(S1, N1, N2, S2).
+string.unsafe_substring(S1, N1, N2) = S2 :-
+    string.unsafe_substring(S1, N1, N2, S2).
 
-string__hash(S) = N :-
-    string__hash(S, N).
+string.hash(S) = N :-
+    string.hash(S, N).
 
-string__format(S1, PT) = S2 :-
-    string__format(S1, PT, S2).
+string.format(S1, PT) = S2 :-
+    string.format(S1, PT, S2).
 
 %------------------------------------------------------------------------------%
 
-string__words(SepP, String) = Words :-
-    I = preceding_boundary(isnt(SepP), String, string__length(String) - 1),
+string.words(SepP, String) = Words :-
+    I = preceding_boundary(isnt(SepP), String, string.length(String) - 1),
     Words = words_2(SepP, String, I, []).
 
 %------------------------------------------------------------------------------%
@@ -4035,7 +4037,7 @@
         Words = Words0
     ;
         WordPre = preceding_boundary(SepP, String, WordEnd),
-        Word = string__unsafe_substring(String, WordPre + 1,
+        Word = string.unsafe_substring(String, WordPre + 1,
             WordEnd - WordPre),
         PrevWordEnd = preceding_boundary(isnt(SepP), String, WordPre),
         Words = words_2(SepP, String, PrevWordEnd, [Word | Words0])
@@ -4043,7 +4045,7 @@
 
 %------------------------------------------------------------------------------%
 
-string__words(String) = string__words(char__is_whitespace, String).
+string.words(String) = string.words(char.is_whitespace, String).
 
 %------------------------------------------------------------------------------%
 
@@ -4059,7 +4061,7 @@
 preceding_boundary(SepP, String, I) =
     ( I < 0 ->
         I
-    ; SepP(string__unsafe_index(String, I)) ->
+    ; SepP(string.unsafe_index(String, I)) ->
         I
     ;
         preceding_boundary(SepP, String, I - 1)
@@ -4067,19 +4069,19 @@
 
 %------------------------------------------------------------------------------%
 
-S1 ++ S2 = string__append(S1, S2).
+S1 ++ S2 = string.append(S1, S2).
 
 %------------------------------------------------------------------------------%
 
-string__det_to_int(S) = string__det_base_string_to_int(10, S).
+string.det_to_int(S) = string.det_base_string_to_int(10, S).
 
 %------------------------------------------------------------------------------%
 
-string__det_base_string_to_int(Base, S) = N :-
-    ( string__base_string_to_int(Base, S, N0) ->
+string.det_base_string_to_int(Base, S) = N :-
+    ( string.base_string_to_int(Base, S, N0) ->
         N = N0
     ;
-        error("string__det_base_string_to_int/2: conversion failed")
+        error("string.det_base_string_to_int/2: conversion failed")
     ).
 
 %-----------------------------------------------------------------------------%
@@ -4167,18 +4169,18 @@
 
 % Various different versions of univ_to_string.
 
-string__string(Univ) = String :-
-    string__string(canonicalize, ops__init_mercury_op_table, Univ, String).
+string.string(Univ) = String :-
+    string.string(canonicalize, ops.init_mercury_op_table, Univ, String).
 
-string__string(OpsTable, Univ) = String :-
-    string__string(canonicalize, OpsTable, Univ, String).
+string.string(OpsTable, Univ) = String :-
+    string.string(canonicalize, OpsTable, Univ, String).
 
-string__string(NonCanon, OpsTable, X, String) :-
+string.string(NonCanon, OpsTable, X, String) :-
     value_to_revstrings(NonCanon, OpsTable, X, [], RevStrings),
-    String = string__append_list(list__reverse(RevStrings)).
+    String = string.append_list(list.reverse(RevStrings)).
 
-:- pred value_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, T, revstrings, revstrings).
+:- pred value_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, T, revstrings, revstrings).
 :- mode value_to_revstrings(in(do_not_allow), in, in, in, out) is det.
 :- mode value_to_revstrings(in(canonicalize), in, in, in, out) is det.
 :- mode value_to_revstrings(in(include_details_cc), in, in, in, out)
@@ -4186,11 +4188,11 @@
 :- mode value_to_revstrings(in, in, in, in, out) is cc_multi.
 
 value_to_revstrings(NonCanon, OpsTable, X, !Rs) :-
-    Priority = ops__max_priority(OpsTable) + 1,
+    Priority = ops.max_priority(OpsTable) + 1,
     value_to_revstrings(NonCanon, OpsTable, Priority, X, !Rs).
 
-:- pred value_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, ops__priority, T, revstrings, revstrings).
+:- pred value_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, ops.priority, T, revstrings, revstrings).
 :- mode value_to_revstrings(in(do_not_allow), in, in, in, in, out) is det.
 :- mode value_to_revstrings(in(canonicalize), in, in, in, in, out) is det.
 :- mode value_to_revstrings(in(include_details_cc), in, in, in, in, out)
@@ -4205,13 +4207,13 @@
     %   and private_builtin:type_info
     %
     ( dynamic_cast(X, String) ->
-        add_revstring(term_io__quoted_string(String), !Rs)
+        add_revstring(term_io.quoted_string(String), !Rs)
     ; dynamic_cast(X, Char) ->
-        add_revstring(term_io__quoted_char(Char), !Rs)
+        add_revstring(term_io.quoted_char(Char), !Rs)
     ; dynamic_cast(X, Int) ->
-        add_revstring(string__int_to_string(Int), !Rs)
+        add_revstring(string.int_to_string(Int), !Rs)
     ; dynamic_cast(X, Float) ->
-        add_revstring(string__float_to_string(Float), !Rs)
+        add_revstring(string.float_to_string(Float), !Rs)
     ; dynamic_cast(X, TypeDesc) ->
         type_desc_to_revstrings(TypeDesc, !Rs)
     ; dynamic_cast(X, TypeCtorDesc) ->
@@ -4232,15 +4234,15 @@
         % rather than the reverse) is also chosen for efficiency, to find
         % failure cheaply in the common cases, rather than for readability.
         %
-        type_desc__type_ctor_and_args(type_of(X), TypeCtor, ArgTypes),
+        type_desc.type_ctor_and_args(type_of(X), TypeCtor, ArgTypes),
         ArgTypes = [ElemType],
-        type_desc__type_ctor_name(TypeCtor) = "array",
-        type_desc__type_ctor_module_name(TypeCtor) = "array"
+        type_desc.type_ctor_name(TypeCtor) = "array",
+        type_desc.type_ctor_module_name(TypeCtor) = "array"
     ->
         % Now that we know the element type, we can constrain the type of
         % the variable `Array' so that we can use det_dynamic_cast.
         %
-        type_desc__has_type(Elem, ElemType),
+        type_desc.has_type(Elem, ElemType),
         same_array_elem_type(Array, Elem),
         det_dynamic_cast(X, Array),
         array_to_revstrings(NonCanon, OpsTable, Array, !Rs)
@@ -4248,12 +4250,12 @@
         % Check if the type is private_builtin.type_info/1.
         % See the comments above for array.array/1.
         %
-        type_desc__type_ctor_and_args(type_of(X), TypeCtor, ArgTypes),
+        type_desc.type_ctor_and_args(type_of(X), TypeCtor, ArgTypes),
         ArgTypes = [ElemType],
-        type_desc__type_ctor_name(TypeCtor) = "type_info",
-        type_desc__type_ctor_module_name(TypeCtor) = "private_builtin"
+        type_desc.type_ctor_name(TypeCtor) = "type_info",
+        type_desc.type_ctor_module_name(TypeCtor) = "private_builtin"
     ->
-        type_desc__has_type(Elem, ElemType),
+        type_desc.has_type(Elem, ElemType),
         same_private_builtin_type(PrivateBuiltinTypeInfo, Elem),
         det_dynamic_cast(X, PrivateBuiltinTypeInfo),
         private_builtin_type_info_to_revstrings(PrivateBuiltinTypeInfo, !Rs)
@@ -4265,13 +4267,13 @@
 
 same_array_elem_type(_, _).
 
-:- pred same_private_builtin_type(private_builtin__type_info::unused,
+:- pred same_private_builtin_type(private_builtin.type_info::unused,
     T::unused) is det.
 
 same_private_builtin_type(_, _).
 
-:- pred ordinary_term_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, ops__priority, T, revstrings, revstrings).
+:- pred ordinary_term_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, ops.priority, T, revstrings, revstrings).
 :- mode ordinary_term_to_revstrings(in(do_not_allow), in, in, in, in, out)
     is det.
 :- mode ordinary_term_to_revstrings(in(canonicalize), in, in, in, in, out)
@@ -4282,7 +4284,7 @@
     is cc_multi.
 
 ordinary_term_to_revstrings(NonCanon, OpsTable, Priority, X, !Rs) :-
-    deconstruct__deconstruct(X, NonCanon, Functor, _Arity, Args),
+    deconstruct.deconstruct(X, NonCanon, Functor, _Arity, Args),
     (
         Functor = "[|]",
         Args = [ListHead, ListTail]
@@ -4313,10 +4315,10 @@
         add_revstring("}", !Rs)
     ;
         Args = [PrefixArg],
-        ops__lookup_prefix_op(OpsTable, Functor, OpPriority, OpAssoc)
+        ops.lookup_prefix_op(OpsTable, Functor, OpPriority, OpAssoc)
     ->
         maybe_add_revstring("(", Priority, OpPriority, !Rs),
-        add_revstring(term_io__quoted_atom(Functor), !Rs),
+        add_revstring(term_io.quoted_atom(Functor), !Rs),
         add_revstring(" ", !Rs),
         adjust_priority(OpPriority, OpAssoc, NewPriority),
         value_to_revstrings(NonCanon, OpsTable, NewPriority,
@@ -4324,18 +4326,18 @@
         maybe_add_revstring(")", Priority, OpPriority, !Rs)
     ;
         Args = [PostfixArg],
-        ops__lookup_postfix_op(OpsTable, Functor, OpPriority, OpAssoc)
+        ops.lookup_postfix_op(OpsTable, Functor, OpPriority, OpAssoc)
     ->
         maybe_add_revstring("(", Priority, OpPriority, !Rs),
         adjust_priority(OpPriority, OpAssoc, NewPriority),
         value_to_revstrings(NonCanon, OpsTable, NewPriority,
             univ_value(PostfixArg), !Rs),
         add_revstring(" ", !Rs),
-        add_revstring(term_io__quoted_atom(Functor), !Rs),
+        add_revstring(term_io.quoted_atom(Functor), !Rs),
         maybe_add_revstring(")", Priority, OpPriority, !Rs)
     ;
         Args = [Arg1, Arg2],
-        ops__lookup_infix_op(OpsTable, Functor, OpPriority,
+        ops.lookup_infix_op(OpsTable, Functor, OpPriority,
             LeftAssoc, RightAssoc)
     ->
         maybe_add_revstring("(", Priority, OpPriority, !Rs),
@@ -4346,7 +4348,7 @@
             add_revstring(", ", !Rs)
         ;
             add_revstring(" ", !Rs),
-            add_revstring(term_io__quoted_atom(Functor), !Rs),
+            add_revstring(term_io.quoted_atom(Functor), !Rs),
             add_revstring(" ", !Rs)
         ),
         adjust_priority(OpPriority, RightAssoc, RightPriority),
@@ -4355,11 +4357,11 @@
         maybe_add_revstring(")", Priority, OpPriority, !Rs)
     ;
         Args = [Arg1, Arg2],
-        ops__lookup_binary_prefix_op(OpsTable, Functor,
+        ops.lookup_binary_prefix_op(OpsTable, Functor,
             OpPriority, FirstAssoc, SecondAssoc)
     ->
         maybe_add_revstring("(", Priority, OpPriority, !Rs),
-        add_revstring(term_io__quoted_atom(Functor), !Rs),
+        add_revstring(term_io.quoted_atom(Functor), !Rs),
         add_revstring(" ", !Rs),
         adjust_priority(OpPriority, FirstAssoc, FirstPriority),
         value_to_revstrings(NonCanon, OpsTable, FirstPriority,
@@ -4372,16 +4374,16 @@
     ;
         (
             Args = [],
-            ops__lookup_op(OpsTable, Functor),
-            Priority =< ops__max_priority(OpsTable)
+            ops.lookup_op(OpsTable, Functor),
+            Priority =< ops.max_priority(OpsTable)
         ->
             add_revstring("(", !Rs),
-            add_revstring(term_io__quoted_atom(Functor), !Rs),
+            add_revstring(term_io.quoted_atom(Functor), !Rs),
             add_revstring(")", !Rs)
         ;
             add_revstring(
-                term_io__quoted_atom(Functor,
-                    term_io__maybe_adjacent_to_graphic_token),
+                term_io.quoted_atom(Functor,
+                    term_io.maybe_adjacent_to_graphic_token),
                 !Rs
             )
         ),
@@ -4396,7 +4398,7 @@
         )
     ).
 
-:- pred maybe_add_revstring(string::in, ops__priority::in, ops__priority::in,
+:- pred maybe_add_revstring(string::in, ops.priority::in, ops.priority::in,
     revstrings::in, revstrings::out) is det.
 
 maybe_add_revstring(String, Priority, OpPriority, !Rs) :-
@@ -4406,14 +4408,14 @@
         true
     ).
 
-:- pred adjust_priority(ops__priority::in, ops__assoc::in, ops__priority::out)
+:- pred adjust_priority(ops.priority::in, ops.assoc::in, ops.priority::out)
     is det.
 
-adjust_priority(Priority, ops__y, Priority).
-adjust_priority(Priority, ops__x, Priority - 1).
+adjust_priority(Priority, ops.y, Priority).
+adjust_priority(Priority, ops.x, Priority - 1).
 
-:- pred univ_list_tail_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, univ, revstrings, revstrings).
+:- pred univ_list_tail_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, univ, revstrings, revstrings).
 :- mode univ_list_tail_to_revstrings(in(do_not_allow), in, in, in, out) is det.
 :- mode univ_list_tail_to_revstrings(in(canonicalize), in, in, in, out) is det.
 :- mode univ_list_tail_to_revstrings(in(include_details_cc), in, in, in, out)
@@ -4421,7 +4423,7 @@
 :- mode univ_list_tail_to_revstrings(in, in, in, in, out) is cc_multi.
 
 univ_list_tail_to_revstrings(NonCanon, OpsTable, Univ, !Rs) :-
-    deconstruct__deconstruct(univ_value(Univ), NonCanon, Functor, _Arity,
+    deconstruct.deconstruct(univ_value(Univ), NonCanon, Functor, _Arity,
         Args),
     (
         Functor = "[|]",
@@ -4442,8 +4444,8 @@
 
     % Write the remaining arguments.
     %
-:- pred term_args_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, list(univ), revstrings, revstrings).
+:- pred term_args_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, list(univ), revstrings, revstrings).
 :- mode term_args_to_revstrings(in(do_not_allow), in, in, in, out) is det.
 :- mode term_args_to_revstrings(in(canonicalize), in, in, in, out) is det.
 :- mode term_args_to_revstrings(in(include_details_cc), in, in, in, out)
@@ -4456,8 +4458,8 @@
     arg_to_revstrings(NonCanon, OpsTable, X, !Rs),
     term_args_to_revstrings(NonCanon, OpsTable, Xs, !Rs).
 
-:- pred arg_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, univ, revstrings, revstrings).
+:- pred arg_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, univ, revstrings, revstrings).
 :- mode arg_to_revstrings(in(do_not_allow), in, in, in, out) is det.
 :- mode arg_to_revstrings(in(canonicalize), in, in, in, out) is det.
 :- mode arg_to_revstrings(in(include_details_cc), in, in, in, out) is cc_multi.
@@ -4467,10 +4469,10 @@
     Priority = comma_priority(OpsTable),
     value_to_revstrings(NonCanon, OpsTable, Priority, univ_value(X), !Rs).
 
-:- func comma_priority(ops__table) = ops__priority.
+:- func comma_priority(ops.table) = ops.priority.
 
 % comma_priority(OpsTable) =
-%   ( ops__lookup_infix_op(OpTable, ",", Priority, _, _) ->
+%   ( ops.lookup_infix_op(OpTable, ",", Priority, _, _) ->
 %       Priority
 %   ;
 %       func_error("arg_priority: can't find the priority of `,'")
@@ -4484,8 +4486,8 @@
 
 c_pointer_to_string(_C_Pointer) = "<<c_pointer>>".
 
-:- pred array_to_revstrings(deconstruct__noncanon_handling,
-    ops__table, array(T), revstrings, revstrings).
+:- pred array_to_revstrings(deconstruct.noncanon_handling,
+    ops.table, array(T), revstrings, revstrings).
 :- mode array_to_revstrings(in(do_not_allow), in, in, in, out) is det.
 :- mode array_to_revstrings(in(canonicalize), in, in, in, out) is det.
 :- mode array_to_revstrings(in(include_details_cc), in, in, in, out)
@@ -4495,22 +4497,22 @@
 array_to_revstrings(NonCanon, OpsTable, Array, !Rs) :-
     add_revstring("array(", !Rs),
     value_to_revstrings(NonCanon, OpsTable,
-        array__to_list(Array) `with_type` list(T), !Rs),
+        array.to_list(Array) `with_type` list(T), !Rs),
     add_revstring(")", !Rs).
 
-:- pred type_desc_to_revstrings(type_desc__type_desc::in,
+:- pred type_desc_to_revstrings(type_desc.type_desc::in,
     revstrings::in, revstrings::out) is det.
 
 type_desc_to_revstrings(TypeDesc, !Rs) :-
-    add_revstring(term_io__quoted_atom(type_desc__type_name(TypeDesc)), !Rs).
+    add_revstring(term_io.quoted_atom(type_desc.type_name(TypeDesc)), !Rs).
 
-:- pred type_ctor_desc_to_revstrings(type_desc__type_ctor_desc::in,
+:- pred type_ctor_desc_to_revstrings(type_desc.type_ctor_desc::in,
     revstrings::in, revstrings::out) is det.
 
 type_ctor_desc_to_revstrings(TypeCtorDesc, !Rs) :-
-    type_desc__type_ctor_name_and_arity(TypeCtorDesc, ModuleName,
+    type_desc.type_ctor_name_and_arity(TypeCtorDesc, ModuleName,
         Name0, Arity0),
-    Name = term_io__quoted_atom(Name0),
+    Name = term_io.quoted_atom(Name0),
     (
         ModuleName = "builtin",
         Name = "func"
@@ -4523,17 +4525,17 @@
         Arity = Arity0
     ),
     ( ModuleName = "builtin" ->
-        String = string__format("%s/%d", [s(Name), i(Arity)])
+        String = string.format("%s/%d", [s(Name), i(Arity)])
     ;
-        String = string__format("%s.%s/%d", [s(ModuleName), s(Name), i(Arity)])
+        String = string.format("%s.%s/%d", [s(ModuleName), s(Name), i(Arity)])
     ),
     add_revstring(String, !Rs).
 
 :- pred private_builtin_type_info_to_revstrings(
-    private_builtin__type_info::in, revstrings::in, revstrings::out) is det.
+    private_builtin.type_info::in, revstrings::in, revstrings::out) is det.
 
 private_builtin_type_info_to_revstrings(PrivateBuiltinTypeInfo, !Rs) :-
-    TypeDesc = rtti_implementation__unsafe_cast(PrivateBuiltinTypeInfo),
+    TypeDesc = rtti_implementation.unsafe_cast(PrivateBuiltinTypeInfo),
     type_desc_to_revstrings(TypeDesc, !Rs).
 
 :- pred det_dynamic_cast(T1::in, T2::out) is det.
@@ -4544,17 +4546,17 @@
 %-----------------------------------------------------------------------------%
 
     % char_list_remove_suffix/3: We use this instead of the more general
-    % list__remove_suffix so that (for example) string__format will succeed in
+    % list.remove_suffix so that (for example) string.format will succeed in
     % grade Java, even though unification has not yet been implemented.
     %
 :- pred char_list_remove_suffix(list(char)::in, list(char)::in,
     list(char)::out) is semidet.
 
 char_list_remove_suffix(List, Suffix, Prefix) :-
-    list__length(List, ListLength),
-    list__length(Suffix, SuffixLength),
+    list.length(List, ListLength),
+    list.length(Suffix, SuffixLength),
     PrefixLength = ListLength - SuffixLength,
-    list__split_list(PrefixLength, List, Prefix, Rest),
+    list.split_list(PrefixLength, List, Prefix, Rest),
     char_list_equal(Suffix, Rest).
 
 :- pred char_list_equal(list(char)::in, list(char)::in) is semidet.
@@ -4565,7 +4567,7 @@
 
 %------------------------------------------------------------------------------%
 
-string__format_table(Columns, Seperator) = Table :-
+string.format_table(Columns, Seperator) = Table :-
     MaxWidths = list.map(find_max_length, Columns),
     PaddedColumns = list.map_corresponding(pad_column, MaxWidths, Columns),
     (
@@ -4617,9 +4619,9 @@
 
 %-----------------------------------------------------------------------------%
 
-string__word_wrap(Str, N) = string__word_wrap(Str, N, "").
+string.word_wrap(Str, N) = string.word_wrap(Str, N, "").
 
-string__word_wrap(Str, N, WordSep) = Wrapped :-
+string.word_wrap(Str, N, WordSep) = Wrapped :-
     Words = string.words(char.is_whitespace, Str),
     SepLen = string.length(WordSep),
     ( SepLen < N ->
@@ -4693,7 +4695,7 @@
                 RevPieces = [LastPiece | Rest]
             ;
                 RevPieces = [],
-                error("string__word_wrap_2: no pieces")
+                error("string.word_wrap_2: no pieces")
             ),
             RestWithSep = list.map(func(S) = S ++ WordSep ++ "\n", Rest),
             NewCol = 1,
cvs diff: Diffing mdbcomp
Index: mdbcomp/prim_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/prim_data.m,v
retrieving revision 1.8
diff -u -b -r1.8 prim_data.m
--- mdbcomp/prim_data.m	7 Dec 2005 16:07:11 -0000	1.8
+++ mdbcomp/prim_data.m	23 Jan 2006 03:37:03 -0000
@@ -218,6 +218,12 @@
 :- pred aditi_private_builtin_module(sym_name::out) is det.
 :- func aditi_private_builtin_module = sym_name.
 
+    % Returns the sym_name of the module with the given name in the
+    % Mercury standard library.
+    %
+:- pred mercury_std_lib_module_name(string::in, sym_name::out) is det.
+:- func mercury_std_lib_module_name(string) = sym_name.
+
     % Succeeds iff the specified module is one of the builtin modules listed
     % above which may be automatically imported.
     %
@@ -311,6 +317,8 @@
 aditi_public_builtin_module(aditi_public_builtin_module).
 aditi_private_builtin_module = unqualified("aditi_private_builtin").
 aditi_private_builtin_module(aditi_private_builtin_module).
+mercury_std_lib_module_name(Name) = unqualified(Name).
+mercury_std_lib_module_name(Name, unqualified(Name)).
 
 any_mercury_builtin_module(Module) :-
     ( mercury_public_builtin_module(Module)
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
Index: tests/invalid/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/invalid/Mercury.options,v
retrieving revision 1.12
diff -u -b -r1.12 Mercury.options
--- tests/invalid/Mercury.options	28 Sep 2005 09:02:16 -0000	1.12
+++ tests/invalid/Mercury.options	25 Jan 2006 03:54:43 -0000
@@ -67,7 +67,12 @@
 				--no-automatic-intermodule-optimization
 MCFLAGS-pragma_c_code_no_det =	--warn-inferred-erroneous
 MCFLAGS-record_syntax_errors =	--verbose-error-messages
-MCFLAGS-sub_c = 	--verbose-error-messages --no-intermodule-optimization \
+MCFLAGS-string_format_bad =	--halt-at-warn --warn-known-bad-format-call \
+				--warn-unknown-format-call
+MCFLAGS-string_format_unknown =	--halt-at-warn --warn-known-bad-format-call \
+				--warn-unknown-format-call
+MCFLAGS-sub_c = 		--verbose-error-messages \
+				--no-intermodule-optimization \
 				--no-automatic-intermodule-optimization
 
 # Force this test to be compiled in a non-trailing grade since in this
Index: tests/invalid/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/invalid/Mmakefile,v
retrieving revision 1.187
diff -u -b -r1.187 Mmakefile
--- tests/invalid/Mmakefile	25 Jan 2006 02:03:44 -0000	1.187
+++ tests/invalid/Mmakefile	25 Jan 2006 03:41:03 -0000
@@ -37,8 +37,8 @@
 	any_mode \
 	any_passed_as_ground \
 	any_should_not_match_bound \
-	any_to_ground_in_ite_cond \
 	anys_in_negated_contexts \
+	any_to_ground_in_ite_cond \
 	assert_in_interface \
 	bad_finalise_decl \
 	bad_initialise_decl \
@@ -156,6 +156,8 @@
 	state_vars_test3 \
 	state_vars_test4 \
 	state_vars_test5 \
+	string_format_bad \
+	string_format_unknown \
 	tc_err1 \
 	tc_err2 \
 	tricky_assert1 \
Index: tests/invalid/string_format_bad.err_exp
===================================================================
RCS file: tests/invalid/string_format_bad.err_exp
diff -N tests/invalid/string_format_bad.err_exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/string_format_bad.err_exp	25 Jan 2006 01:46:02 -0000
@@ -0,0 +1,16 @@
+string_format_bad.m:020: Mismatched format and values in call to
+string_format_bad.m:020:   `string.format'/3:
+string_format_bad.m:020:   format string invalid.
+string_format_bad.m:022: Mismatched format and values in call to
+string_format_bad.m:022:   `string.format'/3:
+string_format_bad.m:022:   invalid conversion specifier.
+string_format_bad.m:025: Mismatched format and values in call to `io.format'/4:
+string_format_bad.m:025:   invalid conversion specifier.
+string_format_bad.m:026: Mismatched format and values in call to `io.format'/5:
+string_format_bad.m:026:   invalid conversion specifier.
+string_format_bad.m:027: Mismatched format and values in call to `io.format'/4:
+string_format_bad.m:027:   invalid conversion specifier.
+string_format_bad.m:036: Mismatched format and values in call to `io.format'/5:
+string_format_bad.m:036:   invalid conversion specifier.
+string_format_bad.m:041: Mismatched format and values in call to `io.format'/5:
+string_format_bad.m:041:   invalid conversion specifier.
Index: tests/invalid/string_format_bad.m
===================================================================
RCS file: tests/invalid/string_format_bad.m
diff -N tests/invalid/string_format_bad.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/string_format_bad.m	25 Jan 2006 01:43:55 -0000
@@ -0,0 +1,62 @@
+% vim: ts=4 sw=4 expandtab ft=mercury
+
+:- module string_format_bad.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+:- import_module bool.
+:- import_module float.
+:- import_module int.
+:- import_module list.
+:- import_module string.
+
+main(!IO) :-
+    S1 = string.format("", [s("x1")]),
+    io.write_string(S1, !IO),
+    S2 = string.format("%d", [s("x2")]),
+    io.write_string(S2, !IO),
+    io.stdout_stream(OutputStream, !IO),
+    io.format("%d", [s("x3")], !IO),
+    io.format(OutputStream, "%d", [s("x4")], !IO),
+    io.format("%w", [i(5)], !IO),
+    io.write_string(p(s("five")), !IO),
+    F6 = "%s %f",
+    make_bool(6, T6),
+    (
+        T6 = yes,
+        V6A = i(6)
+    ->
+        V6 = [s("six"), V6A],
+        io.format(OutputStream, F6, V6, !IO),
+        make_bool(7, T7),
+        F7 = "%d %s %d",
+        (
+            T7 = yes,
+            io.format(OutputStream, F7, [f(7.0) | V6], !IO)
+        ;
+            T7 = no
+        )
+    ;
+        true
+    ).
+
+:- pred make_bool(int::in, bool::out) is det.
+
+make_bool(_, yes).
+
+:- func t(string) = string.
+
+t(S) = S.
+
+:- func p(string.poly_type) = string.
+
+p(s(S)) = t(string.format("%s", [s(S)])).
+p(c(C)) = t(string.format("%c", [c(C)])).
+p(i(I)) = t(string.format("%d", [i(I)])).
+p(f(F)) = t(string.format("%f", [f(F)])).
Index: tests/invalid/string_format_unknown.err_exp
===================================================================
RCS file: tests/invalid/string_format_unknown.err_exp
diff -N tests/invalid/string_format_unknown.err_exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/string_format_unknown.err_exp	25 Jan 2006 01:46:39 -0000
@@ -0,0 +1,18 @@
+string_format_unknown.m:021: Unknown format string in call to
+string_format_unknown.m:021:   `string.format'/3.
+string_format_unknown.m:023: Mismatched format and values in call to
+string_format_unknown.m:023:   `string.format'/3:
+string_format_unknown.m:023:   invalid conversion specifier.
+string_format_unknown.m:026: Mismatched format and values in call to
+string_format_unknown.m:026:   `io.format'/4:
+string_format_unknown.m:026:   invalid conversion specifier.
+string_format_unknown.m:027: Mismatched format and values in call to
+string_format_unknown.m:027:   `io.format'/5:
+string_format_unknown.m:027:   invalid conversion specifier.
+string_format_unknown.m:028: Mismatched format and values in call to
+string_format_unknown.m:028:   `io.format'/4:
+string_format_unknown.m:028:   invalid conversion specifier.
+string_format_unknown.m:038: Unknown format values in call to `io.format'/5.
+string_format_unknown.m:043: Mismatched format and values in call to
+string_format_unknown.m:043:   `io.format'/5:
+string_format_unknown.m:043:   invalid conversion specifier.
Index: tests/invalid/string_format_unknown.m
===================================================================
RCS file: tests/invalid/string_format_unknown.m
diff -N tests/invalid/string_format_unknown.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/string_format_unknown.m	25 Jan 2006 01:43:58 -0000
@@ -0,0 +1,64 @@
+% vim: ts=4 sw=4 expandtab ft=mercury
+
+:- module string_format_unknown.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+:- implementation.
+
+:- import_module bool.
+:- import_module float.
+:- import_module int.
+:- import_module list.
+:- import_module string.
+
+main(!IO) :-
+    copy("", F1),
+    S1 = string.format(F1, [s("x1")]),
+    io.write_string(S1, !IO),
+    S2 = string.format("%d", [s("x2")]),
+    io.write_string(S2, !IO),
+    io.stdout_stream(OutputStream, !IO),
+    io.format("%d", [s("x3")], !IO),
+    io.format(OutputStream, "%d", [s("x4")], !IO),
+    io.format("%w", [i(5)], !IO),
+    io.write_string(p(s("five")), !IO),
+    F6 = "%s %f",
+    make_bool(6, T6),
+    (
+        T6 = yes,
+        V6A = i(6)
+    ->
+        V6 = [s("six"), V6A],
+        copy(V6, C6),
+        io.format(OutputStream, F6, C6, !IO),
+        make_bool(7, T7),
+        F7 = "%d %s %d",
+        (
+            T7 = yes,
+            io.format(OutputStream, F7, [f(7.0) | V6], !IO)
+        ;
+            T7 = no
+        )
+    ;
+        true
+    ).
+
+:- pred make_bool(int::in, bool::out) is det.
+
+make_bool(_, yes).
+
+:- func t(string) = string.
+
+t(S) = S.
+
+:- func p(string.poly_type) = string.
+
+p(s(S)) = t(string.format("%s", [s(S)])).
+p(c(C)) = t(string.format("%c", [c(C)])).
+p(i(I)) = t(string.format("%d", [i(I)])).
+p(f(F)) = t(string.format("%f", [f(F)])).
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/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:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list