[m-rev.] diff: cleanup some of the mode constraints module

Julien Fischer juliensf at cs.mu.OZ.AU
Fri Feb 25 19:44:42 AEDT 2005


Estimated hours taken: 1
Branches: main

Clean up some of the modules Richard added the other day while
the details of what they do are still in my head.  There
are no changes to any algorithms except the addition of
a synonym for the `--prop-mode-constraints' option.

compiler/abstract_mode_constraints.m:
compiler/build_mode_constraints.m:
compiler/prop_mode_constraints.m:
	Perform a quick cleanup of these modules and bring them
	more into line with our current coding standard.

	Fix up some typos in the documentation of these modules.

	Use 4-space indentation in build_mode_constraints.

	Remove some unnecessary module imports.

compiler/options.m:
	Add `--propagate-mode-constraints' as a synonym for
	`--prop-mode-constraints'.

Julien.

Workspace:/home/swordfish/juliensf/ws-misc
Index: compiler/abstract_mode_constraints.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/abstract_mode_constraints.m,v
retrieving revision 1.1
diff -u -r1.1 abstract_mode_constraints.m
--- compiler/abstract_mode_constraints.m	22 Feb 2005 12:32:09 -0000	1.1
+++ compiler/abstract_mode_constraints.m	25 Feb 2005 07:55:47 -0000
@@ -12,24 +12,31 @@
 % variables, such as those one might use to describe where a program
 % variable may be produced.
 %
-
-
+%-----------------------------------------------------------------------------%

 :- module check_hlds.abstract_mode_constraints.

 :- interface.

-:- type mc_type.
+:- import_module bool.
+:- import_module counter.
+:- import_module io.
+:- import_module list.
+:- import_module map.
+:- import_module std_util.
+:- import_module term.
+:- import_module varset.

-:- import_module term, list, bool, map, counter.
-:- import_module std_util, varset, io.
+%-----------------------------------------------------------------------------%
+
+:- type mc_type.

 :- type mc_var == var(mc_type).		% Constraint variable.
+
 :- type mc_varset == varset(mc_type).	% Source of constraint variables
 					% And their names.
 :- type vars(T) == list(var(T)).

-
 %-----------------------------------------------------------------------------%
 %
 % Data structures for storing abstract constraints. Conjunctions and
@@ -40,7 +47,6 @@
 % Stuckey documents these mode constraints.
 %

-
 	% Represents conjunctions and disjunctions between atomic
 	% constraints on constraint variables.  The advantage of the
 	% constraints for this implementation of mode checking is that
@@ -84,23 +90,16 @@
 			% (all Xi, Xj in Xs).(i = j or not(Xi and Xj))
 	;	at_least_one(vars(T))
 			% at_least_one(Xs) gives OR(Xs)
-	;	exactly_one(vars(T))
+	;	exactly_one(vars(T)).
 			% exactly_one(Xs) gives
 			% at_least_one(Xs) and at_most_one(Xs)
-.
-
-
-

 	% Attempts to print the constraint_formulae it is passed in a
 	% human readable format. Always puts a new line after it is
 	% finished.
 	%
-:- pred pretty_print_constraints(
-	mc_varset::in, constraint_formulae::in, io::di, io::uo
-	) is det.
-
-
+:- pred pretty_print_constraints(mc_varset::in, constraint_formulae::in,
+	io::di, io::uo) is det.

 %-----------------------------------------------------------------------------%
 %
@@ -115,7 +114,7 @@
 % variable has been bound, the propagator looks it up in the var_map
 % field of mode_constraints_info. The var_state structure will then
 % reveal which constraints this variable participates in. These
-% constraints are then looked up inthe constraint_map field of
+% constraints are then looked up in the constraint_map field of
 % mode_constraints_info. Then can be refined due to the variable having
 % been bound, and may now imply new bindings on other variables. These
 % new variables can be put in a stack, queue or similar structure to be
@@ -127,9 +126,6 @@
 % described above is truly intended.
 %

-
-
-
 % XXX	What's lacking in this is the following:
 % Done 	1)	An at least one constraint, for when equiv_disj simplifies
 % 	2)	A good reason to keep the propagate if true/false lists
@@ -143,10 +139,6 @@
 % 		possible models?
 % 	6)	Access and manipulation predicates.

-
-
-
-
 :- type mode_constraints_info --->
 	mode_constraints_info(
 		constraint_map	:: map(constraint_id, constraint),
@@ -157,7 +149,6 @@
 			% Supplies unique IDs for the constraint map.
 	).

-
 :- type constraint_id == int.

 :- type constraint --->
@@ -177,8 +168,6 @@
 		participating_vars	:: vars(mc_type)
 	).

-
-
 :- type var_state --->
 	var_state(
 		is_bound	:: maybe(var_binding),
@@ -208,7 +197,6 @@
 			% is bound, for space considerations.
 	).

-
 :- type constrainment_info --->
 	constrainment_info(
 %		variable		:: mc_var,
@@ -222,40 +210,36 @@
 		constraint		:: constraint_id
 	).

-
-
-
-% Initiates all the parts of a mode_constraints_info type.
+	% Initiates all the parts of a mode_constraints_info type.
+	%
 :- pred abstract_mode_constraints.init(mode_constraints_info::out) is det.

-% Functional version if init/1.
-:- func abstract_mode_constraints.init = (mode_constraints_info::out) is det.
-
-% Incorporates a new constraint into the system.
-:- pred abstract_mode_constraints.add_constraint(
-	constraint_formula::in,
-	mode_constraints_info::in,
-	mode_constraints_info::out
-	) is det.
+	% Function version if init/1.
+:- func abstract_mode_constraints.init = mode_constraints_info.

-% Functional version of add_constraint/3.
-:- func abstract_mode_constraints.add_constraint(
-	constraint_formula::in,
-	mode_constraints_info::in
-	) = (mode_constraints_info::out) is det.
+	% Incorporates a new constraint into the system.
+	%
+:- pred abstract_mode_constraints.add_constraint(constraint_formula::in,
+	mode_constraints_info::in, mode_constraints_info::out) is det.

+	% Function version of add_constraint/3.
+	%
+:- func abstract_mode_constraints.add_constraint(constraint_formula,
+	mode_constraints_info) = mode_constraints_info.

+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%

 :- implementation.

-
 :- import_module string.

-:- type mc_type --->
-	mc_type.
+%-----------------------------------------------------------------------------%

+:- type mc_type ---> mc_type.

-% Initiates all the parts of a mode_constraints_info type.
+	% Initiates all the parts of a mode_constraints_info type.
+	%
 abstract_mode_constraints.init(ModeConstraintsInfo) :-
 	ModeConstraintsInfo = mode_constraints_info(
 		map.init,
@@ -263,50 +247,33 @@
 		counter.init(0)		% Start allocating ids from 0
 	).

-% See the predicate version.
+	% See the predicate version.
+	%
 abstract_mode_constraints.init = ModeConstraintsInfo :-
 	abstract_mode_constraints.init(ModeConstraintsInfo).

-
-% Incorporates a new constraint into the system.
-abstract_mode_constraints.add_constraint(
-	ConstraintFormula,
-	!ModeConstraintsInfo
-	) :-
-	formula_to_formula_and_vars(
-		ConstraintFormula,
-		Vars,
-		FormulaAndVars
-	),
-	counter.allocate(
-		NewID,
-		!.ModeConstraintsInfo ^ id_counter,
-		NewCounter
-	),
+	% Incorporates a new constraint into the system.
+	%
+abstract_mode_constraints.add_constraint(ConstraintFormula,
+		!ModeConstraintsInfo) :-
+	formula_to_formula_and_vars(ConstraintFormula,
+		Vars, FormulaAndVars),
+	counter.allocate(NewID, !.ModeConstraintsInfo ^ id_counter,
+		NewCounter),
 	!:ModeConstraintsInfo =
 		!.ModeConstraintsInfo ^ id_counter := NewCounter,
-	update_vars_map_with_constrainment_info(
-		constrainment_info(NewID),
-		Vars,
-		!ModeConstraintsInfo
-		),
-	!:ModeConstraintsInfo =
-		!.ModeConstraintsInfo ^ constraint_map :=
-		map.det_insert(
-			!.ModeConstraintsInfo ^ constraint_map,
-			NewID,
-			constraint(NewID, FormulaAndVars, FormulaAndVars)
-		).
+	update_vars_map_with_constrainment_info(constrainment_info(NewID),
+		Vars, !ModeConstraintsInfo),
+	!:ModeConstraintsInfo = !.ModeConstraintsInfo ^ constraint_map :=
+		map.det_insert(!.ModeConstraintsInfo ^ constraint_map,
+			NewID,
+			constraint(NewID, FormulaAndVars, FormulaAndVars)).

-
-
-% Functional version of add_constraint/3.
+	% Functional version of add_constraint/3.
+	%
 abstract_mode_constraints.add_constraint(CF, MCI0) = MCI :-
 	abstract_mode_constraints.add_constraint(CF, MCI0, MCI).

-
-
-
 % update_vars_map_with_constrainment_info adds the supplied
 % constrainment_info to the list of constraints associated with each of
 % the variables supplied in the mode_constraints_info structure.
@@ -329,10 +296,6 @@
 	),
 	update_vars_map_with_constrainment_info(ConstrainmentInfo, Vars, !MCI).

-
-
-
-
 % formula_to_formula_and_vars makes the list Vars of variables that
 % appear in Formula and packages Formula and Vars together in
 % FormulaAndVars.
@@ -346,7 +309,6 @@
 	formula_to_vars(Formula, Vars),
 	FormulaAndVars = constraint_formula_and_vars(Formula, Vars).

-
 % Sub section of the formula_to_formula_and_vars predicate, Vars is the
 % variables that appear in Formula
 :- pred formula_to_vars(constraint_formula::in, vars(mc_type)::out) is det.
@@ -377,7 +339,6 @@
 		Vars
 	).

-
 % var_constraint_to_vars takes a constraint between variables as input
 % and gives a list of those variables as output.
 :- pred var_constraint_to_vars(var_constraint::in, vars(mc_type)::out) is det.
@@ -390,9 +351,6 @@
 var_constraint_to_vars(at_least_one(Vars), Vars).
 var_constraint_to_vars(exactly_one(Vars), Vars).

-
-
-
 % Some thoughts:
 % add_constraint or similar pred adds the specified constraint (making
 % sure that the variables in it are added if need be, and updated with a
@@ -405,16 +363,11 @@
 % and only modifies the 'current' branch - eg replacing one var with an
 % equivalent etc.

-
-
-
 %-----------------------------------------------------------------------------%
 %
 % Pretty printing predicates for the formulae type, and others
 %

-
-
 pretty_print_constraints(Varset, Constraints, !IO) :-
 	pretty_print_constraints(
 		Varset,
@@ -426,30 +379,19 @@
 	% Same as before, but with an indent argument used to indent
 	% conjunctions and disjunctions of constraints.
 	%
-:- pred pretty_print_constraints(
-	mc_varset::in,
-	constraint_formulae::in,
-	string::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_constraints(mc_varset::in, constraint_formulae::in,
+	string::in, io::di, io::uo) is det.

 pretty_print_constraints(_Varset, [], _Indent, !IO).
 pretty_print_constraints(Varset, [Constr|Constrs], Indent, !IO) :-
 	pretty_print_constraint(Varset, Constr, Indent, !IO),
 	pretty_print_constraints(Varset, Constrs, Indent, !IO).

-
 	% Prints one constraint_formulae to the output stream. Always
 	% puts a new line at the end.
 	%
-:- pred pretty_print_constraint(
-	mc_varset::in,
-	constraint_formula::in,
-	string::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_constraint(mc_varset::in, constraint_formula::in,
+	string::in, io::di, io::uo) is det.

 pretty_print_constraint(Varset, disj(Constraints), Indent, !IO) :-
 	io.print(Indent, !IO),
@@ -478,12 +420,8 @@
 	% Prints a var_constraint to the screen. No indents, no line
 	% return.
 	%
-:- pred pretty_print_var_constraint(
-	mc_varset::in,
-	var_constraint::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_var_constraint(mc_varset::in, var_constraint::in,
+	io::di, io::uo) is det.

 pretty_print_var_constraint(Varset, equiv_bool(X, TF), !IO) :-
 	pretty_print_mc_var(Varset, X, !IO),
@@ -521,31 +459,20 @@
 	pretty_print_mc_vars(Varset, Xs, !IO),
 	io.print(")", !IO).

-
 	% Prints a constraint var to the screen. No indents, no line
 	% return.  Simply uses the variable's name from the varset.
 	%
-:- pred pretty_print_mc_var(
-	mc_varset::in,
-	mc_var::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_mc_var(mc_varset::in, mc_var::in,
+	io::di, io::uo) is det.

 pretty_print_mc_var(Varset, Var, !IO) :-
 	varset.lookup_name(Varset, Var, VarName),
 	io.print(VarName, !IO).

-
-
 	% Prints a comma separated list of constraint variables.
 	%
-:- pred pretty_print_mc_vars(
-	mc_varset::in,
-	list(mc_var)::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_mc_vars(mc_varset::in, list(mc_var)::in,
+	io::di, io::uo) is det.

 pretty_print_mc_vars(_Varset, [], !IO).
 pretty_print_mc_vars(Varset, [Var| Tail], !IO) :-
@@ -557,19 +484,14 @@
 	% prints a divider then prints the rest of the list.  If there
 	% is no more list it does nothing.
 	%
-:- pred pretty_print_mc_vars_tail(
-	mc_varset::in,
-	list(mc_var)::in,
-	io::di,
-	io::uo
-	) is det.
+:- pred pretty_print_mc_vars_tail(mc_varset::in, list(mc_var)::in,
+	io::di, io::uo) is det.

 pretty_print_mc_vars_tail(_Varset, [], !IO).
 pretty_print_mc_vars_tail(Varset, [Var| Vars], !IO) :-
 	io.print(", ", !IO),
 	pretty_print_mc_vars(Varset, [Var| Vars], !IO).

-
-
-
-
+%-----------------------------------------------------------------------------%
+:- end_module abstract_mode_constraints.
+%-----------------------------------------------------------------------------%
Index: compiler/build_mode_constraints.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/build_mode_constraints.m,v
retrieving revision 1.1
diff -u -r1.1 build_mode_constraints.m
--- compiler/build_mode_constraints.m	22 Feb 2005 12:32:09 -0000	1.1
+++ compiler/build_mode_constraints.m	25 Feb 2005 07:55:15 -0000
@@ -1,4 +1,6 @@
 %-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
 % Copyright (C) 2004-2005 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
@@ -8,20 +10,15 @@
 % Main author: richardf
 %
 % This module contains predicates and data structures needed for
-% traversing hlds and building a list of abstract constraint formulae to
-% describe variable producers in a mercury program.
+% traversing the HLDS and building a list of abstract constraint formulae to
+% describe variable producers in a Mercury program.
 %
-
-
-% XXX Change tabs to 4-spaces would make things neater.
-
+%-----------------------------------------------------------------------------%

 :- module check_hlds.build_mode_constraints.

 :- interface.

-
-
 :- import_module check_hlds.abstract_mode_constraints.

 :- import_module hlds.hlds_goal.
@@ -31,8 +28,11 @@
 % 	% Needed if converting for partial instantiation.
 :- import_module parse_tree__prog_data.

-:- import_module bimap, list, set.
+:- import_module bimap.
+:- import_module list.
+:- import_module set.

+%-----------------------------------------------------------------------------%

 	% XXX Change to include more information?  This will just be a
 	% list of constraints representing the conjunction of them. When
@@ -42,9 +42,9 @@
 	%
 	% This represents the conjunction of the constraints it
 	% contains.
+	%
 :- type mode_constraints == constraint_formulae.

-
 	% A map between the constraint variables (mc_var) and what they
 	% represent ie that some program variable is produced at some
 	% goal path (for a particular predicate).
@@ -55,12 +55,10 @@
 	%
 :- type mc_var_map == bimap(mc_rep_var, mc_var).

-
 	% Just a conveniently descriptive name.
 	%
 :- type args == list(prog_var).

-
 	% Just a conveniently descriptive name.
 	%
 :- type nonlocals == set(prog_var).
@@ -70,9 +68,7 @@
 	% specify the predicate to which this prog_var is intended to
 	% apply.
 	%
-:- type mc_prog_var --->
-	prog_var `in` pred_id.
-
+:- type mc_prog_var ---> prog_var `in` pred_id.

 	% An abstract representation of a mode constraint variable.
 	%
@@ -80,9 +76,7 @@
 	% the program variable specified is produced at the goal path
 	% specified.
 	%
-:- type mc_rep_var --->
-	mc_prog_var `at` goal_path.
-
+:- type mc_rep_var ---> mc_prog_var `at` goal_path.

 	% Provides a nice way to display constraint variables - just
 	% convert to the relevant mc_rep_var using the mc_var_map and
@@ -91,21 +85,16 @@
 	%
 :- func rep_var_to_string(prog_varset, mc_rep_var) = (string).

-
 	% For each head variable of each predicate in the supplied SCC,
 	% this predicate adds to the varset the constraint variable for
-	% HeadVariable `in` PredID `at` []. In other words, it creates
+	% HeadVariable `in` PredId `at` []. In other words, it creates
 	% the constraint variables that describe whether or not a head
 	% variable is produced by a call to the predicate. At the same
 	% time it records in the mc_var_map the position and program
 	% variable to which the new constraint variable corresponds.
 	%
-:- pred add_mc_vars_for_scc_heads(
-	module_info::in, list(pred_id)::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out
-	) is det.
-
+:- pred add_mc_vars_for_scc_heads(module_info::in, list(pred_id)::in,
+	mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out) is det.

 	% Makes sure that the necessary constraint variables exist to
 	% create goal constraints for all goal types except predicate
@@ -124,21 +113,13 @@
 	% any predicate in an SCC add_mc_vars_for_scc_heads should be
 	% called for that whole SCC.
 	%
-:- pred add_mc_vars_for_goal(
-	pred_id::in,
-	prog_varset::in,
-	hlds_goal::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out
-	) is det.
-
+:- pred add_mc_vars_for_goal(pred_id::in, prog_varset::in, hlds_goal::in,
+    mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out) is det.

-
-
-	% mode_decls_constraints(ModuleInfo, VarMap, PredID, Decls,
+	% mode_decls_constraints(ModuleInfo, VarMap, PredId, Decls,
 	% HeadVarsList, Constraints)
 	%
-	% Constraints is the disjuction of the constraints for
+	% Constraints is the disjunction of the constraints for
 	% individual declared modes being satisfied.  ie
 	% disj([ConstraintsForMode1, ..., ConstraintsForModen])
 	%
@@ -158,77 +139,80 @@
 	% and is not produced.
 	%
 :- pred mode_decls_constraints(module_info::in, mc_var_map::in,
-	pred_id::in, list(list(mode))::in,
-	list(args)::in, mode_constraints::out) is det.
-
+	pred_id::in, list(list(mode))::in, list(args)::in, mode_constraints::out)
+    is det.

 	% In the event that type_info arguments have been added to a
 	% predicate call's arguments/headvars, but the modes have not
 	% been edited to reflect this, extra in modes need to be added
 	% to the front of the mode declaration to account for this.
+	%
 	% XXX This predicate shouldn't be needed, but if you're getting
 	% map_corresponding errors for the use of lists of different
-	% lenths it would be worthwhile modifying any calls to
+	% lengths it would be worthwhile modifying any calls to
 	% mode_decl predicates with this so that the headvars list and
 	% mode declarations are the same length.
 	% Unfortunately this predicate relies the type_info arguments
 	% being added to the front of the arg list, and assumes that
 	% they are all specifically of mode in as given by function
 	% prog_tree.prog_mode.in_mode
-:- pred add_sufficient_in_modes_for_type_info_args(
-	args::in, list(mode)::in, list(mode)::out
-	) is det.
-
+:- pred add_sufficient_in_modes_for_type_info_args(args::in,
+    list(mode)::in, list(mode)::out) is det.

 	% goal_expr_constraints generates the constraints that apply to
 	% a given goal_expr at a given goal path.
 	%
-:- pred goal_expr_constraints(
-	module_info::in,
-	mc_var_map::in,
-	pred_id::in,
-	hlds_goal_expr::in,
-	goal_path::in,
-	nonlocals::in,
-	mode_constraints::out
-	) is det.
+:- pred goal_expr_constraints( module_info::in, mc_var_map::in,
+	pred_id::in, hlds_goal_expr::in, goal_path::in, nonlocals::in,
+    mode_constraints::out) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%

 :- implementation.

 :- import_module check_hlds.goal_path.
 :- import_module check_hlds.mode_util.
 :- import_module check_hlds.inst_match.
-:- import_module hlds__hlds_data.
-:- import_module hlds__passes_aux.
-:- import_module parse_tree__prog_mode.
-:- import_module transform_hlds__dependency_graph.

+:- import_module hlds.hlds_data.
+:- import_module hlds.passes_aux.
+
+:- import_module parse_tree.error_util.
+:- import_module parse_tree.prog_mode.

-:- import_module bool, gc, int, map, multi_map, require, sparse_bitset.
-:- import_module std_util, string, term, term_io, varset.
+:- import_module transform_hlds.dependency_graph.

+:- import_module bool.
+:- import_module int.
+:- import_module map.
+:- import_module multi_map.
+:- import_module sparse_bitset.
+:- import_module std_util.
+:- import_module string.
+:- import_module svbimap.
+:- import_module svmulti_map.
+:- import_module svvarset.
+:- import_module term.
+:- import_module varset.
+
+%-----------------------------------------------------------------------------%

 add_mc_vars_for_scc_heads(_ModuleInfo, [], !Varset, !VarMap).
-add_mc_vars_for_scc_heads(ModuleInfo, [PredID| PredIDs], !Varset, !VarMap) :-
-	module_info_pred_info(ModuleInfo, PredID, PredInfo),
+add_mc_vars_for_scc_heads(ModuleInfo, [PredId | PredIds], !Varset, !VarMap) :-
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
 	pred_info_clauses_info(PredInfo, ClausesInfo),
 	clauses_info_headvars(ClausesInfo, Headvars),
 	clauses_info_varset(ClausesInfo, ProgVarset),
-	list.foldl2(
-		add_mc_var_for_pred_head(PredID, ProgVarset),
-		Headvars,
-		!Varset,
-		!VarMap
-	),
-	add_mc_vars_for_scc_heads(ModuleInfo, PredIDs, !Varset, !VarMap).
+	list.foldl2(add_mc_var_for_pred_head(PredId, ProgVarset), Headvars,
+		!Varset, !VarMap),
+	add_mc_vars_for_scc_heads(ModuleInfo, PredIds, !Varset, !VarMap).
 		% XXX This potentially needs to be performed for the
 		% headvars in the proc_infos associated with a predicate
 		% as well, since the mode declaration constraints refer
 		% to them, however at this point in time they should be
 		% the same as the headvars in the clauses_info

-
-
 	% Makes sure a constraint variable exists to say that the
 	% supplied program variable is produced by the predicate in
 	% which it exists.
@@ -237,36 +221,27 @@
 	% already exist, and then gets a new one from the varset and
 	% adds it to the varmap if it doesn't.
 	%
-:- pred add_mc_var_for_pred_head(
-	pred_id::in,
-	prog_varset::in, prog_var::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out
-	) is det.
-
-add_mc_var_for_pred_head(PredID, ProgVarset, HeadVar, !Varset, !VarMap) :-
-	RepVar = (HeadVar `in` PredID) `at` [],
-	(	bimap.search(!.VarMap, RepVar, _MCVar)
-	->	true
-	;	varset.new_named_var(
-			!.Varset,
-			rep_var_to_string(ProgVarset, RepVar),
-			NewMCvar,
-			!:Varset
-		),
-		bimap.det_insert(!.VarMap, RepVar, NewMCvar, !:VarMap)
-	).
-
+:- pred add_mc_var_for_pred_head(pred_id::in, prog_varset::in, prog_var::in,
+	mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out) is det.

+add_mc_var_for_pred_head(PredId, ProgVarset, HeadVar, !Varset, !VarMap) :-
+	RepVar = (HeadVar `in` PredId) `at` [],
+	( bimap.search(!.VarMap, RepVar, _MCVar) ->
+    	true
+	;
+        svvarset.new_named_var(rep_var_to_string(ProgVarset, RepVar),
+			NewMCvar, !Varset),
+		svbimap.det_insert(RepVar, NewMCvar, !VarMap)
+	).

 add_mc_vars_for_goal(
-	PredID, ProgVarset, GoalExpr - GoalInfo, !Varset, !VarMap) :-
+	PredId, ProgVarset, GoalExpr - GoalInfo, !Varset, !VarMap) :-
 	goal_info_get_nonlocals(GoalInfo, Nonlocals),
 	goal_info_get_goal_path(GoalInfo, GoalPath),

 	{!:Varset, !:VarMap} = set.fold(
 		(func(Nonlocal, {Vset0, Vmap0}) = {Vset, Vmap} :-
-			RepVar = (Nonlocal `in` PredID) `at` GoalPath,
+			RepVar = (Nonlocal `in` PredId) `at` GoalPath,
 			(	bimap.search(Vmap0, RepVar, _)
 			->	Vset = Vset0,
 				Vmap = Vmap0
@@ -285,7 +260,7 @@
 		% Switch on GoalExpr for recursion
 	(	GoalExpr = conj(Goals),
 		list.foldl2(
-			add_mc_vars_for_goal(PredID, ProgVarset),
+			add_mc_vars_for_goal(PredId, ProgVarset),
 			Goals,
 			!Varset,
 			!VarMap
@@ -294,32 +269,28 @@
 	;	GoalExpr = generic_call(_, _, _, _)
 	;	GoalExpr = switch(_, _, Cases),
 		Goals = list.map(func(case(_, Goal)) = Goal, Cases),
-		list.foldl2(
-			add_mc_vars_for_goal(PredID, ProgVarset),
-			Goals,
-			!Varset,
-			!VarMap
-		)
+		list.foldl2(add_mc_vars_for_goal(PredId, ProgVarset), Goals,
+			!Varset, !VarMap)
 	;	GoalExpr = unify(_, _, _, _, _)
 	;	GoalExpr = disj(Goals),
 		list.foldl2(
-			add_mc_vars_for_goal(PredID, ProgVarset),
+			add_mc_vars_for_goal(PredId, ProgVarset),
 			Goals,
 			!Varset,
 			!VarMap
 		)
 	;	GoalExpr = not(Goal),
 		add_mc_vars_for_goal(
-			PredID, ProgVarset, Goal, !Varset, !VarMap
+			PredId, ProgVarset, Goal, !Varset, !VarMap
 		)
 	;	GoalExpr = some(_, _, Goal),
 		add_mc_vars_for_goal(
-			PredID, ProgVarset, Goal, !Varset, !VarMap
+			PredId, ProgVarset, Goal, !Varset, !VarMap
 		)
 	;	GoalExpr = if_then_else(_, Cond, Then, Else),
 		Goals = [Cond, Then, Else],
 		list.foldl2(
-			add_mc_vars_for_goal(PredID, ProgVarset),
+			add_mc_vars_for_goal(PredId, ProgVarset),
 			Goals,
 			!Varset,
 			!VarMap
@@ -329,68 +300,50 @@
 	;	GoalExpr = shorthand(_ShorthandGoalExpr)
 	).

-
-
 rep_var_to_string(ProgVarset, (ProgVar `in` _) `at` GoalPath) = RepString :-
 	goal_path_to_string(GoalPath, GoalPathString),
 	varset.lookup_name(ProgVarset, ProgVar, ProgVarString),
-	(	GoalPathString = ""
-	->	RepString = ProgVarString
-	;	RepString = ProgVarString ++ "." ++ GoalPathString
+	( GoalPathString = "" ->
+        RepString = ProgVarString
+	;
+        RepString = ProgVarString ++ "." ++ GoalPathString
 	).
-
-
-%-----------------------------------------------------------------------------

+%-----------------------------------------------------------------------------%

 	% goal_constraints gives the mode constraints for the supplied
 	% hlds_goal
 	%
-:- pred goal_constraints(
-	module_info::in,
-	mc_var_map::in,
-	pred_id::in,
-	hlds_goal::in,
-	mode_constraints::out
-	) is det.
+:- pred goal_constraints(module_info::in, mc_var_map::in, pred_id::in,
+	hlds_goal::in, mode_constraints::out) is det.

-goal_constraints(
-	ModuleInfo, VarMap, PredID, GoalExpr - GoalInfo, Constraints) :-
+goal_constraints(ModuleInfo, VarMap, PredId, GoalExpr - GoalInfo,
+        Constraints) :-
 	goal_info_get_nonlocals(GoalInfo, Nonlocals),
 	goal_info_get_goal_path(GoalInfo, GoalPath),
-	goal_expr_constraints(
-		ModuleInfo,
-		VarMap,
-		PredID,
-		GoalExpr,
-		GoalPath,
-		Nonlocals,
-		Constraints
-	).
-
-
-
+	goal_expr_constraints(ModuleInfo, VarMap, PredId, GoalExpr, GoalPath,
+        Nonlocals, Constraints).

 	% Goal:
 	% G1, ..., Gn where Goals = [G1, ..., Gn]
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	conj(Goals), GoalPath, Nonlocals, Constraints) :-

 	list.map(
-		goal_constraints(ModuleInfo, VarMap, PredID),
+		goal_constraints(ModuleInfo, VarMap, PredId),
 		Goals, ConjunctConstraints
 	),
 	Constraints0 = list.condense(ConjunctConstraints),
-	foldl(
+	list.foldl(
 		fold_local_var_into_conj_constraints(VarMap, LocalsPositions),
 		multi_map.keys(LocalsPositions),
 		Constraints0, Constraints1
 	),
-	foldl(
+	list.foldl(
 		fold_nonlocal_var_into_conj_constraints(
 			VarMap,
-			PredID,
+			PredId,
 			NonlocalsPositions,
 			GoalPath
 		),
@@ -401,10 +354,11 @@

 	EmptyMultiMap = multi_map.init,
 	list.foldl2(
-		fold_goal_into_var_position_maps(VarMap, PredID, Nonlocals),
+		fold_goal_into_var_position_maps(VarMap, PredId, Nonlocals),
 		Goals,
 		EmptyMultiMap,
-		LocalsPositions,	% A map from each local variable to
+		LocalsPositions,
+                    % A map from each local variable to
 					% its corresponding constraint
 					% variables for the paths at each of
 					% the conjuncts it is non-local to,
@@ -412,7 +366,8 @@
 					% variable is local to one conjunct we
 					% need not deal with it here).
 		EmptyMultiMap,
-		NonlocalsPositions	% A map from each non-local variable
+		NonlocalsPositions
+                    % A map from each non-local variable
 					% to its corresponding constraint
 					% variables at the paths of each of the
 					% conjuncts it is non-local to. Note
@@ -423,12 +378,10 @@
 					% non-local set of at least one of the
 					% conjuncts.
 	).
-
-

 	% Pred Call
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	call(CalledPred, _ProcID, Args, _Builtin, _UnifyContext, _Name),
 	GoalPath, _Nonlocals, Constraints) :-

@@ -456,7 +409,7 @@

 		call_headvar_constraints(
 			VarMap, GoalPath,
-			PredID, Args, CalledPred, HeadVars,
+			PredId, Args, CalledPred, HeadVars,
 			Constraints
 		)
 	;	ArgModeDecls = [_| _],
@@ -474,7 +427,7 @@
 		call_mode_decls_constraints(
 			ModuleInfo,
 			VarMap,
-			PredID,
+			PredId,
 			ArgModeDecls,
 			GoalPath,
 			Args,
@@ -484,48 +437,48 @@

 	% XXX Need to do something here.
 	%
-goal_expr_constraints(_ModuleInfo, _VarMap, _PredID,
+goal_expr_constraints(_ModuleInfo, _VarMap, _PredId,
 	generic_call(_, _, _, _), _GoalPath, _Nonlocals, _Constraints) :-
-	error("build_mode_constraints.m: "
-		++ "sorry, generic_call not implemented.").
-
+	sorry(this_file, "generic_call NYI.").

 	% XXX Need to do something here.
 	%
-goal_expr_constraints(_ModuleInfo, _VarMap, _PredID,
+goal_expr_constraints(_ModuleInfo, _VarMap, _PredId,
 	switch(_, _, _), _GoalPath, _Nonlocals, _Constraints) :-
-	error("build_mode_constraints.m: "
-		++ "sorry, switch not implemented.").
+	sorry(this_file, "switch NYI.").

 	% Unification Goals
 	%
-goal_expr_constraints(_ModuleInfo, VarMap, PredID,
+goal_expr_constraints(_ModuleInfo, VarMap, PredId,
 	unify(LHSvar, RHS, _Mode, _Kind, _Context),
 	GoalPath, _Nonlocals, Constraints) :-
-	(	RHS = var(RHSvar),
+	(
+        RHS = var(RHSvar),
 			% Goal: LHSvar = RHSvar
 		Constraints = [
 			atomic_constraint(at_most_one([
 				prog_var_at_path(
-					VarMap, PredID, GoalPath, LHSvar
+					VarMap, PredId, GoalPath, LHSvar
 				),
 				prog_var_at_path(
-					VarMap, PredID, GoalPath, RHSvar
+					VarMap, PredId, GoalPath, RHSvar
 				)
 			]))	% At most one of the left and right hand
 				% sides of a unification is produced
 				% at the unification.
 		]
-	;	RHS = functor(_Functor, _IsExistConstr, Args),
+	;
+        RHS = functor(_Functor, _IsExistConstr, Args),
 		LHSproducedHere = prog_var_at_path(
-			VarMap, PredID, GoalPath, LHSvar
+			VarMap, PredId, GoalPath, LHSvar
 		),
 		ArgsProducedHere =
 			list.map(
-				prog_var_at_path(VarMap, PredID, GoalPath),
+				prog_var_at_path(VarMap, PredId, GoalPath),
 				Args
 			),
-		(	ArgsProducedHere = [OneArgProducedHere, _Two| _],
+		(
+            ArgsProducedHere = [OneArgProducedHere, _Two| _],
 				% Goal: LHSvar = functor(Args)
 			Constraints = [
 				atomic_constraint(
@@ -538,7 +491,8 @@
 				]))		% At most one side of the
 						% unification is produced.
 			]
-		;	ArgsProducedHere = [OneArgProducedHere],
+		;
+            ArgsProducedHere = [OneArgProducedHere],
 				% Goal: LHSvar = functor(Arg)
 			Constraints = [
 				atomic_constraint(at_most_one([
@@ -547,29 +501,27 @@
 				]))		% At most one side of the
 						% unification is produced.
 			]
-		;	ArgsProducedHere = [],
+		;
+            ArgsProducedHere = [],
 				% Goal: LHSvar = functor
 				% In this case, LHSvar need not be produced
 				% - it could be a test, so no constraints.
 			Constraints = []
 		)

-	;	RHS = lambda_goal(_, _, _, _, _, _, _, _, _),
-		error("build_mode_constraints.m: "
-			++ "sorry, unify with lambda_goal not implemented.")
+	;
+        RHS = lambda_goal(_, _, _, _, _, _, _, _, _),
+		sorry(this_file, "unify with lambda goal NYI")
 	).

-
-
-
 	% Goal:
 	% G1; ...; Gn where Goals = [G1, ..., Gn]
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	disj(Goals), GoalPath, Nonlocals, Constraints) :-

 	nonlocals_at_path_and_subpaths(
-		VarMap, PredID, GoalPath, DisjunctGoalPaths,
+		VarMap, PredId, GoalPath, DisjunctGoalPaths,
 		Nonlocals, NonlocalsHere, NonlocalsAtDisjuncts
 	),
 	list.map(
@@ -580,7 +532,7 @@
 	),

 	list.map(
-		goal_constraints(ModuleInfo, VarMap, PredID),
+		goal_constraints(ModuleInfo, VarMap, PredId),
 		Goals,
 		DisjunctConstraints
 	),
@@ -599,20 +551,18 @@
 		DisjunctConstraints
 	]).

-
-
 	% Goal:
 	% not (Goal)
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	not(Goal), GoalPath, Nonlocals, Constraints) :-
 	Goal = _ - NegatedGoalInfo,
 	goal_info_get_goal_path(NegatedGoalInfo, NegatedGoalPath),
 	NonlocalsConstraintVars = set.fold(
 		func(Nonlocal, MCVars) = [
-			prog_var_at_path(VarMap, PredID, GoalPath, Nonlocal),
+			prog_var_at_path(VarMap, PredId, GoalPath, Nonlocal),
 			prog_var_at_path(
-				VarMap, PredID, NegatedGoalPath, Nonlocal
+				VarMap, PredId, NegatedGoalPath, Nonlocal
 			)|
 			MCVars
 		],
@@ -620,7 +570,7 @@
 		[]
 	),
 	goal_constraints(
-		ModuleInfo, VarMap, PredID, Goal, NegatedGoalConstraints
+		ModuleInfo, VarMap, PredId, Goal, NegatedGoalConstraints
 	),
 	Constraints = list.foldl(
 		func(MCVar, Cnstrnts) = [
@@ -633,12 +583,11 @@
 		NonlocalsConstraintVars,
 		NegatedGoalConstraints
 	).
-

 	% Goal:
 	% some Xs Goal
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	some(_ExistVars, _CanRemove, Goal),
 	GoalPath, Nonlocals, Constraints) :-
 	Goal = _ - SomeGoalInfo,
@@ -646,9 +595,9 @@
 	Constraints = set.fold(
 		func(NL, NLConstraints) = [
 			atomic_constraint(equivalent([
-				prog_var_at_path(VarMap, PredID, GoalPath, NL),
+				prog_var_at_path(VarMap, PredId, GoalPath, NL),
 				prog_var_at_path(
-					VarMap, PredID, SomeGoalPath, NL
+					VarMap, PredId, SomeGoalPath, NL
 				)
 			]))|		% If a program variable is produced
 					% by the sub-goal of the some
@@ -661,15 +610,13 @@
 					% recursive call on the sub-goal.
 	),
 	goal_constraints(
-		ModuleInfo, VarMap, PredID, Goal, SomeGoalConstraints
+		ModuleInfo, VarMap, PredId, Goal, SomeGoalConstraints
 	).
-
-

 	% Goal:
 	% If -> Then; Else
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	if_then_else(ExistVars, If, Then, Else),
 	GoalPath, Nonlocals, Constraints) :-
 	If = _ - IfInfo, Then = _ - ThenInfo, Else = _ - ElseInfo,
@@ -678,40 +625,39 @@
 	goal_info_get_goal_path(ElseInfo, ElsePath),

 	NonlocalsHere = list.map(
-		prog_var_at_path(VarMap, PredID, GoalPath),
+		prog_var_at_path(VarMap, PredId, GoalPath),
 		NonlocalsList
 	),
 	NonlocalsAtCond = list.map(
-		prog_var_at_path(VarMap, PredID, CondPath),
+		prog_var_at_path(VarMap, PredId, CondPath),
 		NonlocalsList
 	),
 	NonlocalsAtThen = list.map(
-		prog_var_at_path(VarMap, PredID, ThenPath),
+		prog_var_at_path(VarMap, PredId, ThenPath),
 		NonlocalsList
 	),
 	NonlocalsAtElse = list.map(
-		prog_var_at_path(VarMap, PredID, ElsePath),
+		prog_var_at_path(VarMap, PredId, ElsePath),
 		NonlocalsList
 	),
 	NonlocalsList = set.to_sorted_list(Nonlocals),

-
 		% The existentially quantified variables shared between
 		% the condition and the then-part have special
 		% constraints
 		%
 	LocalAndSharedAtCond = list.map(
-		prog_var_at_path(VarMap, PredID, CondPath),
+		prog_var_at_path(VarMap, PredId, CondPath),
 		ExistVars
 	),
 	LocalAndSharedAtThen = list.map(
-		prog_var_at_path(VarMap, PredID, ThenPath),
+		prog_var_at_path(VarMap, PredId, ThenPath),
 		ExistVars
 	),

-	goal_constraints(ModuleInfo, VarMap, PredID, If, IfConstraints),
-	goal_constraints(ModuleInfo, VarMap, PredID, Then, ThenConstraints),
-	goal_constraints(ModuleInfo, VarMap, PredID, Else, ElseConstraints),
+	goal_constraints(ModuleInfo, VarMap, PredId, If, IfConstraints),
+	goal_constraints(ModuleInfo, VarMap, PredId, Then, ThenConstraints),
+	goal_constraints(ModuleInfo, VarMap, PredId, Else, ElseConstraints),

 	Constraints = list.condense([
 		list.map_corresponding3(
@@ -742,7 +688,7 @@
 			% variable shared between the condition and
 			% then-part should always be bound in the
 			% condition, but I'm not sure about the
-			% posibility of checking the variable's type in
+			% possibility of checking the variable's type in
 			% the Cond and then binding it in the Then...
 		IfConstraints,
 		ThenConstraints,
@@ -752,13 +698,13 @@

 	% Foreign procedure
 	%
-goal_expr_constraints(ModuleInfo, VarMap, PredID,
+goal_expr_constraints(ModuleInfo, VarMap, PredId,
 	foreign_proc(_, CalledPred, ProcID, ForeignArgs, _, _),
 	GoalPath, _Nonlocals, Constraints) :-
 	CallArgs = list.map(foreign_arg_var, ForeignArgs),
 	module_info_pred_proc_info(ModuleInfo, CalledPred, ProcID, _, ProcInfo),
-	(	proc_info_maybe_declared_argmodes(ProcInfo, yes(_OrigDecl))
-	->	proc_info_argmodes(ProcInfo, Decl),
+	( proc_info_maybe_declared_argmodes(ProcInfo, yes(_OrigDecl)) ->
+        proc_info_argmodes(ProcInfo, Decl),
 /*
 		add_sufficient_in_modes_for_type_info_args(
 			CallArgs,
@@ -771,65 +717,59 @@
 		call_mode_decls_constraints(
 			ModuleInfo,
 			VarMap,
-			PredID,
+			PredId,
 			[Decl],
 			GoalPath,
 			CallArgs,
 			Constraints
 		)	% This pred should strip the disj(conj()) for the
 			% single declaration.
-	;	Constraints = [],
-		error("build_mode_constraints.m: "
-			++ "no mode declaration for foreign proc")
+	;
+		unexpected(this_file, "no mode declaration for foreign proc")
 	).

-
 	% Parallel conjunction
 	%
 	% XXX What to do here?
 	%
-goal_expr_constraints(_ModuleInfo, _VarMap, _PredID,
-	par_conj(_Goals), _GoalPath, _Nonlocals, _Constraints) :-
-	error("build_mode_constraints.m: "
-		++ "sorry, par_conj not implemented").
-
+goal_expr_constraints(_ModuleInfo, _VarMap, _PredId,
+	    par_conj(_Goals), _GoalPath, _Nonlocals, _Constraints) :-
+    sorry(this_file, "NYI par_conj").

 	% Shorthand goals. Should not exist at this point in compilation.
 	%
-goal_expr_constraints(_ModuleInfo, _VarMap, _PredID,
-	shorthand(_ShorthandGoalExpr), _GoalPath, _Nonlocals, _Constraints) :-
-	error("build_mode_constraints.m: shorthand goal").
-
-
+goal_expr_constraints(_ModuleInfo, _VarMap, _PredId,
+	    shorthand(_ShorthandGoalExpr), _GoalPath, _Nonlocals, _Constraints) :-
+	unexpected(this_file, "shorthand goal").

 %-----------------------------------------------------------------------------%

-
-
-	% prog_var_at_path(VarMap, PredID, GoalPath, ProgVar) =
+	% prog_var_at_path(VarMap, PredId, GoalPath, ProgVar) =
 	% ConstraintVar consults the map to get the constraint variable
 	% ConstraintVar that says that ProgVar is produced at GoalPath.
 	% The lookup function will report an error if the key (ProgVar
-	% `in` PredID) `at` GoalPath does not exist in the map.
+	% `in` PredId) `at` GoalPath does not exist in the map.
 	%
 :- func prog_var_at_path(mc_var_map, pred_id, goal_path, prog_var) = (mc_var).
-prog_var_at_path(VarMap, PredID, GoalPath, ProgVar) =
-	bimap.lookup(VarMap, ((ProgVar `in` PredID) `at` GoalPath)).
+
+prog_var_at_path(VarMap, PredId, GoalPath, ProgVar) =
+	bimap.lookup(VarMap, ((ProgVar `in` PredId) `at` GoalPath)).

 	% prog_var_at_paths(VarMap, GoalPaths, ProgVar) = ConstraintVars
 	% consults the map to form a list of the constraint variables
 	% that say that ProgVar is produced at each of the paths in
 	% GoalPaths respectively.  The lookup function will report an
-	% error if the key (ProgVar `in` PredID) `at` GoalPath does not
+	% error if the key (ProgVar `in` PredId) `at` GoalPath does not
 	% exist in the map for any of the 'GoalPath's in GoalPaths.
 	%
 :- func prog_var_at_paths(mc_var_map, pred_id, list(goal_path), prog_var) =
 	list(mc_var).
-prog_var_at_paths(VarMap, PredID, GoalPaths, ProgVar) =
+
+prog_var_at_paths(VarMap, PredId, GoalPaths, ProgVar) =
 	list.map(
 		func(GoalPath) = bimap.lookup(
 			VarMap,
-			(ProgVar `in` PredID) `at` GoalPath
+			(ProgVar `in` PredId) `at` GoalPath
 		),
 		GoalPaths
 	).
@@ -840,7 +780,7 @@
 	% consults the VarMap to find constraint variables associated
 	% with each of the program variables in the Nonlocals set for a
 	% GoalPath eg a conjunction and its SubPaths (ie the individual
-	% conjunts), although it doesn't check that the SubPaths are
+	% conjuncts), although it doesn't check that the SubPaths are
 	% indeed subpaths of GoalPath.  Nonlocals are converted to a
 	% sorted set, so the Nth entry of NonlocalsAtPath and the Nth
 	% entry of NonlocalsAtSubPaths are respectively the constraint
@@ -849,45 +789,39 @@
 	%
 :- pred nonlocals_at_path_and_subpaths(
 	mc_var_map::in, pred_id::in, goal_path::in, list(goal_path)::in,
-	nonlocals::in, list(mc_var)::out, list(list(mc_var))::out
-	) is det.
+	nonlocals::in, list(mc_var)::out, list(list(mc_var))::out) is det.

-nonlocals_at_path_and_subpaths(VarMap, PredID, GoalPath, SubPaths, Nonlocals,
+nonlocals_at_path_and_subpaths(VarMap, PredId, GoalPath, SubPaths, Nonlocals,
 	NonlocalsAtPath, NonlocalsAtSubPaths) :-
 	NonlocalsAtPath = list.map(
-		prog_var_at_path(VarMap, PredID, GoalPath),
+		prog_var_at_path(VarMap, PredId, GoalPath),
 		NonlocalsList
 	),
 	NonlocalsAtSubPaths = list.map(
-		prog_var_at_paths(VarMap, PredID, SubPaths),
+		prog_var_at_paths(VarMap, PredId, SubPaths),
 		NonlocalsList
 	),
 	NonlocalsList = set.to_sorted_list(Nonlocals).

-
-
-
 %----------------------------------------------------------------------------%

 mode_decls_constraints(
-	ModuleInfo, VarMap, PredID, Decls, HeadVarsList, Constraints) :-
+	ModuleInfo, VarMap, PredId, Decls, HeadVarsList, Constraints) :-
 	ConstraintsList = list.map_corresponding(
 		mode_decl_constraints(ModuleInfo),
 		list.map(
-			list.map(prog_var_at_path(VarMap, PredID, [])),
+			list.map(prog_var_at_path(VarMap, PredId, [])),
 			HeadVarsList
 		),
 		Decls
 	),
 	Constraints0 = list.condense(ConstraintsList),
-	(	Constraints0 = [conj(OneModeOnlyConstraints)]
-	->	Constraints = OneModeOnlyConstraints
-	;	Constraints = [disj(Constraints0)]
+	( Constraints0 = [conj(OneModeOnlyConstraints)] ->
+        Constraints = OneModeOnlyConstraints
+	;
+        Constraints = [disj(Constraints0)]
 	).

-
-
-
 	% call_mode_decls_constraints(ModuleInfo, VarMap, CallingPred,
 	% 	Decls, GoalPath, CallArgs, Constraints)
 	%
@@ -912,31 +846,27 @@
 :- pred call_mode_decls_constraints(module_info::in,
 	mc_var_map::in, pred_id::in, list(list(mode))::in,
 	goal_path::in, args::in, mode_constraints::out) is det.
-call_mode_decls_constraints(
-	ModuleInfo, VarMap, CallingPred,
-	Decls, GoalPath, CallArgs, Constraints) :-
-	CallArgsHere = list.map(
-		prog_var_at_path(VarMap, CallingPred, GoalPath),
-		CallArgs
-	),
-	Constraints0 = list.condense(list.map(
-		mode_decl_constraints(ModuleInfo, CallArgsHere),
-		Decls
-	)),
-	(	Constraints0 = [conj(OneModeOnlyConstraints)]
-	->	Constraints = OneModeOnlyConstraints
-	;	Constraints = [disj(Constraints0)]
-	).
-

+call_mode_decls_constraints(ModuleInfo, VarMap, CallingPred, Decls, GoalPath,
+        CallArgs, Constraints) :-
+	CallArgsHere = list.map(prog_var_at_path(VarMap, CallingPred, GoalPath),
+		CallArgs),
+	Constraints0 =
+        list.condense(list.map(mode_decl_constraints(ModuleInfo, CallArgsHere),
+		    Decls)),
+	( Constraints0 = [conj(OneModeOnlyConstraints)] ->
+        Constraints = OneModeOnlyConstraints
+	;
+        Constraints = [disj(Constraints0)]
+	).

 	% mode_decl_constraints(ModuleInfo, ConstraintVars, ArgModes)
 	% looks at each mode to see if its variable is produced, and
 	% creates constraints for the corresponding constraint variables
 	% accordingly.
 	%
-:- func mode_decl_constraints(module_info::in,  list(mc_var)::in,
-	list(mode)::in) = (mode_constraints::out) is det.
+:- func mode_decl_constraints(module_info, list(mc_var), list(mode)) =
+    mode_constraints.

 mode_decl_constraints(ModuleInfo, ConstraintVars, ArgModes) =
 	[conj(list.map_corresponding(
@@ -948,18 +878,19 @@
 				InitialInst,
 				FinalInst
 			),
-			(	not inst_match.inst_is_free(
-					ModuleInfo,
-					InitialInst
-				)			% Already produced.
-			->	IsProduced = no		% Not produced here.
-			;	not inst_match.inst_is_free(
-					ModuleInfo,
-					FinalInst
-				)			% free -> non-free
-			->	IsProduced = yes	% Produced here.
-			;	IsProduced = no		% free -> free
-							% Not produced here.
+			(
+			    % Already produced.
+                not inst_match.inst_is_free(ModuleInfo, InitialInst)
+			->
+                IsProduced = no		% Not produced here.
+			;
+                % free -> non-free
+                not inst_match.inst_is_free( ModuleInfo, FinalInst)
+			->
+                IsProduced = yes	% Produced here.
+			;
+                IsProduced = no		% free -> free
+				% Not produced here.
 			)
 		),
 		ConstraintVars,
@@ -970,20 +901,17 @@
 	NumArgs = list.length(Args),
 	NumArgModes = list.length(Decl),
 	Diff = NumArgs - NumArgModes,
-	(	Diff = 0
-	->	FullDecl = Decl
-	;	Diff > 0
-	->	FullDecl = list.append(
+	( Diff = 0 ->
+        FullDecl = Decl
+	; Diff > 0 ->
+        FullDecl = list.append(
 			list.duplicate(Diff, prog_mode.in_mode),
 			Decl
 		)
-	;	error("build_mode_constraints.m: Too many mode declared args.")
+	;
+        unexpected(this_file, "Too many mode declared args.m")
 	).

-
-
-
-
 	% call_headvar_constraints(HeadVars, VarMap, GoalPath, CallArgs,
 	% 	Constraints)
 	% Forms constraints that mean any call arg will be produced if
@@ -992,21 +920,18 @@
 	%
 	% This should not be used if a mode declaration is supplied, as
 	% it means a predicate can only be used in a single mode
-	% throughout a whole scc.
+	% throughout a whole SCC.
 	%
 :- pred call_headvar_constraints(mc_var_map::in, goal_path::in,
-	pred_id::in, args::in, pred_id::in, args::in,
-	mode_constraints::out) is det.
+	    pred_id::in, args::in, pred_id::in, args::in,
+	    mode_constraints::out) is det.
+
 call_headvar_constraints(VarMap, GoalPath,
 	CallingPred, CallArgs, CalledPred, HeadVars, Constraints) :-
-	HeadVarsAtHome = list.map(
-		prog_var_at_path(VarMap, CalledPred, []),
-		HeadVars
-	),
-	CallArgsHere = list.map(
-		prog_var_at_path(VarMap, CallingPred, GoalPath),
-		CallArgs
-	),
+	HeadVarsAtHome = list.map(prog_var_at_path(VarMap, CalledPred, []),
+	    HeadVars),
+	CallArgsHere = list.map( prog_var_at_path(VarMap, CallingPred, GoalPath),
+		CallArgs),
 	Constraints = list.map_corresponding(
 		(func(HeadVarThere, CallArgHere) =
 			atomic_constraint(equivalent(
@@ -1029,12 +954,13 @@
 	% produced at each of the goal paths in which they appear.
 	%
 :- pred fold_goal_into_var_position_maps(
-	mc_var_map::in, pred_id::in, nonlocals::in, hlds_goal::in,
-	multi_map(prog_var, mc_var)::in, multi_map(prog_var, mc_var)::out,
-	multi_map(prog_var, mc_var)::in, multi_map(prog_var, mc_var)::out
-	) is det.
-fold_goal_into_var_position_maps(VarMap, PredID, Nonlocals,
-	_SubGoalExpr - SubGoalInfo, !LocalsMap, !NonlocalsMap) :-
+    mc_var_map::in, pred_id::in, nonlocals::in, hlds_goal::in,
+   	multi_map(prog_var, mc_var)::in, multi_map(prog_var, mc_var)::out,
+   	multi_map(prog_var, mc_var)::in, multi_map(prog_var, mc_var)::out
+    ) is det.
+
+fold_goal_into_var_position_maps(VarMap, PredId, Nonlocals,
+	    _SubGoalExpr - SubGoalInfo, !LocalsMap, !NonlocalsMap) :-
 	goal_info_get_nonlocals(SubGoalInfo, SubGoalNonlocals),
 	goal_info_get_goal_path(SubGoalInfo, SubGoalPath),
 	Nonlocal = set.intersect(SubGoalNonlocals, Nonlocals),
@@ -1048,22 +974,10 @@
 	Local = set.difference(SubGoalNonlocals, Nonlocals),
 		% Note this is the local variables that
 		% are non-local to this particular sub-goal
-	set.fold(
-		fold_variable_into_var_position_map(
-			VarMap, PredID, SubGoalPath
-		),
-		Local,
-		!LocalsMap
-	),
-	set.fold(
-		fold_variable_into_var_position_map(
-			VarMap, PredID, SubGoalPath
-	),
-		Nonlocal,
-		!NonlocalsMap
-	).
-
-
+	set.fold(fold_variable_into_var_position_map(VarMap, PredId, SubGoalPath),
+		Local, !LocalsMap),
+	set.fold(fold_variable_into_var_position_map(VarMap, PredId, SubGoalPath),
+		Nonlocal, !NonlocalsMap).

 	% A subsection of fold_goal_into_var_position_maps, puts into
 	% the map the key ProgVar with the constraint variable that says
@@ -1073,11 +987,10 @@
 	mc_var_map::in, pred_id::in, goal_path::in, prog_var::in,
 	multi_map(prog_var, mc_var)::in, multi_map(prog_var, mc_var)::out
 	) is det .
-fold_variable_into_var_position_map(
-	VarMap, PredID, GoalPath, ProgVar, !Map) :-
-	MCVar = prog_var_at_path(VarMap, PredID, GoalPath, ProgVar),
-	multi_map.set(!.Map, ProgVar, MCVar, !:Map).
-
+
+fold_variable_into_var_position_map(VarMap, PredId, GoalPath, ProgVar, !Map) :-
+	MCVar = prog_var_at_path(VarMap, PredId, GoalPath, ProgVar),
+	svmulti_map.set(ProgVar, MCVar, !Map).

 	% This predicate adds the constraints for a variable in the
 	% non-local set of a conjunction (to other previously
@@ -1088,19 +1001,16 @@
 :- pred fold_nonlocal_var_into_conj_constraints(mc_var_map::in,
 	pred_id::in, multi_map(prog_var, mc_var)::in, goal_path::in,
 	prog_var::in, mode_constraints::in, mode_constraints::out) is det.
-fold_nonlocal_var_into_conj_constraints(
-	VarMap, PredID, NonlocalsMap, GoalPath, ProgVar, !Constraints) :-
-	!:Constraints = [
+
+fold_nonlocal_var_into_conj_constraints(VarMap, PredId, NonlocalsMap,
+        GoalPath, ProgVar, !Constraints) :-
+	list.append([
 		atomic_constraint(equiv_disj(ProgVarAtGoalPath, Xs)),
-		atomic_constraint(at_most_one(Xs))|
-		!.Constraints
-	],
-	ProgVarAtGoalPath = prog_var_at_path(
-		VarMap, PredID, GoalPath, ProgVar
-	),
+		atomic_constraint(at_most_one(Xs))],
+		!Constraints),
+	ProgVarAtGoalPath = prog_var_at_path(VarMap, PredId, GoalPath, ProgVar),
 	Xs = multi_map.lookup(NonlocalsMap, ProgVar).

-
 	% This predicate adds the constraints for a variable in the
 	% non-local set of a conjunct but not nonlocal to the
 	% conjunction as a whole, to the constraints supplied. The
@@ -1112,10 +1022,17 @@
 	mc_var_map::in, multi_map(prog_var, mc_var)::in,
 	prog_var::in, mode_constraints::in, mode_constraints::out) is det.

-fold_local_var_into_conj_constraints(
-	_VarMap, LocalsMap, ProgVar, !Constraints) :-
-	!:Constraints = [
-		atomic_constraint(exactly_one(Xs))|
-		!.Constraints
-	],
+fold_local_var_into_conj_constraints(_VarMap, LocalsMap, ProgVar,
+        !Constraints) :-
+	list.cons(atomic_constraint(exactly_one(Xs)), !Constraints),
 	Xs = multi_map.lookup(LocalsMap, ProgVar).
+
+%-----------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "build_mode_constraints.m".
+
+%-----------------------------------------------------------------------------%
+:- end_module build_mode_constraints.
+%-----------------------------------------------------------------------------%
Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.447
diff -u -r1.447 options.m
--- compiler/options.m	24 Feb 2005 06:07:09 -0000	1.447
+++ compiler/options.m	25 Feb 2005 07:52:14 -0000
@@ -1524,6 +1524,7 @@
 long_option("mode-constraints",		mode_constraints).
 long_option("simple-mode-constraints",	simple_mode_constraints).
 long_option("prop-mode-constraints",	prop_mode_constraints).
+long_option("propagate-mode-constraints", prop_mode_constraints).
 long_option("benchmark-modes",		benchmark_modes).
 long_option("benchmark-modes-repeat",	benchmark_modes_repeat).

Index: compiler/prop_mode_constraints.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prop_mode_constraints.m,v
retrieving revision 1.1
diff -u -r1.1 prop_mode_constraints.m
--- compiler/prop_mode_constraints.m	22 Feb 2005 12:32:11 -0000	1.1
+++ compiler/prop_mode_constraints.m	25 Feb 2005 07:54:21 -0000
@@ -12,37 +12,39 @@
 % structures intended for a propagation solver. It deals only with the
 % simple constraint system, described in the paper "Constraint-based
 % mode analysis of Mercury" by David Overton, Zoltan Somogyi and Peter
-% Stuckey. XXX That paper is the main documentation of the concepts
+% Stuckey.
+%
+% XXX That paper is the main documentation of the concepts
 % behind the algorithm as well as the algorithm itself.
 %
+%-----------------------------------------------------------------------------%

 :- module check_hlds.prop_mode_constraints.
 :- interface.

-:- import_module hlds__hlds_module.
-:- import_module check_hlds.build_mode_constraints.
 :- import_module check_hlds.abstract_mode_constraints.
-:- import_module hlds.hlds_pred.
-:- import_module list, map, io.
+:- import_module check_hlds.build_mode_constraints.

+:- import_module hlds.hlds_module.
+:- import_module hlds.hlds_pred.

+:- import_module io.
+:- import_module list.
+:- import_module map.

+%-----------------------------------------------------------------------------%

 	% This predicate adds to the pred_constraints_map the mode
 	% declaration and goal constraints for each of the predicates in
-	% the provided scc. Any required constraint variables are added
+	% the provided SCC.  Any required constraint variables are added
 	% to the mc_varset and mc_var_map. Calls to predicates with no
 	% mode declaration require head variable constraint variables,
 	% so these are produced first for all preds in the SCC before
 	% goal constraints.
 	%
-:- pred process_scc(
-	module_info::in, list(pred_id)::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out,
-	pred_constraints_map::in, pred_constraints_map::out
-	) is det.
-
+:- pred process_scc(module_info::in, list(pred_id)::in,
+	mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out,
+	pred_constraints_map::in, pred_constraints_map::out) is det.

 	% Storing constraints by predicate.
 	%
@@ -52,45 +54,46 @@
 	% information in the pred_constraints_map, indicating which
 	% predicate each set of constraints applies to.
 	%
-:- pred pretty_print_pred_constraints_map(
-	module_info::in,
-	mc_varset::in,
-	pred_constraints_map::in,
-	io::di, io::uo
-	) is det.
+:- pred pretty_print_pred_constraints_map(module_info::in, mc_varset::in,
+	pred_constraints_map::in, io::di, io::uo) is det.

+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%

 :- implementation.

+:- import_module check_hlds.goal_path.
+:- import_module check_hlds.mode_constraint_robdd.
+:- import_module check_hlds.mode_ordering.
+:- import_module check_hlds.mode_util.
+
+:- import_module hlds.hhf.
+:- import_module hlds.hlds_data.
+:- import_module hlds.hlds_goal.
+:- import_module hlds.inst_graph.
+:- import_module hlds.passes_aux.
+
+:- import_module libs.globals.
+:- import_module libs.options.

-:- import_module check_hlds__goal_path.
-:- import_module check_hlds__mode_constraint_robdd.
-:- import_module check_hlds__mode_ordering.
-:- import_module check_hlds__mode_util.
-:- import_module hlds__hhf.
-:- import_module hlds__hlds_data.
-:- import_module hlds__hlds_goal.
-:- import_module hlds__hlds_pred.
-:- import_module hlds__inst_graph.
-:- import_module hlds__passes_aux.
-:- import_module libs__globals.
-:- import_module libs__options.
 :- import_module mode_robdd.
-:- import_module parse_tree__prog_data.
-:- import_module parse_tree__prog_mode.
+:- import_module parse_tree.prog_data.
+:- import_module parse_tree.prog_mode.
 :- import_module parse_tree.modules.
-:- import_module transform_hlds__dependency_graph.
+:- import_module transform_hlds.dependency_graph.

-:- import_module map, std_util, bool, set, multi_map, require, int.
+:- import_module std_util, bool, set, multi_map, require, int.
 :- import_module robdd, term, string, assoc_list, sparse_bitset.
 :- import_module bimap, varset, term_io.
-:- import_module gc.
+:- import_module svmap.
+
+%-----------------------------------------------------------------------------%

 process_scc(ModuleInfo, SCC0, !Varset, !VarMap, !Constraints) :-
 		% Process only predicates from this module
 	list.filter(
-		(pred(PredID::in) is semidet :-
-			module_info_pred_info(ModuleInfo, PredID, PredInfo),
+		(pred(PredId::in) is semidet :-
+			module_info_pred_info(ModuleInfo, PredId, PredInfo),
 			(	pred_info_is_imported(PredInfo)
 			;	pred_info_is_pseudo_imported(PredInfo)
 			)
@@ -108,11 +111,7 @@

 		% Now go through the SCC and add the constraint
 		% variables and then constraints predicate by predicate
-	foldl3(process_pred(ModuleInfo), SCC, !Varset, !VarMap, !Constraints).
-
-
-
-
+	list.foldl3(process_pred(ModuleInfo), SCC, !Varset, !VarMap, !Constraints).

 	% Performs a number of tasks for one predicate:
 	% 	1) Fills out the goal_path information in the
@@ -123,43 +122,32 @@
 	% 	3) Adds mode declaration constraints
 	% 	4) Adds goal constraints
 	%
-	% Note: It relies on the head variables for any predicate
+	% NOTE: it relies on the head variables for any predicate
 	% without mode declarations that is called to have the
 	% constraint variables corresponding to [] to already be in the
 	% mc_var_map
 	%
 :- pred process_pred(module_info::in, pred_id::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out,
-	pred_constraints_map::in, pred_constraints_map::out
-	) is det.
+	mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out,
+	pred_constraints_map::in, pred_constraints_map::out) is det.

-
-process_pred(ModuleInfo, PredID, !Varset, !VarMap, !Constraints) :-
-	module_info_pred_info(ModuleInfo, PredID, PredInfo),
-	process_pred(
-		ModuleInfo,
-		PredID,
-		PredInfo,
-		!Varset,
-		!VarMap,
-		!Constraints
-	).
+process_pred(ModuleInfo, PredId, !Varset, !VarMap, !Constraints) :-
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	process_pred(ModuleInfo, PredId, PredInfo, !Varset, !VarMap,
+		!Constraints).

 	% The working part of process_pred/8 - just with the pred_info
 	% unpacked from the module_info
 	%
 :- pred process_pred(module_info::in, pred_id::in, pred_info::in,
-	mc_varset::in, mc_varset::out,
-	mc_var_map::in, mc_var_map::out,
-	pred_constraints_map::in, pred_constraints_map::out
-	) is det.
+	mc_varset::in, mc_varset::out, mc_var_map::in, mc_var_map::out,
+	pred_constraints_map::in, pred_constraints_map::out) is det.

-process_pred(ModuleInfo, PredID, PredInfo0, !Varset, !VarMap, !Constraints) :-
+process_pred(ModuleInfo, PredId, PredInfo0, !Varset, !VarMap, !Constraints) :-

 		% XXX Currently the constraints simply say that if a
 		% variable is bound at a disjunct it is bound at the
-		% disjuction by making the relevant variables
+		% disjunction by making the relevant variables
 		% equivalent. Setting GoalPathOptimisation to yes will
 		% cause the disjucts to be given the same path as the
 		% disjunction, so that the relevant constraint variables
@@ -183,23 +171,16 @@
 	clauses_info_headvars(ClausesInfo, HeadVars),
 	clauses_info_clauses(ClausesInfo, Clauses),
 	clauses_info_varset(ClausesInfo, ProgVarset),
-	Goals = list.map(
-		func(clause(_, ClauseBody, _, _)) = ClauseBody,
-		Clauses
-	),
+	Goals = list.map((func(clause(_, ClauseBody, _, _)) = ClauseBody),
+		Clauses),

 		% Here build goal constraint vars.
-	foldl2(
-		add_mc_vars_for_goal(PredID, ProgVarset),
-		Goals,
-		!Varset,
-		!VarMap
-	),
+	list.foldl2(add_mc_vars_for_goal(PredId, ProgVarset),
+		Goals, !Varset, !VarMap),

 		% Here check for mode declarations and add apppropriate
 		% constraints.
 	map.values(ProcTable, ProcInfos),
-

 	list.filter_map(
 		(pred(ProcInfo::in, (ProcHVars - ArgModes)::out) is semidet :-
@@ -218,30 +199,28 @@
 		),
 		ProcInfos,
 		HeadVarArgModesPairs
-	),	% Pair up the any existing arg mode declarations with
-		% their corresponding head variables from the
-		% proc_info's.
-
-	(	HeadVarArgModesPairs = [],
-			% No declared modes, no constraints
+	),
+	%
+	% Pair up the any existing arg mode declarations with
+	% their corresponding head variables from the proc_infos.
+	%
+	(
+		HeadVarArgModesPairs = [], % No declared modes, no constraints
 		ModeDeclConstraints = []
-	;	HeadVarArgModesPairs = [_|_],	% Some declared modes
-		mode_decls_constraints(
-			ModuleInfo,
-			!.VarMap,
-			PredID,
+	;
+		HeadVarArgModesPairs = [_|_],	% Some declared modes
+		mode_decls_constraints(ModuleInfo, !.VarMap, PredId,
 			list.map(snd, HeadVarArgModesPairs),
 			list.map(fst, HeadVarArgModesPairs),
-			ModeDeclConstraints
-		)
+			ModeDeclConstraints)
 	),
-
-
-		% This builds the constraints for this predicate. Note
-		% that the main goal may need to be temporarily formed
-		% by putting clauses into a disjunction. The goal paths
-		% added by goal_path.fill_slots_in_clauses reflect this
-		% disjunction.
+	%
+	% This builds the constraints for this predicate. Note
+	% that the main goal may need to be temporarily formed
+	% by putting clauses into a disjunction. The goal paths
+	% added by goal_path.fill_slots_in_clauses reflect this
+	% disjunction.
+	%
 	(
 		Goals = [],
 		GoalConstraints = []
@@ -252,16 +231,11 @@
 		MainGoal = disj(Goals),
 		MainGoalPath = [],
 		Nonlocals = set.list_to_set(HeadVars),
-		goal_expr_constraints(
-			ModuleInfo, !.VarMap, PredID, MainGoal,
-			MainGoalPath, Nonlocals, GoalConstraints
-		)
+		goal_expr_constraints(ModuleInfo, !.VarMap, PredId, MainGoal,
+			MainGoalPath, Nonlocals, GoalConstraints)
 	),
 	PredConstraints = list.append(ModeDeclConstraints, GoalConstraints),
-	map.det_insert(!.Constraints, PredID, PredConstraints, !:Constraints).
-
-
-
+	svmap.det_insert(PredId, PredConstraints, !Constraints).

 	% Put the constraints to the current output stream in human
 	% readable format. It titles each pred's constraints with a
@@ -281,21 +255,17 @@
 		!IO
 	).

-
-
 	% Puts the constraints for the specified predicate from the
 	% pred_constraints_map to the current output stream in human
 	% readable format.
 	%
-:- pred pretty_print_pred_constraints(
-	module_info::in, mc_varset::in, pred_constraints_map::in,
-	pred_id::in, io::di, io::uo
-	) is det.
-
-pretty_print_pred_constraints(
-	ModuleInfo, ConstraintVarset, PredConstraintsMap, PredID, !IO) :-
-	io.print("\nConstraints for pred ", !IO),
-	hlds_module.module_info_pred_info(ModuleInfo, PredID, PredInfo),
+:- pred pretty_print_pred_constraints(module_info::in, mc_varset::in,
+	pred_constraints_map::in, pred_id::in, io::di, io::uo) is det.
+
+pretty_print_pred_constraints(ModuleInfo, ConstraintVarset,
+		PredConstraintsMap, PredId, !IO) :-
+	io.write_string("\nConstraints for pred ", !IO),
+	hlds_module.module_info_pred_info(ModuleInfo, PredId, PredInfo),
 	ModuleName = hlds_pred.pred_info_module(PredInfo),
 	PredName = hlds_pred.pred_info_name(PredInfo),
 	CreateDirectories = no,
@@ -304,16 +274,12 @@
 		CreateDirectories,
 		FullPredNameString, !IO
 	),
-	io.print(FullPredNameString, !IO),
-	io.print(":\n", !IO),
+	io.write_string(FullPredNameString ++ ":\n", !IO),

-	map.lookup(
-		PredConstraintsMap,
-		PredID,
-		PredConstraints
-	),
-	abstract_mode_constraints.pretty_print_constraints(
-		ConstraintVarset,
-		PredConstraints,
-		!IO
-	).
+	map.lookup(PredConstraintsMap, PredId, PredConstraints),
+	abstract_mode_constraints.pretty_print_constraints(ConstraintVarset,
+		PredConstraints, !IO).
+
+%----------------------------------------------------------------------------%
+:- end_module prop_mode_constraints.
+%----------------------------------------------------------------------------%

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