[m-rev.] diff: more cleanups, part 2

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Apr 5 15:05:36 AEST 2004


Index: compiler/dead_proc_elim.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dead_proc_elim.m,v
retrieving revision 1.88
diff -u -b -r1.88 dead_proc_elim.m
--- compiler/dead_proc_elim.m	23 Mar 2004 10:52:02 -0000	1.88
+++ compiler/dead_proc_elim.m	3 Apr 2004 14:21:21 -0000
@@ -28,23 +28,20 @@
 
 :- type dead_proc_pass
 	--->	warning_pass
-	;	final_optimization_pass
-	.
+	;	final_optimization_pass.
 
 	% Eliminate dead procedures.
 	% If the first argument is `warning_pass',
 	% also warn about any user-defined procedures that are dead.
 	% If the first argument is `final_optimization_pass',
 	% also eliminate any opt_imported procedures.
-:- pred dead_proc_elim(dead_proc_pass, module_info, module_info,
-		io__state, io__state).
-:- mode dead_proc_elim(in, in, out, di, uo) is det.
+:- pred dead_proc_elim(dead_proc_pass::in, module_info::in, module_info::out,
+	io::di, io::uo) is det.
 
 	% Analyze which entities are needed, and for those entities
 	% which are needed, record how many times they are referenced
 	% (this information is used by our inlining heuristics).
-:- pred dead_proc_elim__analyze(module_info, needed_map).
-:- mode dead_proc_elim__analyze(in, out) is det.
+:- pred dead_proc_elim__analyze(module_info::in, needed_map::out) is det.
 
 	% Optimize away any dead predicates.
 	% This is performed immediately after make_hlds.m to avoid doing
@@ -52,8 +49,7 @@
 	% files which are not used in the current module. This assumes that
 	% the clauses_info is still valid, so it cannot be run after mode
 	% analysis.
-:- pred dead_pred_elim(module_info, module_info).
-:- mode dead_pred_elim(in, out) is det.
+:- pred dead_pred_elim(module_info::in, module_info::out) is det.
 
 :- type entity
 	--->	proc(pred_id, proc_id)
@@ -122,33 +118,32 @@
 	% Note: changes here are likely to require changes to
 	% dead_pred_elim as well.
 
-:- pred dead_proc_elim__initialize(module_info, entity_queue, needed_map).
-:- mode dead_proc_elim__initialize(in, out, out) is det.
+:- pred dead_proc_elim__initialize(module_info::in,
+	entity_queue::out, needed_map::out) is det.
 
-dead_proc_elim__initialize(ModuleInfo, Queue, Needed) :-
-	queue__init(Queue0),
-	map__init(Needed0),
+dead_proc_elim__initialize(ModuleInfo, !:Queue, !:Needed) :-
+	!:Queue = queue__init,
+	!:Needed = map__init,
 	module_info_predids(ModuleInfo, PredIds),
 	module_info_preds(ModuleInfo, PredTable),
-	dead_proc_elim__initialize_preds(PredIds, PredTable,
-		Queue0, Queue1, Needed0, Needed1),
+	dead_proc_elim__initialize_preds(PredIds, PredTable, !Queue, !Needed),
 	module_info_get_pragma_exported_procs(ModuleInfo, PragmaExports),
 	dead_proc_elim__initialize_pragma_exports(PragmaExports,
-		Queue1, Queue2, Needed1, Needed2),
+		!Queue, !Needed),
 	module_info_type_ctor_gen_infos(ModuleInfo, TypeCtorGenInfos),
 	dead_proc_elim__initialize_base_gen_infos(TypeCtorGenInfos,
-		Queue2, Queue3, Needed2, Needed3),
+		!Queue, !Needed),
 	module_info_classes(ModuleInfo, Classes),
 	module_info_instances(ModuleInfo, Instances),
 	dead_proc_elim__initialize_class_methods(Classes, Instances,
-		Queue3, Queue, Needed3, Needed).
+		!Queue, !Needed).
 
 	% Add all normally exported procedures within the listed predicates
 	% to the queue and map.
 
-:- pred dead_proc_elim__initialize_preds(list(pred_id), pred_table,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__initialize_preds(in, in, in, out, in, out) is det.
+:- pred dead_proc_elim__initialize_preds(list(pred_id)::in, pred_table::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
 dead_proc_elim__initialize_preds([], _PredTable, !Queue, !Needed).
 dead_proc_elim__initialize_preds([PredId | PredIds], PredTable,
@@ -160,41 +155,41 @@
 
 	% Add the listed procedures to the queue and map.
 
-:- pred dead_proc_elim__initialize_procs(pred_id, list(proc_id),
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__initialize_procs(in, in, in, out, in, out) is det.
+:- pred dead_proc_elim__initialize_procs(pred_id::in, list(proc_id)::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-dead_proc_elim__initialize_procs(_PredId, [], Queue, Queue, Needed, Needed).
+dead_proc_elim__initialize_procs(_PredId, [], !Queue, !Needed).
 dead_proc_elim__initialize_procs(PredId, [ProcId | ProcIds],
-		Queue0, Queue, Needed0, Needed) :-
-	queue__put(Queue0, proc(PredId, ProcId), Queue1),
-	map__set(Needed0, proc(PredId, ProcId), no, Needed1),
-	dead_proc_elim__initialize_procs(PredId, ProcIds,
-		Queue1, Queue, Needed1, Needed).
+		!Queue, !Needed) :-
+	queue__put(!.Queue, proc(PredId, ProcId), !:Queue),
+	map__set(!.Needed, proc(PredId, ProcId), no, !:Needed),
+	dead_proc_elim__initialize_procs(PredId, ProcIds, !Queue, !Needed).
 
 	% Add procedures exported to C by a pragma(export, ...) declaration
 	% to the queue and map.
 
-:- pred dead_proc_elim__initialize_pragma_exports(list(pragma_exported_proc),
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__initialize_pragma_exports(in, in, out, in, out) is det.
+:- pred dead_proc_elim__initialize_pragma_exports(
+	list(pragma_exported_proc)::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-dead_proc_elim__initialize_pragma_exports([], Queue, Queue, Needed, Needed).
+dead_proc_elim__initialize_pragma_exports([], !Queue, !Needed).
 dead_proc_elim__initialize_pragma_exports([PragmaProc | PragmaProcs],
-		Queue0, Queue, Needed0, Needed) :-
+		!Queue, !Needed) :-
 	PragmaProc = pragma_exported_proc(PredId, ProcId, _CFunction, _Ctxt),
-	queue__put(Queue0, proc(PredId, ProcId), Queue1),
-	map__set(Needed0, proc(PredId, ProcId), no, Needed1),
+	queue__put(!.Queue, proc(PredId, ProcId), !:Queue),
+	map__set(!.Needed, proc(PredId, ProcId), no, !:Needed),
 	dead_proc_elim__initialize_pragma_exports(PragmaProcs,
-		Queue1, Queue, Needed1, Needed).
+		!Queue, !Needed).
 
-:- pred dead_proc_elim__initialize_base_gen_infos(list(type_ctor_gen_info),
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__initialize_base_gen_infos(in, in, out, in, out) is det.
+:- pred dead_proc_elim__initialize_base_gen_infos(list(type_ctor_gen_info)::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-dead_proc_elim__initialize_base_gen_infos([], Queue, Queue, Needed, Needed).
+dead_proc_elim__initialize_base_gen_infos([], !Queue, !Needed).
 dead_proc_elim__initialize_base_gen_infos([TypeCtorGenInfo | TypeCtorGenInfos],
-		Queue0, Queue, Needed0, Needed) :-
+		!Queue, !Needed) :-
 	TypeCtorGenInfo = type_ctor_gen_info(_TypeCtor, ModuleName, TypeName,
 		Arity, _Status, _HldsDefn, _Unify, _Compare),
 	(
@@ -217,35 +212,32 @@
 		semidet_succeed
 	->
 		Entity = base_gen_info(ModuleName, TypeName, Arity),
-		queue__put(Queue0, Entity, Queue1),
-		map__set(Needed0, Entity, no, Needed1)
+		queue__put(!.Queue, Entity, !:Queue),
+		map__set(!.Needed, Entity, no, !:Needed)
 	;
-		Queue1 = Queue0,
-		Needed1 = Needed0
+		true
 	),
 	dead_proc_elim__initialize_base_gen_infos(TypeCtorGenInfos,
-		Queue1, Queue, Needed1, Needed).
+		!Queue, !Needed).
+
+:- pred dead_proc_elim__initialize_class_methods(class_table::in,
+	instance_table::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-:- pred dead_proc_elim__initialize_class_methods(class_table, instance_table,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__initialize_class_methods(in, in,
-	in, out, in, out) is det.
-
-dead_proc_elim__initialize_class_methods(Classes, Instances, Queue0, Queue,
-		Needed0, Needed) :-
-	map__values(Instances, InstanceDefns0),
-	list__condense(InstanceDefns0, InstanceDefns),
-	list__foldl2(get_instance_pred_procs, InstanceDefns, Queue0, Queue1,
-		Needed0, Needed1),
+dead_proc_elim__initialize_class_methods(Classes, Instances,
+		!Queue, !Needed) :-
+	map__values(Instances, InstanceDefnsLists),
+	list__condense(InstanceDefnsLists, InstanceDefns),
+	list__foldl2(get_instance_pred_procs, InstanceDefns, !Queue, !Needed),
 	map__values(Classes, ClassDefns),
-	list__foldl2(get_class_pred_procs, ClassDefns, Queue1, Queue,
-		Needed1, Needed).
+	list__foldl2(get_class_pred_procs, ClassDefns, !Queue, !Needed).
 
-:- pred get_instance_pred_procs(hlds_instance_defn, entity_queue, entity_queue,
-	needed_map, needed_map).
-:- mode get_instance_pred_procs(in, in, out, in, out) is det.
+:- pred get_instance_pred_procs(hlds_instance_defn::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-get_instance_pred_procs(Instance, Queue0, Queue, Needed0, Needed) :-
+get_instance_pred_procs(Instance, !Queue, !Needed) :-
 	Instance = hlds_instance_defn(_, _, _, _, _, _, PredProcIds, _, _),
 
 	%
@@ -254,46 +246,42 @@
 	%
 	(
 			% This should never happen
-		PredProcIds = no,
-		Queue = Queue0,
-		Needed = Needed0
+		PredProcIds = no
 	;
 		PredProcIds = yes(Ids),
 		list__foldl2(get_class_interface_pred_proc, Ids,
-			Queue0, Queue, Needed0, Needed)
+			!Queue, !Needed)
 	).
 
-:- pred get_class_pred_procs(hlds_class_defn, entity_queue, entity_queue,
-		needed_map, needed_map).
-:- mode get_class_pred_procs(in, in, out, in, out) is det.
+:- pred get_class_pred_procs(hlds_class_defn::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-get_class_pred_procs(Class, Queue0, Queue, Needed0, Needed) :-
+get_class_pred_procs(Class, !Queue, !Needed) :-
 	Class = hlds_class_defn(_, _, _, _, Methods, _, _),
-	list__foldl2(get_class_interface_pred_proc, Methods,
-		Queue0, Queue, Needed0, Needed).
+	list__foldl2(get_class_interface_pred_proc, Methods, !Queue, !Needed).
 
 :- pred get_class_interface_pred_proc(hlds_class_proc::in,
 	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
 	is det.
 
-get_class_interface_pred_proc(ClassProc, Queue0, Queue, Needed0, Needed) :-
+get_class_interface_pred_proc(ClassProc, !Queue, !Needed) :-
 	ClassProc = hlds_class_proc(PredId, ProcId),
-	queue__put(Queue0, proc(PredId, ProcId), Queue),
-	map__set(Needed0, proc(PredId, ProcId), no, Needed).
+	queue__put(!.Queue, proc(PredId, ProcId), !:Queue),
+	map__set(!.Needed, proc(PredId, ProcId), no, !:Needed).
 
 %-----------------------------------------------------------------------------%
 
-:- pred dead_proc_elim__examine(entity_queue, examined_set, module_info,
-	needed_map, needed_map).
-:- mode dead_proc_elim__examine(in, in, in, in, out) is det.
+:- pred dead_proc_elim__examine(entity_queue::in, examined_set::in,
+	module_info::in, needed_map::in, needed_map::out) is det.
 
-dead_proc_elim__examine(Queue0, Examined0, ModuleInfo, Needed0, Needed) :-
+dead_proc_elim__examine(Queue0, Examined0, ModuleInfo, !Needed) :-
 	% see if the queue is empty
 	( queue__get(Queue0, Entity, Queue1) ->
 		% see if the next element has been examined before
 		( set__member(Entity, Examined0) ->
 			dead_proc_elim__examine(Queue1, Examined0, ModuleInfo,
-				Needed0, Needed)
+				!Needed)
 		;
 			set__insert(Examined0, Entity, Examined1),
 			(
@@ -301,44 +289,42 @@
 				PredProcId = proc(PredId, ProcId),
 				dead_proc_elim__examine_proc(
 					PredProcId, ModuleInfo,
-					Queue1, Queue2, Needed0, Needed1)
+					Queue1, Queue2, !Needed)
 			;
 				Entity = base_gen_info(Module, Type, Arity),
 				dead_proc_elim__examine_base_gen_info(
 					Module, Type, Arity, ModuleInfo,
-					Queue1, Queue2, Needed0, Needed1)
+					Queue1, Queue2, !Needed)
 			),
 			dead_proc_elim__examine(Queue2, Examined1, ModuleInfo,
-				Needed1, Needed)
+				!Needed)
 		)
 	;
-		Needed = Needed0
+		true
 	).
 
 %-----------------------------------------------------------------------------%
 
-:- pred dead_proc_elim__examine_base_gen_info(module_name, string, arity,
-	module_info, entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_base_gen_info(in, in, in, in, in, out, in, out)
+:- pred dead_proc_elim__examine_base_gen_info(module_name::in, string::in,
+	arity::in, module_info::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
 	is det.
 
 dead_proc_elim__examine_base_gen_info(ModuleName, TypeName, Arity, ModuleInfo,
-		Queue0, Queue, Needed0, Needed) :-
+		!Queue, !Needed) :-
 	module_info_type_ctor_gen_infos(ModuleInfo, TypeCtorGenInfos),
 	(
 		dead_proc_elim__find_base_gen_info(ModuleName, TypeName,
 			Arity, TypeCtorGenInfos, Refs)
 	->
-		dead_proc_elim__examine_refs(Refs, Queue0, Queue,
-			Needed0, Needed)
+		dead_proc_elim__examine_refs(Refs, !Queue, !Needed)
 	;
-		Queue = Queue0,
-		Needed = Needed0
+		true
 	).
 
-:- pred dead_proc_elim__find_base_gen_info(module_name, string, arity,
-	list(type_ctor_gen_info), list(pred_proc_id)).
-:- mode dead_proc_elim__find_base_gen_info(in, in, in, in, out) is semidet.
+:- pred dead_proc_elim__find_base_gen_info(module_name::in, string::in,
+	arity::in, list(type_ctor_gen_info)::in, list(pred_proc_id)::out)
+	is semidet.
 
 dead_proc_elim__find_base_gen_info(ModuleName, TypeName, TypeArity,
 		[TypeCtorGenInfo | TypeCtorGenInfos], Refs) :-
@@ -348,36 +334,34 @@
 			Unify, Compare)
 	->
 		Refs = [Unify, Compare]
-		% dead_proc_elim__maybe_add_ref(MaybePretty,  Refs0, Refs)
 	;
 		dead_proc_elim__find_base_gen_info(ModuleName, TypeName,
 			TypeArity, TypeCtorGenInfos, Refs)
 	).
 
-:- pred dead_proc_elim__maybe_add_ref(maybe(pred_proc_id),
-	list(pred_proc_id), list(pred_proc_id)).
-:- mode dead_proc_elim__maybe_add_ref(in, in, out) is det.
+:- pred dead_proc_elim__maybe_add_ref(maybe(pred_proc_id)::in,
+	list(pred_proc_id)::in, list(pred_proc_id)::out) is det.
 
 dead_proc_elim__maybe_add_ref(no, Refs, Refs).
 dead_proc_elim__maybe_add_ref(yes(Ref), Refs, [Ref | Refs]).
 
-:- pred dead_proc_elim__examine_refs(list(pred_proc_id),
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_refs(in, in, out, in, out) is det.
+:- pred dead_proc_elim__examine_refs(list(pred_proc_id)::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-dead_proc_elim__examine_refs([], Queue, Queue, Needed, Needed).
-dead_proc_elim__examine_refs([Ref | Refs], Queue0, Queue, Needed0, Needed) :-
+dead_proc_elim__examine_refs([], !Queue, !Needed).
+dead_proc_elim__examine_refs([Ref | Refs], !Queue, !Needed) :-
 	Ref = proc(PredId, ProcId),
 	Entity = proc(PredId, ProcId),
-	queue__put(Queue0, Entity, Queue1),
-	map__set(Needed0, Entity, no, Needed1),
-	dead_proc_elim__examine_refs(Refs, Queue1, Queue, Needed1, Needed).
+	queue__put(!.Queue, Entity, !:Queue),
+	map__set(!.Needed, Entity, no, !:Needed),
+	dead_proc_elim__examine_refs(Refs, !Queue, !Needed).
 
 %-----------------------------------------------------------------------------%
 
-:- pred dead_proc_elim__examine_proc(pred_proc_id, module_info,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_proc(in, in, in, out, in, out) is det.
+:- pred dead_proc_elim__examine_proc(pred_proc_id::in, module_info::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
 dead_proc_elim__examine_proc(proc(PredId, ProcId), ModuleInfo,
 		!Queue, !Needed) :-
@@ -396,106 +380,82 @@
 		true
 	).
 
-:- pred dead_proc_elim__examine_goals(list(hlds_goal), pred_proc_id,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_goals(in, in, in, out, in, out) is det.
-
-dead_proc_elim__examine_goals([], _, Queue, Queue, Needed, Needed).
-dead_proc_elim__examine_goals([Goal | Goals], CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue1,
-		Needed0, Needed1),
-	dead_proc_elim__examine_goals(Goals, CurrProc, Queue1, Queue,
-		Needed1, Needed).
-
-:- pred dead_proc_elim__examine_cases(list(case), pred_proc_id,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_cases(in, in, in, out, in, out) is det.
-
-dead_proc_elim__examine_cases([], _CurrProc, Queue, Queue, Needed, Needed).
-dead_proc_elim__examine_cases([case(_, Goal) | Cases], CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue1,
-		Needed0, Needed1),
-	dead_proc_elim__examine_cases(Cases, CurrProc, Queue1, Queue,
-		Needed1, Needed).
-
-:- pred dead_proc_elim__examine_goal(hlds_goal, pred_proc_id,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_goal(in, in, in, out, in, out) is det.
-
-dead_proc_elim__examine_goal(GoalExpr - _, CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_expr(GoalExpr, CurrProc, Queue0, Queue,
-		Needed0, Needed).
+:- pred dead_proc_elim__examine_goals(list(hlds_goal)::in, pred_proc_id::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
 
-:- pred dead_proc_elim__examine_expr(hlds_goal_expr, pred_proc_id,
-	entity_queue, entity_queue, needed_map, needed_map).
-:- mode dead_proc_elim__examine_expr(in, in, in, out, in, out) is det.
-
-dead_proc_elim__examine_expr(disj(Goals), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goals(Goals, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(conj(Goals), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goals(Goals, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(par_conj(Goals), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goals(Goals, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(not(Goal), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(some(_, _, Goal), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_goal(Goal, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(switch(_, _, Cases), CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
-	dead_proc_elim__examine_cases(Cases, CurrProc, Queue0, Queue,
-		Needed0, Needed).
-dead_proc_elim__examine_expr(if_then_else(_, Cond, Then, Else),
-		CurrProc, Queue0, Queue, Needed0, Needed) :-
-	dead_proc_elim__examine_goal(Cond, CurrProc, Queue0, Queue1,
-		Needed0, Needed1),
-	dead_proc_elim__examine_goal(Then, CurrProc, Queue1, Queue2,
-		Needed1, Needed2),
-	dead_proc_elim__examine_goal(Else, CurrProc, Queue2, Queue,
-		Needed2, Needed).
-dead_proc_elim__examine_expr(generic_call(_,_,_,_), _,
-		Queue, Queue, Needed, Needed).
+dead_proc_elim__examine_goals([], _, !Queue, !Needed).
+dead_proc_elim__examine_goals([Goal | Goals], CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goal(Goal, CurrProc, !Queue, !Needed),
+	dead_proc_elim__examine_goals(Goals, CurrProc, !Queue, !Needed).
+
+:- pred dead_proc_elim__examine_cases(list(case)::in, pred_proc_id::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
+
+dead_proc_elim__examine_cases([], _CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_cases([case(_, Goal) | Cases], CurrProc,
+		!Queue, !Needed) :-
+	dead_proc_elim__examine_goal(Goal, CurrProc, !Queue, !Needed),
+	dead_proc_elim__examine_cases(Cases, CurrProc, !Queue, !Needed).
+
+:- pred dead_proc_elim__examine_goal(hlds_goal::in, pred_proc_id::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
+
+dead_proc_elim__examine_goal(GoalExpr - _, CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_expr(GoalExpr, CurrProc, !Queue, !Needed).
+
+:- pred dead_proc_elim__examine_expr(hlds_goal_expr::in, pred_proc_id::in,
+	entity_queue::in, entity_queue::out, needed_map::in, needed_map::out)
+	is det.
+
+dead_proc_elim__examine_expr(disj(Goals), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goals(Goals, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(conj(Goals), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goals(Goals, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(par_conj(Goals), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goals(Goals, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(not(Goal), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goal(Goal, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(some(_, _, Goal), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_goal(Goal, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(switch(_, _, Cases), CurrProc, !Queue, !Needed) :-
+	dead_proc_elim__examine_cases(Cases, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(if_then_else(_, Cond, Then, Else), CurrProc,
+		!Queue, !Needed) :-
+	dead_proc_elim__examine_goal(Cond, CurrProc, !Queue, !Needed),
+	dead_proc_elim__examine_goal(Then, CurrProc, !Queue, !Needed),
+	dead_proc_elim__examine_goal(Else, CurrProc, !Queue, !Needed).
+dead_proc_elim__examine_expr(generic_call(_,_,_,_), _, !Queue, !Needed).
 dead_proc_elim__examine_expr(call(PredId, ProcId, _,_,_,_),
-		CurrProc, Queue0, Queue, Needed0, Needed) :-
-	queue__put(Queue0, proc(PredId, ProcId), Queue),
+		CurrProc, !Queue, !Needed) :-
+	queue__put(!.Queue, proc(PredId, ProcId), !:Queue),
 	( proc(PredId, ProcId) = CurrProc ->
 		% if it's reachable and recursive, then we can't
 		% eliminate or inline it
 		NewNotation = no,
-		map__set(Needed0, proc(PredId, ProcId), NewNotation, Needed)
-	; map__search(Needed0, proc(PredId, ProcId), OldNotation) ->
+		map__set(!.Needed, proc(PredId, ProcId), NewNotation, !:Needed)
+	; map__search(!.Needed, proc(PredId, ProcId), OldNotation) ->
 		(
 			OldNotation = no,
 			NewNotation = no
 		;
-			OldNotation = yes(Count0),
-			Count = Count0 + 1,
-			NewNotation = yes(Count)
+			OldNotation = yes(Count),
+			NewNotation = yes(Count + 1)
 		),
-		map__det_update(Needed0, proc(PredId, ProcId), NewNotation,
-			Needed)
+		map__det_update(!.Needed, proc(PredId, ProcId), NewNotation,
+			!:Needed)
 	;
 		NewNotation = yes(1),
-		map__set(Needed0, proc(PredId, ProcId), NewNotation, Needed)
+		map__set(!.Needed, proc(PredId, ProcId), NewNotation, !:Needed)
 	).
-dead_proc_elim__examine_expr(foreign_proc(_, PredId, ProcId, _,
-		_, _, _), _CurrProc, Queue0, Queue, Needed0, Needed) :-
-	queue__put(Queue0, proc(PredId, ProcId), Queue),
-	map__set(Needed0, proc(PredId, ProcId), no, Needed).
-dead_proc_elim__examine_expr(unify(_,_,_, Uni, _), _CurrProc, Queue0, Queue,
-		Needed0, Needed) :-
+dead_proc_elim__examine_expr(foreign_proc(_, PredId, ProcId, _, _, _, _),
+		_CurrProc, !Queue, !Needed) :-
+	queue__put(!.Queue, proc(PredId, ProcId), !:Queue),
+	map__set(!.Needed, proc(PredId, ProcId), no, !:Needed).
+dead_proc_elim__examine_expr(unify(_,_,_, Uni, _), _CurrProc,
+		!Queue, !Needed) :-
 	(
 		Uni = construct(_, ConsId, _, _, _, _, _),
 		(
@@ -506,11 +466,10 @@
 			Entity = base_gen_info(Module, TypeName, Arity)
 		)
 	->
-		queue__put(Queue0, Entity, Queue),
-		map__set(Needed0, Entity, no, Needed)
+		queue__put(!.Queue, Entity, !:Queue),
+		map__set(!.Needed, Entity, no, !:Needed)
 	;
-		Queue = Queue0,
-		Needed = Needed0
+		true
 	).
 dead_proc_elim__examine_expr(shorthand(_), _, _, _, _, _) :-
 	% these should have been expanded out by now
@@ -536,20 +495,21 @@
 	module_info::in, module_info::out, io__state::di, io__state::uo)
 	is det.
 
-dead_proc_elim__eliminate(Pass, Needed0, !ModuleInfo, !IO) :-
+dead_proc_elim__eliminate(Pass, !.Needed, !ModuleInfo, !IO) :-
 	module_info_predids(!.ModuleInfo, PredIds),
 	module_info_preds(!.ModuleInfo, PredTable0),
 
 	Changed0 = no,
-	ElimInfo0 = elimination_info(Needed0, !.ModuleInfo, PredTable0,
+	ElimInfo0 = elimination_info(!.Needed, !.ModuleInfo, PredTable0,
 		Changed0),
 	list__foldl2(dead_proc_elim__eliminate_pred(Pass), PredIds,
 		ElimInfo0, ElimInfo, !IO),
-	ElimInfo = elimination_info(Needed, !:ModuleInfo, PredTable, Changed),
+	ElimInfo = elimination_info(!:Needed, !:ModuleInfo, PredTable,
+		Changed),
 
 	module_info_set_preds(PredTable, !ModuleInfo),
 	module_info_type_ctor_gen_infos(!.ModuleInfo, TypeCtorGenInfos0),
-	dead_proc_elim__eliminate_base_gen_infos(TypeCtorGenInfos0, Needed,
+	dead_proc_elim__eliminate_base_gen_infos(TypeCtorGenInfos0, !.Needed,
 		TypeCtorGenInfos),
 	module_info_set_type_ctor_gen_infos(TypeCtorGenInfos, !ModuleInfo),
 	(
@@ -564,12 +524,12 @@
 
 		% eliminate any unused procedures for this pred
 
-:- pred dead_proc_elim__eliminate_pred(dead_proc_pass, pred_id,
-	elim_info, elim_info, io__state, io__state).
-:- mode dead_proc_elim__eliminate_pred(in, in, in, out, di, uo) is det.
+:- pred dead_proc_elim__eliminate_pred(dead_proc_pass::in, pred_id::in,
+	elim_info::in, elim_info::out, io::di, io::uo) is det.
 
-dead_proc_elim__eliminate_pred(Pass, PredId, ElimInfo0, ElimInfo, !IO) :-
-	ElimInfo0 = elimination_info(Needed, ModuleInfo, PredTable0, Changed0),
+dead_proc_elim__eliminate_pred(Pass, PredId, !ElimInfo, !IO) :-
+	!.ElimInfo = elimination_info(Needed, ModuleInfo, PredTable0,
+		Changed0),
 	map__lookup(PredTable0, PredId, PredInfo0),
 	pred_info_import_status(PredInfo0, Status),
 	(
@@ -613,9 +573,9 @@
 	->
 		ProcIds = pred_info_procids(PredInfo0),
 		pred_info_procedures(PredInfo0, ProcTable0),
-		list__foldl2(dead_proc_elim__eliminate_proc(Pass, PredId,
-			Keep, WarnForThisProc, ElimInfo0),
-			ProcIds, Changed0 - ProcTable0, Changed - ProcTable,
+		list__foldl3(dead_proc_elim__eliminate_proc(Pass, PredId,
+			Keep, WarnForThisProc, !.ElimInfo),
+			ProcIds, ProcTable0, ProcTable, Changed0, Changed,
 			!IO),
 		pred_info_set_procedures(ProcTable, PredInfo0, PredInfo),
 		map__det_update(PredTable0, PredId, PredInfo, PredTable)
@@ -663,58 +623,55 @@
 		PredTable = PredTable0,
 		Changed = Changed0
 	),
-	ElimInfo = elimination_info(Needed, ModuleInfo, PredTable, Changed).
+	!:ElimInfo = elimination_info(Needed, ModuleInfo, PredTable, Changed).
 
 		% eliminate a procedure, if unused
 
-:- pred dead_proc_elim__eliminate_proc(dead_proc_pass, pred_id, maybe(proc_id),
-	bool, elim_info, proc_id,
-	pair(bool, proc_table), pair(bool, proc_table),
-	io__state, io__state).
-:- mode dead_proc_elim__eliminate_proc(in, in, in, in, in, in, in, out, di, uo)
-	is det.
+:- pred dead_proc_elim__eliminate_proc(dead_proc_pass::in, pred_id::in,
+	maybe(proc_id)::in, bool::in, elim_info::in, proc_id::in,
+	proc_table::in, proc_table::out, bool::in, bool::out,
+	io::di, io::uo) is det.
 
 dead_proc_elim__eliminate_proc(Pass, PredId, Keep, WarnForThisProc, ElimInfo,
-		ProcId, Changed0 - ProcTable0, Changed - ProcTable) -->
-	{ ElimInfo = elimination_info(Needed, ModuleInfo, _PredTable, _) },
+		ProcId, !ProcTable, !Changed, !IO) :-
+	ElimInfo = elimination_info(Needed, ModuleInfo, _PredTable, _),
 	(
 		% Keep the procedure if it is in the needed map
 		% or if it is to be kept because it is exported.
-		( { map__search(Needed, proc(PredId, ProcId), _) }
-		; { Keep = yes(ProcId) }
+		( map__search(Needed, proc(PredId, ProcId), _)
+		; Keep = yes(ProcId)
 		)
 	->
-		{ ProcTable = ProcTable0 },
-		{ Changed = Changed0 }
+		true
 	;
-		{ Changed = yes },
-		globals__io_lookup_bool_option(very_verbose, VeryVerbose),
-		( { VeryVerbose = yes } ->
+		!:Changed = yes,
+		globals__io_lookup_bool_option(very_verbose, VeryVerbose, !IO),
+		( VeryVerbose = yes ->
 			write_proc_progress_message(
 				"% Eliminated the dead procedure ",
-				PredId, ProcId, ModuleInfo)
+				PredId, ProcId, ModuleInfo, !IO)
 		;
-			[]
+			true
 		),
 		(
-			{ Pass = warning_pass },
-			{ WarnForThisProc = yes }
+			Pass = warning_pass,
+			WarnForThisProc = yes
 			% we don't need to check the warn_dead_procs option
 			% since that is already checked by mercury_compile.m
 			% when deciding whether to invoke this warning_pass
 		->
-			{ proc_info_context(ProcTable0 ^ det_elem(ProcId),
-				Context) },
-			warn_dead_proc(PredId, ProcId, Context, ModuleInfo)
+			proc_info_context(!.ProcTable ^ det_elem(ProcId),
+				Context),
+			warn_dead_proc(PredId, ProcId, Context, ModuleInfo,
+				!IO)
 		;
-			[]
+			true
 		),
-		{ map__delete(ProcTable0, ProcId, ProcTable) }
+		map__delete(!.ProcTable, ProcId, !:ProcTable)
 	).
 
-:- pred warn_dead_proc(pred_id, proc_id, prog_context, module_info,
-		io__state, io__state).
-:- mode warn_dead_proc(in, in, in, in, di, uo) is det.
+:- pred warn_dead_proc(pred_id::in, proc_id::in, prog_context::in,
+	module_info::in, io::di, io::uo) is det.
 
 warn_dead_proc(PredId, ProcId, Context, ModuleInfo, !IO) :-
 	describe_one_proc_name(ModuleInfo, proc(PredId, ProcId),
@@ -723,9 +680,8 @@
 			words("is never called.")],
 	error_util__report_warning(Context, 0, Components, !IO).
 
-:- pred dead_proc_elim__eliminate_base_gen_infos(list(type_ctor_gen_info),
-	needed_map, list(type_ctor_gen_info)).
-:- mode dead_proc_elim__eliminate_base_gen_infos(in, in, out) is det.
+:- pred dead_proc_elim__eliminate_base_gen_infos(list(type_ctor_gen_info)::in,
+	needed_map::in, list(type_ctor_gen_info)::out) is det.
 
 dead_proc_elim__eliminate_base_gen_infos([], _Needed, []).
 dead_proc_elim__eliminate_base_gen_infos([TypeCtorGenInfo0 | TypeCtorGenInfos0],
Index: compiler/delay_construct.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_construct.m,v
retrieving revision 1.5
diff -u -b -r1.5 delay_construct.m
--- compiler/delay_construct.m	24 Oct 2003 06:17:36 -0000	1.5
+++ compiler/delay_construct.m	3 Apr 2004 16:35:29 -0000
@@ -32,7 +32,7 @@
 :- import_module io.
 
 :- pred delay_construct_proc(pred_id::in, proc_id::in, module_info::in,
-	proc_info::in, proc_info::out, io__state::di, io__state::uo) is det.
+	proc_info::in, proc_info::out, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/dependency_graph.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dependency_graph.m,v
retrieving revision 1.68
diff -u -b -r1.68 dependency_graph.m
--- compiler/dependency_graph.m	23 Mar 2004 10:52:02 -0000	1.68
+++ compiler/dependency_graph.m	3 Apr 2004 14:31:08 -0000
@@ -31,36 +31,33 @@
 	% for which there are clauses defined (ie not imported except
 	% for opt_imported).
 	%
-:- pred module_info_ensure_dependency_info(module_info, module_info).
-:- mode module_info_ensure_dependency_info(in, out) is det.
+:- pred module_info_ensure_dependency_info(module_info::in, module_info::out)
+	is det.
 
 	% Build the dependency graph, if the bool is yes then
 	% imported procedures are included in the dependency graph,
 	% otherwise they aren't.
 	%
-:- pred dependency_graph__build_pred_dependency_graph(module_info, bool,
-	dependency_info(pred_id)).
-:- mode dependency_graph__build_pred_dependency_graph(in, in, out) is det.
+:- pred dependency_graph__build_pred_dependency_graph(module_info::in,
+	bool::in, dependency_info(pred_id)::out) is det.
 
 	% Output a form of the static call graph to a file, in a format
 	% suitable for use in .dependency_info files.
-:- pred dependency_graph__write_dependency_graph(module_info, module_info,
-	io__state, io__state).
-:- mode dependency_graph__write_dependency_graph(in, out, di, uo) is det.
+:- pred dependency_graph__write_dependency_graph(module_info::in,
+	module_info::out, io::di, io::uo) is det.
 
 	% Output a form of the static call graph to a file for use by the
 	% profiler.
-:- pred dependency_graph__write_prof_dependency_graph(module_info, module_info,
-	io__state, io__state).
-:- mode dependency_graph__write_prof_dependency_graph(in, out, di, uo) is det.
+:- pred dependency_graph__write_prof_dependency_graph(module_info::in,
+	module_info::out, io::di, io::uo) is det.
 
 	% Given the list of predicates in a strongly connected component
 	% of the dependency graph, a list of the higher SCCs in the module
 	% and a module_info, find out which members of the SCC can be
 	% called from outside the SCC.
-:- pred dependency_graph__get_scc_entry_points(list(pred_proc_id),
-	dependency_ordering, module_info, list(pred_proc_id)).
-:- mode dependency_graph__get_scc_entry_points(in, in, in, out) is det.
+:- pred dependency_graph__get_scc_entry_points(list(pred_proc_id)::in,
+	dependency_ordering::in, module_info::in, list(pred_proc_id)::out)
+	is det.
 
 	% Create the Aditi dependency ordering. This contains all the Aditi
 	% SCCs in the original program. The difference is that SCCs which
@@ -71,8 +68,8 @@
 	% dead_proc_elim.m should be be run before this is called
 	% to avoid missing some opportunities for merging where
 	% a procedure is called from a dead procedure.
-:- pred module_info_ensure_aditi_dependency_info(module_info, module_info).
-:- mode module_info_ensure_aditi_dependency_info(in, out) is det.
+:- pred module_info_ensure_aditi_dependency_info(module_info::in,
+	module_info::out) is det.
 
 	% write_graph(Graph, WriteNode, WriteEdge)
 	%
@@ -84,7 +81,7 @@
 	pred(pred_proc_id, io__state, io__state)::pred(in, di, uo) is det,
 	pred(pred_proc_id, pred_proc_id, io__state, io__state)::
 		pred(in, in, di, uo) is det,
-	io__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 
 	% write_graph_nodes(Nodes, Graph, WriteNode, WriteEdge)
 	%
@@ -96,7 +93,7 @@
 	pred(pred_proc_id, io__state, io__state)::pred(in, di, uo) is det,
 	pred(pred_proc_id, pred_proc_id, io__state, io__state)::
 		pred(in, in, di, uo) is det,
-	io__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -141,9 +138,8 @@
 dependency_graph__build_pred_dependency_graph(ModuleInfo, Imported, DepInfo) :-
 	dependency_graph__build_dependency_graph(ModuleInfo, Imported, DepInfo).
 
-:- pred dependency_graph__build_dependency_graph(module_info, bool,
-	dependency_info(T)) <= dependency_node(T).
-:- mode dependency_graph__build_dependency_graph(in, in, out) is det.
+:- pred dependency_graph__build_dependency_graph(module_info::in, bool::in,
+	dependency_info(T)::out) is det <= dependency_node(T).
 
 dependency_graph__build_dependency_graph(ModuleInfo, Imported, DepInfo) :-
 	module_info_predids(ModuleInfo, PredIds),
@@ -158,9 +154,8 @@
 	dependency_graph__sets_to_lists(DepOrd0, [], DepOrd),
 	hlds_dependency_info_set_dependency_ordering(DepOrd, DepInfo1, DepInfo).
 
-:- pred dependency_graph__sets_to_lists(list(set(T)), list(list(T)),
-	list(list(T))).
-:- mode dependency_graph__sets_to_lists(in, in, out) is det.
+:- pred dependency_graph__sets_to_lists(list(set(T))::in, list(list(T))::in,
+	list(list(T))::out) is det.
 
 dependency_graph__sets_to_lists([], Xs, Xs).
 dependency_graph__sets_to_lists([X | Xs], Ys, Zs) :-
@@ -171,13 +166,13 @@
 %-----------------------------------------------------------------------------%
 
 :- typeclass dependency_node(T) where [
-	pred dependency_graph__add_nodes(list(pred_id), module_info, bool,
-		dependency_graph(T), dependency_graph(T)),
-	mode dependency_graph__add_nodes(in, in, in, in, out) is det,
-
-	pred dependency_graph__add_arcs(list(pred_id), module_info, bool,
-		dependency_graph(T), dependency_graph(T)),
-	mode dependency_graph__add_arcs(in, in, in, in, out) is det,
+	pred dependency_graph__add_nodes(list(pred_id)::in, module_info::in,
+		bool::in, dependency_graph(T)::in, dependency_graph(T)::out)
+		is det,
+
+	pred dependency_graph__add_arcs(list(pred_id)::in, module_info::in,
+		bool::in, dependency_graph(T)::in, dependency_graph(T)::out)
+		is det,
 
 	func dependency_node(pred_proc_id) = T
 ].
@@ -201,9 +196,9 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_pred_proc_nodes(list(pred_id), module_info,
-	bool, dependency_graph, dependency_graph).
-:- mode dependency_graph__add_pred_proc_nodes(in, in, in, in, out) is det.
+:- pred dependency_graph__add_pred_proc_nodes(list(pred_id)::in,
+	module_info::in, bool::in,
+	dependency_graph::in, dependency_graph::out) is det.
 
 dependency_graph__add_pred_proc_nodes([], _ModuleInfo, _, !DepGraph).
 dependency_graph__add_pred_proc_nodes([PredId | PredIds], ModuleInfo, Imported,
@@ -225,9 +220,8 @@
 	dependency_graph__add_pred_proc_nodes(PredIds, ModuleInfo, Imported,
 		!DepGraph).
 
-:- pred dependency_graph__add_proc_nodes(list(proc_id), pred_id, module_info,
-	dependency_graph, dependency_graph).
-:- mode dependency_graph__add_proc_nodes(in, in, in, in, out) is det.
+:- pred dependency_graph__add_proc_nodes(list(proc_id)::in, pred_id::in,
+	module_info::in, dependency_graph::in, dependency_graph::out) is det.
 
 dependency_graph__add_proc_nodes([], _PredId, _ModuleInfo, !DepGraph).
 dependency_graph__add_proc_nodes([ProcId | ProcIds], PredId, ModuleInfo,
@@ -238,9 +232,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_pred_nodes(list(pred_id), module_info,
-	bool, dependency_graph(pred_id), dependency_graph(pred_id)).
-:- mode dependency_graph__add_pred_nodes(in, in, in, in, out) is det.
+:- pred dependency_graph__add_pred_nodes(list(pred_id)::in, module_info::in,
+	bool::in,
+	dependency_graph(pred_id)::in, dependency_graph(pred_id)::out) is det.
 
 dependency_graph__add_pred_nodes([], _ModuleInfo, _, DepGraph, DepGraph).
 dependency_graph__add_pred_nodes([PredId | PredIds], ModuleInfo,
@@ -263,9 +257,9 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_pred_proc_arcs(list(pred_id), module_info, bool,
-	dependency_graph, dependency_graph).
-:- mode dependency_graph__add_pred_proc_arcs(in, in, in, in, out) is det.
+:- pred dependency_graph__add_pred_proc_arcs(list(pred_id)::in,
+	module_info::in, bool::in,
+	dependency_graph::in, dependency_graph::out) is det.
 
 dependency_graph__add_pred_proc_arcs([], _ModuleInfo, _, !DepGraph).
 dependency_graph__add_pred_proc_arcs([PredId | PredIds], ModuleInfo, Imported,
@@ -287,9 +281,9 @@
 	dependency_graph__add_pred_proc_arcs(PredIds, ModuleInfo, Imported,
 		!DepGraph).
 
-:- pred dependency_graph__add_proc_arcs(list(proc_id), pred_id, module_info,
-	bool, dependency_graph, dependency_graph).
-:- mode dependency_graph__add_proc_arcs(in, in, in, in, in, out) is det.
+:- pred dependency_graph__add_proc_arcs(list(proc_id)::in, pred_id::in,
+	module_info::in, bool::in,
+	dependency_graph::in, dependency_graph::out) is det.
 
 dependency_graph__add_proc_arcs([], _PredId, _ModuleInfo, _, !DepGraph).
 dependency_graph__add_proc_arcs([ProcId | ProcIds], PredId, ModuleInfo,
@@ -325,9 +319,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_pred_arcs(list(pred_id), module_info, bool,
-	dependency_graph(pred_id), dependency_graph(pred_id)).
-:- mode dependency_graph__add_pred_arcs(in, in, in, in, out) is det.
+:- pred dependency_graph__add_pred_arcs(list(pred_id)::in, module_info::in,
+	bool::in,
+	dependency_graph(pred_id)::in, dependency_graph(pred_id)::out) is det.
 
 dependency_graph__add_pred_arcs([], _ModuleInfo, _, !DepGraph).
 dependency_graph__add_pred_arcs([PredId | PredIds], ModuleInfo,
@@ -359,18 +353,19 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_arcs_in_goal(hlds_goal, relation_key,
-	dependency_graph(T), dependency_graph(T)) <= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_goal(in, in, in, out) is det.
+:- pred dependency_graph__add_arcs_in_goal(hlds_goal::in, relation_key::in,
+	dependency_graph(T)::in, dependency_graph(T)::out) is det
+	<= dependency_node(T).
 
 dependency_graph__add_arcs_in_goal(Goal - _GoalInfo, PPId, !DepGraph) :-
 	dependency_graph__add_arcs_in_goal_2(Goal, PPId, !DepGraph).
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_arcs_in_goal_2(hlds_goal_expr, relation_key,
-	dependency_graph(T), dependency_graph(T)) <= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_goal_2(in, in, in, out) is det.
+:- pred dependency_graph__add_arcs_in_goal_2(hlds_goal_expr::in,
+	relation_key::in,
+	dependency_graph(T)::in, dependency_graph(T)::out) is det
+	<= dependency_node(T).
 
 dependency_graph__add_arcs_in_goal_2(conj(Goals), Caller, !DepGraph) :-
 	dependency_graph__add_arcs_in_list(Goals, Caller, !DepGraph).
@@ -402,9 +397,7 @@
 
 dependency_graph__add_arcs_in_goal_2(call(PredId, ProcId, _, Builtin, _, _),
 		Caller, !DepGraph) :-
-	(
-		Builtin = inline_builtin
-	->
+	( Builtin = inline_builtin ->
 		true
 	;
 		(
@@ -447,11 +440,9 @@
 	dependency_graph__add_arcs_in_goal_2_shorthand(ShorthandGoal, Caller,
 		!DepGraph).
 
-:- pred dependency_graph__add_arcs_in_goal_2_shorthand(shorthand_goal_expr,
-	relation_key, dependency_graph(T), dependency_graph(T))
-	<= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_goal_2_shorthand(in, in, in, out)
-	is det.
+:- pred dependency_graph__add_arcs_in_goal_2_shorthand(shorthand_goal_expr::in,
+	relation_key::in, dependency_graph(T)::in, dependency_graph(T)::out)
+	is det <= dependency_node(T).
 
 dependency_graph__add_arcs_in_goal_2_shorthand(bi_implication(LHS, RHS),
 		Caller, !DepGraph) :-
@@ -459,9 +450,10 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_arcs_in_list(list(hlds_goal), relation_key,
-	dependency_graph(T), dependency_graph(T)) <= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_list(in, in, in, out) is det.
+:- pred dependency_graph__add_arcs_in_list(list(hlds_goal)::in,
+	relation_key::in,
+	dependency_graph(T)::in, dependency_graph(T)::out) is det
+	<= dependency_node(T).
 
 dependency_graph__add_arcs_in_list([], _Caller, !DepGraph).
 dependency_graph__add_arcs_in_list([Goal|Goals], Caller, !DepGraph) :-
@@ -470,9 +462,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_arcs_in_cases(list(case), relation_key,
-	dependency_graph(T), dependency_graph(T)) <= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_cases(in, in, in, out) is det.
+:- pred dependency_graph__add_arcs_in_cases(list(case)::in, relation_key::in,
+	dependency_graph(T)::in, dependency_graph(T)::out) is det
+	<= dependency_node(T).
 
 dependency_graph__add_arcs_in_cases([], _Caller, !DepGraph).
 dependency_graph__add_arcs_in_cases([case(Cons, Goal) | Goals], Caller,
@@ -483,9 +475,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__add_arcs_in_cons(cons_id, relation_key,
-	dependency_graph(T), dependency_graph(T)) <= dependency_node(T).
-:- mode dependency_graph__add_arcs_in_cons(in, in, in, out) is det.
+:- pred dependency_graph__add_arcs_in_cons(cons_id::in, relation_key::in,
+	dependency_graph(T)::in, dependency_graph(T)::out) is det
+	<= dependency_node(T).
 
 dependency_graph__add_arcs_in_cons(cons(_, _), _Caller, !DepGraph).
 dependency_graph__add_arcs_in_cons(int_const(_), _Caller, !DepGraph).
@@ -524,9 +516,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred dependency_graph__write_dependency_ordering(list(list(pred_proc_id)),
-	module_info, int, io__state, io__state).
-:- mode dependency_graph__write_dependency_ordering(in, in, in, di, uo) is det.
+:- pred dependency_graph__write_dependency_ordering(
+	list(list(pred_proc_id))::in, module_info::in, int::in,
+	io::di, io::uo) is det.
 
 dependency_graph__write_dependency_ordering([], _ModuleInfo, _N, !IO) :-
 	io__write_string("\n", !IO).
@@ -539,9 +531,8 @@
 	N1 = N + 1,
 	dependency_graph__write_dependency_ordering(Rest, ModuleInfo, N1, !IO).
 
-:- pred dependency_graph__write_clique(list(pred_proc_id), module_info,
-	io__state, io__state).
-:- mode dependency_graph__write_clique(in, in, di, uo) is det.
+:- pred dependency_graph__write_clique(list(pred_proc_id)::in, module_info::in,
+	io::di, io::uo) is det.
 
 dependency_graph__write_clique([], _ModuleInfo, !IO).
 dependency_graph__write_clique([proc(PredId, ProcId) | Rest], ModuleInfo,
@@ -856,7 +847,8 @@
 			EqvSCCs, MergedSCCs, NoMerge, SCCRel,
 			SCCPred, [], Ordering)
 	;
-		error("dependency_graph__merge_aditi_sccs: SCC dependency relation is cyclic")
+		error("dependency_graph__merge_aditi_sccs: " ++
+			"SCC dependency relation is cyclic")
 	).
 
 :- pred dependency_graph__merge_aditi_sccs_2(list(scc_id)::in,
@@ -867,9 +859,7 @@
 dependency_graph__merge_aditi_sccs_2([], _, _, _, _, _, _, !Ordering).
 dependency_graph__merge_aditi_sccs_2([SCCid | SCCs0], ModuleInfo, EqvSCCs0,
 		MergedSCCs0, NoMergeSCCs, SCCRel, SCCPreds, !Ordering) :-
-	(
-		set__member(SCCid, MergedSCCs0)
-	->
+	( set__member(SCCid, MergedSCCs0) ->
 			% This SCC has been merged into its parent.
 		EqvSCCs = EqvSCCs0,
 		SCCs = SCCs0
Index: compiler/det_analysis.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/det_analysis.m,v
retrieving revision 1.164
diff -u -b -r1.164 det_analysis.m
--- compiler/det_analysis.m	1 Apr 2004 04:32:38 -0000	1.164
+++ compiler/det_analysis.m	3 Apr 2004 18:20:50 -0000
@@ -67,33 +67,31 @@
 	% Perform determinism inference for local predicates with no
 	% determinism declarations, and determinism checking for all other
 	% predicates.
-:- pred determinism_pass(module_info, module_info, io__state, io__state).
-:- mode determinism_pass(in, out, di, uo) is det.
+:- pred determinism_pass(module_info::in, module_info::out,
+	io::di, io::uo) is det.
 
 	% Check the determinism of a single procedure
 	% (only works if the determinism of the procedures it calls
 	% has already been inferred).
-:- pred determinism_check_proc(proc_id, pred_id, module_info, module_info,
-	io__state, io__state).
-:- mode determinism_check_proc(in, in, in, out, di, uo) is det.
+:- pred determinism_check_proc(proc_id::in, pred_id::in,
+	module_info::in, module_info::out, io::di, io::uo) is det.
 
 	% Infer the determinism of a procedure.
 
-:- pred det_infer_proc(pred_id, proc_id, module_info, module_info, globals,
-	determinism, determinism, list(det_msg)).
-:- mode det_infer_proc(in, in, in, out, in, out, out, out) is det.
+:- 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.
 
 	% Infers the determinism of `Goal0' and returns this in `Detism'.
 	% It annotates the goal and all its subgoals with their determinism
 	% and returns the annotated goal in `Goal'.
 
-:- pred det_infer_goal(hlds_goal, instmap, soln_context, det_info,
-	hlds_goal, determinism, list(det_msg)).
-:- mode det_infer_goal(in, in, in, in, out, out, out) is det.
+:- pred det_infer_goal(hlds_goal::in, instmap::in, soln_context::in,
+	det_info::in, hlds_goal::out, determinism::out, list(det_msg)::out)
+	is det.
 
 	% Work out how many solutions are needed for a given determinism.
-:- pred det_get_soln_context(determinism, soln_context).
-:- mode det_get_soln_context(in, out) is det.
+:- pred det_get_soln_context(determinism::in, soln_context::out) is det.
 
 :- type soln_context
 	--->	all_solns
@@ -102,29 +100,27 @@
 	% The tables for computing the determinism of compound goals
 	% from the determinism of their components.
 
-:- pred det_conjunction_detism(determinism, determinism, determinism).
-:- mode det_conjunction_detism(in, in, out) is det.
+:- pred det_conjunction_detism(determinism::in, determinism::in,
+	determinism::out) is det.
 
-:- pred det_par_conjunction_detism(determinism, determinism, determinism).
-:- mode det_par_conjunction_detism(in, in, out) is det.
+:- pred det_par_conjunction_detism(determinism::in, determinism::in,
+	determinism::out) is det.
 
-:- pred det_switch_detism(determinism, determinism, determinism).
-:- mode det_switch_detism(in, in, out) is det.
+:- pred det_switch_detism(determinism::in, determinism::in, determinism::out)
+	is det.
 
-:- pred det_disjunction_maxsoln(soln_count, soln_count, soln_count).
-:- mode det_disjunction_maxsoln(in, in, out) is det.
+:- pred det_disjunction_maxsoln(soln_count::in, soln_count::in,
+	soln_count::out) is det.
 
-:- pred det_disjunction_canfail(can_fail, can_fail, can_fail).
-:- mode det_disjunction_canfail(in, in, out) is det.
+:- pred det_disjunction_canfail(can_fail::in, can_fail::in, can_fail::out)
+	is det.
 
-:- pred det_switch_maxsoln(soln_count, soln_count, soln_count).
-:- mode det_switch_maxsoln(in, in, out) is det.
+:- pred det_switch_maxsoln(soln_count::in, soln_count::in, soln_count::out)
+	is det.
 
-:- pred det_switch_canfail(can_fail, can_fail, can_fail).
-:- mode det_switch_canfail(in, in, out) is det.
+:- pred det_switch_canfail(can_fail::in, can_fail::in, can_fail::out) is det.
 
-:- pred det_negation_det(determinism, maybe(determinism)).
-:- mode det_negation_det(in, out) is det.
+:- pred det_negation_det(determinism::in, maybe(determinism)::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -143,36 +139,34 @@
 
 %-----------------------------------------------------------------------------%
 
-determinism_pass(ModuleInfo0, ModuleInfo) -->
-	{ determinism_declarations(ModuleInfo0, DeclaredProcs,
-		UndeclaredProcs, NoInferProcs) },
-	{ list__foldl(set_non_inferred_proc_determinism, NoInferProcs,
-		ModuleInfo0, ModuleInfo1) },
-	globals__io_lookup_bool_option(verbose, Verbose),
-	globals__io_lookup_bool_option(debug_det, Debug),
-	( { UndeclaredProcs = [] } ->
-		{ ModuleInfo2 = ModuleInfo1 }
+determinism_pass(!ModuleInfo, !IO) :-
+	determinism_declarations(!.ModuleInfo, DeclaredProcs,
+		UndeclaredProcs, NoInferProcs),
+	list__foldl(set_non_inferred_proc_determinism, NoInferProcs,
+		!ModuleInfo),
+	globals__io_lookup_bool_option(verbose, Verbose, !IO),
+	globals__io_lookup_bool_option(debug_det, Debug, !IO),
+	( UndeclaredProcs = [] ->
+		true
 	;
 		maybe_write_string(Verbose,
-			"% Doing determinism inference...\n"),
-		global_inference_pass(ModuleInfo1, UndeclaredProcs, Debug,
-			ModuleInfo2),
-		maybe_write_string(Verbose, "% done.\n")
-	),
-	maybe_write_string(Verbose, "% Doing determinism checking...\n"),
-	global_final_pass(ModuleInfo2, DeclaredProcs, Debug, ModuleInfo),
-	maybe_write_string(Verbose, "% done.\n").
-
-determinism_check_proc(ProcId, PredId, ModuleInfo0, ModuleInfo) -->
-	globals__io_lookup_bool_option(debug_det, Debug),
-	global_final_pass(ModuleInfo0, [proc(PredId, ProcId)], Debug,	
-		ModuleInfo).
+			"% Doing determinism inference...\n", !IO),
+		global_inference_pass(!ModuleInfo, UndeclaredProcs, Debug,
+			!IO),
+		maybe_write_string(Verbose, "% done.\n", !IO)
+	),
+	maybe_write_string(Verbose, "% Doing determinism checking...\n", !IO),
+	global_final_pass(!ModuleInfo, DeclaredProcs, Debug, !IO),
+	maybe_write_string(Verbose, "% done.\n", !IO).
+
+determinism_check_proc(ProcId, PredId, !ModuleInfo, !IO) :-
+	globals__io_lookup_bool_option(debug_det, Debug, !IO),
+	global_final_pass(!ModuleInfo, [proc(PredId, ProcId)], Debug, !IO).
 
 %-----------------------------------------------------------------------------%
 
-:- pred global_inference_pass(module_info, pred_proc_list, bool, module_info,
-	io__state, io__state).
-:- mode global_inference_pass(in, in, in, out, di, uo) is det.
+:- pred global_inference_pass(module_info::in, module_info::out,
+	pred_proc_list::in, bool::in, io::di, io::uo) is det.
 
 	% Iterate until a fixpoint is reached. This can be expensive
 	% if a module has many predicates with undeclared determinisms.
@@ -180,78 +174,73 @@
 	% iterations only on strongly connected components of the
 	% dependency graph.
 
-global_inference_pass(ModuleInfo0, ProcList, Debug, ModuleInfo) -->
-	global_inference_single_pass(ProcList, Debug, ModuleInfo0, ModuleInfo1,
-		[], Msgs, unchanged, Changed),
-	maybe_write_string(Debug, "% Inference pass complete\n"),
-	( { Changed = changed } ->
-		global_inference_pass(ModuleInfo1, ProcList, Debug, ModuleInfo)
+global_inference_pass(!ModuleInfo, ProcList, Debug, !IO) :-
+	global_inference_single_pass(ProcList, Debug, !ModuleInfo, [], Msgs,
+		unchanged, Changed, !IO),
+	maybe_write_string(Debug, "% Inference pass complete\n", !IO),
+	( Changed = changed ->
+		global_inference_pass(!ModuleInfo, ProcList, Debug, !IO)
 	;
 		% We have arrived at a fixpoint. Therefore all the messages we
 		% have are based on the final determinisms of all procedures,
 		% which means it is safe to print them.
-		det_report_and_handle_msgs(Msgs, ModuleInfo1, ModuleInfo)
+		det_report_and_handle_msgs(Msgs, !ModuleInfo, !IO)
 	).
 
-:- pred global_inference_single_pass(pred_proc_list, bool,
-	module_info, module_info, list(det_msg), list(det_msg),
-	maybe_changed, maybe_changed, io__state, io__state).
-:- mode global_inference_single_pass(in, in, in, out, in, out, in, out, di, uo)
-	is det.
+:- 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,
+	maybe_changed::in, maybe_changed::out, io::di, io::uo) is det.
 
-global_inference_single_pass([], _, ModuleInfo, ModuleInfo, Msgs, Msgs,
-		Changed, Changed) --> [].
+global_inference_single_pass([], _, !ModuleInfo, !Msgs, !Changed, !IO).
 global_inference_single_pass([proc(PredId, ProcId) | PredProcs], Debug,
-		ModuleInfo0, ModuleInfo, Msgs0, Msgs, Changed0, Changed) -->
-	globals__io_get_globals(Globals),
-	{ det_infer_proc(PredId, ProcId, ModuleInfo0, ModuleInfo1, Globals,
-		Detism0, Detism, ProcMsgs) },
-	( { Detism = Detism0 } ->
-		( { Debug = yes } ->
-			io__write_string("% Inferred old detism "),
-			mercury_output_det(Detism),
-			io__write_string(" for "),
-			hlds_out__write_pred_proc_id(ModuleInfo1,
-				PredId, ProcId),
-			io__write_string("\n")
-		;
-			[]
-		),
-		{ Changed1 = Changed0 }
-	;
-		( { Debug = yes } ->
-			io__write_string("% Inferred new detism "),
-			mercury_output_det(Detism),
-			io__write_string(" for "),
-			hlds_out__write_pred_proc_id(ModuleInfo1,
-				PredId, ProcId),
-			io__write_string("\n")
-		;
-			[]
-		),
-		{ Changed1 = changed }
-	),
-	{ list__append(ProcMsgs, Msgs0, Msgs1) },
-	global_inference_single_pass(PredProcs, Debug,
-		ModuleInfo1, ModuleInfo, Msgs1, Msgs, Changed1, Changed).
-
-:- pred global_final_pass(module_info, pred_proc_list, bool,
-	module_info, io__state, io__state).
-:- mode global_final_pass(in, in, in, out, di, uo) is det.
-
-global_final_pass(ModuleInfo0, ProcList, Debug, ModuleInfo) -->
-	global_inference_single_pass(ProcList, Debug, ModuleInfo0, ModuleInfo1,
-		[], Msgs, unchanged, _),
-	det_report_and_handle_msgs(Msgs, ModuleInfo1, ModuleInfo2),
-	global_checking_pass(ProcList, ModuleInfo2, ModuleInfo).
+		!ModuleInfo, !Msgs, !Changed, !IO) :-
+	globals__io_get_globals(Globals, !IO),
+	det_infer_proc(PredId, ProcId, !ModuleInfo, Globals,
+		Detism0, Detism, ProcMsgs),
+	( Detism = Detism0 ->
+		( Debug = yes ->
+			io__write_string("% Inferred old detism ", !IO),
+			mercury_output_det(Detism, !IO),
+			io__write_string(" for ", !IO),
+			hlds_out__write_pred_proc_id(!.ModuleInfo,
+				PredId, ProcId, !IO),
+			io__write_string("\n", !IO)
+		;
+			true
+		)
+	;
+		( Debug = yes ->
+			io__write_string("% Inferred new detism ", !IO),
+			mercury_output_det(Detism, !IO),
+			io__write_string(" for ", !IO),
+			hlds_out__write_pred_proc_id(!.ModuleInfo,
+				PredId, ProcId, !IO),
+			io__write_string("\n", !IO)
+		;
+			true
+		),
+		!:Changed = changed
+	),
+	list__append(ProcMsgs, !Msgs),
+	global_inference_single_pass(PredProcs, Debug, !ModuleInfo, !Msgs,
+		!Changed, !IO).
+
+:- pred global_final_pass(module_info::in, module_info::out,
+	pred_proc_list::in, bool::in, io::di, io::uo) is det.
+
+global_final_pass(!ModuleInfo, ProcList, Debug, !IO) :-
+	global_inference_single_pass(ProcList, Debug, !ModuleInfo,
+		[], Msgs, unchanged, _, !IO),
+	det_report_and_handle_msgs(Msgs, !ModuleInfo, !IO),
+	global_checking_pass(ProcList, !ModuleInfo, !IO).
 
 %-----------------------------------------------------------------------------%
 
-det_infer_proc(PredId, ProcId, ModuleInfo0, ModuleInfo, Globals,
-		Detism0, Detism, Msgs) :-
+det_infer_proc(PredId, ProcId, !ModuleInfo, Globals, Detism0, Detism, Msgs) :-
 
 		% Get the proc_info structure for this procedure
-	module_info_preds(ModuleInfo0, Preds0),
+	module_info_preds(!.ModuleInfo, Preds0),
 	map__lookup(Preds0, PredId, Pred0),
 	pred_info_procedures(Pred0, Procs0),
 	map__lookup(Procs0, ProcId, Proc0),
@@ -282,9 +271,10 @@
 
 		% Infer the determinism of the goal
 	proc_info_goal(Proc0, Goal0),
-	proc_info_get_initial_instmap(Proc0, ModuleInfo0, InstMap0),
+	proc_info_get_initial_instmap(Proc0, !.ModuleInfo, InstMap0),
 	proc_info_vartypes(Proc0, VarTypes),
-	det_info_init(ModuleInfo0, VarTypes, PredId, ProcId, Globals, DetInfo),
+	det_info_init(!.ModuleInfo, VarTypes, PredId, ProcId, Globals,
+		DetInfo),
 	det_infer_goal(Goal0, InstMap0, SolnContext, DetInfo,
 			Goal, Detism1, Msgs),
 
@@ -313,7 +303,7 @@
 	map__det_update(Procs0, ProcId, Proc, Procs),
 	pred_info_set_procedures(Procs, Pred0, Pred),
 	map__det_update(Preds0, PredId, Pred, Preds),
-	module_info_set_preds(Preds, ModuleInfo0, ModuleInfo).
+	module_info_set_preds(Preds, !ModuleInfo).
 
 %-----------------------------------------------------------------------------%
 
@@ -470,11 +460,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_infer_goal_2(hlds_goal_expr, hlds_goal_info, instmap,
-	soln_context, det_info, set(prog_var), instmap_delta,
-	hlds_goal_expr, determinism, list(det_msg)).
-:- mode det_infer_goal_2(in, in, in, in, in, in, in, out, out, out) is det.
-
+:- pred det_infer_goal_2(hlds_goal_expr::in, hlds_goal_info::in, instmap::in,
+	soln_context::in, det_info::in, set(prog_var)::in, instmap_delta::in,
+	hlds_goal_expr::out, determinism::out, list(det_msg)::out) is det.
 	% The determinism of a conjunction is the worst case of the elements
 	% of that conjuction.
 
@@ -529,8 +517,8 @@
 	),
 	ExaminesRep = yes,
 	det_check_for_noncanonical_type(Var, ExaminesRep, SwitchCanFail,
-		SwitchSolnContext, GoalInfo, switch, DetInfo, Msgs0,
-		SwitchSolns, Msgs),
+		SwitchSolnContext, GoalInfo, switch, DetInfo, SwitchSolns,
+		Msgs0, Msgs),
 	det_conjunction_canfail(SwitchCanFail, CasesCanFail, CanFail),
 	det_conjunction_maxsoln(SwitchSolns, CasesSolns, NumSolns),
 	determinism_components(Detism, CanFail, NumSolns).
@@ -633,8 +621,8 @@
 	det_infer_unify_canfail(U, UnifyCanFail),
 	det_infer_unify_examines_rep(U, ExaminesRepresentation),
 	det_check_for_noncanonical_type(LT, ExaminesRepresentation,
-		UnifyCanFail, SolnContext, GoalInfo, unify(C), DetInfo, Msgs3,
-		UnifyNumSolns, Msgs),
+		UnifyCanFail, SolnContext, GoalInfo, unify(C), DetInfo,
+		UnifyNumSolns, Msgs3, Msgs),
 	determinism_components(UnifyDet, UnifyCanFail, UnifyNumSolns).
 
 det_infer_goal_2(if_then_else(Vars, Cond0, Then0, Else0), _GoalInfo0,
@@ -769,9 +757,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_infer_conj(list(hlds_goal), instmap, soln_context, det_info,
-		list(hlds_goal), determinism, list(det_msg)).
-:- mode det_infer_conj(in, in, in, in, out, out, out) is det.
+:- pred det_infer_conj(list(hlds_goal)::in, instmap::in, soln_context::in,
+	det_info::in, list(hlds_goal)::out, determinism::out,
+	list(det_msg)::out) is det.
 
 det_infer_conj([], _InstMap0, _SolnContext, _DetInfo, [], det, []).
 det_infer_conj([Goal0 | Goals0], InstMap0, SolnContext, DetInfo, 
@@ -820,9 +808,9 @@
 	det_conjunction_detism(DetismA, DetismB, Detism),
 	list__append(MsgsA, MsgsB, Msgs).
 
-:- pred det_infer_par_conj(list(hlds_goal), instmap, soln_context, det_info,
-		list(hlds_goal), determinism, list(det_msg)).
-:- mode det_infer_par_conj(in, in, in, in, out, out, out) is det.
+:- pred det_infer_par_conj(list(hlds_goal)::in, instmap::in, soln_context::in,
+	det_info::in, list(hlds_goal)::out, determinism::out,
+	list(det_msg)::out) is det.
 
 det_infer_par_conj([], _InstMap0, _SolnContext, _DetInfo, [], det, []).
 det_infer_par_conj([Goal0 | Goals0], InstMap0, SolnContext, DetInfo, 
@@ -841,9 +829,9 @@
 	determinism_components(Detism, CanFail, MaxSolns),
 	list__append(MsgsA, MsgsB, Msgs).
 
-:- pred det_infer_disj(list(hlds_goal), instmap, soln_context, det_info,
-	can_fail, soln_count, list(hlds_goal), determinism, list(det_msg)).
-:- mode det_infer_disj(in, in, in, in, in, in, out, out, out) is det.
+:- pred det_infer_disj(list(hlds_goal)::in, instmap::in, soln_context::in,
+	det_info::in, can_fail::in, soln_count::in, list(hlds_goal)::out,
+	determinism::out, list(det_msg)::out) is det.
 
 det_infer_disj([], _InstMap0, _SolnContext, _DetInfo, CanFail, MaxSolns,
 		[], Detism, []) :-
@@ -887,9 +875,9 @@
 		MaxSolns3, Goals1, Detism, Msgs2),
 	list__append(Msgs1, Msgs2, Msgs).
 
-:- pred det_infer_switch(list(case), instmap, soln_context, det_info,
-	can_fail, soln_count, list(case), determinism, list(det_msg)).
-:- mode det_infer_switch(in, in, in, in, in, in, out, out, out) is det.
+:- pred det_infer_switch(list(case)::in, instmap::in, soln_context::in,
+	det_info::in, can_fail::in, soln_count::in, list(case)::out,
+	determinism::out, list(det_msg)::out) is det.
 
 det_infer_switch([], _InstMap0, _SolnContext, _DetInfo, CanFail, MaxSolns,
 		[], Detism, []) :-
@@ -919,49 +907,47 @@
 	%	determinism is non-cc whereas ProcId0's detism is cc.
 	%	Let ProcId be the first such mode.
 
-:- pred det_find_matching_non_cc_mode(det_info, pred_id, proc_id, proc_id).
-:- mode det_find_matching_non_cc_mode(in, in, in, out) is semidet.
+:- pred det_find_matching_non_cc_mode(det_info::in, pred_id::in, proc_id::in,
+	proc_id::out) is semidet.
 
-det_find_matching_non_cc_mode(DetInfo, PredId, ProcId0, ProcId) :-
+det_find_matching_non_cc_mode(DetInfo, PredId, !ProcId) :-
 	det_info_get_module_info(DetInfo, ModuleInfo),
 	module_info_preds(ModuleInfo, PredTable),
 	map__lookup(PredTable, PredId, PredInfo),
 	pred_info_procedures(PredInfo, ProcTable),
 	map__to_assoc_list(ProcTable, ProcList),
 	det_find_matching_non_cc_mode_2(ProcList, ModuleInfo, PredInfo,
-		ProcId0, ProcId).
+		!ProcId).
 
-:- pred det_find_matching_non_cc_mode_2(assoc_list(proc_id, proc_info),
-		module_info, pred_info, proc_id, proc_id).
-:- mode det_find_matching_non_cc_mode_2(in, in, in, in, out) is semidet.
+:- pred det_find_matching_non_cc_mode_2(assoc_list(proc_id, proc_info)::in,
+	module_info::in, pred_info::in, proc_id::in, proc_id::out) is semidet.
 
-det_find_matching_non_cc_mode_2([ProcId1 - ProcInfo | Rest],
-		ModuleInfo, PredInfo, ProcId0, ProcId) :-
+det_find_matching_non_cc_mode_2([TestProcId - ProcInfo | Rest],
+		ModuleInfo, PredInfo, !ProcId) :-
 	(
-		ProcId1 \= ProcId0,
+		TestProcId \= !.ProcId,
 		proc_info_interface_determinism(ProcInfo, Detism),
 		determinism_components(Detism, _CanFail, MaxSoln),
 		MaxSoln = at_most_many,
-		modes_are_identical_bar_cc(ProcId0, ProcId1, PredInfo,
+		modes_are_identical_bar_cc(!.ProcId, TestProcId, PredInfo,
 			ModuleInfo)
 	->
-		ProcId = ProcId1
+		true
 	;
 		det_find_matching_non_cc_mode_2(Rest, ModuleInfo, PredInfo,
-				ProcId0, ProcId)
+			!ProcId)
 	).
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_check_for_noncanonical_type(prog_var, bool, can_fail, soln_context,
-		hlds_goal_info, cc_unify_context, det_info, list(det_msg),
-		soln_count, list(det_msg)).
-:- mode det_check_for_noncanonical_type(in, in, in, in,
-		in, in, in, in, out, out) is det.
+:- pred det_check_for_noncanonical_type(prog_var::in, bool::in, can_fail::in,
+	soln_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.
 
 det_check_for_noncanonical_type(Var, ExaminesRepresentation, CanFail,
-		SolnContext, GoalInfo, GoalContext, DetInfo, Msgs0,
-		NumSolns, Msgs) :-
+		SolnContext, GoalInfo, GoalContext, DetInfo, NumSolns,
+		!Msgs) :-
 	(
 		%
 		% check for unifications that attempt to examine
@@ -976,14 +962,14 @@
 	->
 		( CanFail = can_fail ->
 			proc_info_varset(ProcInfo, VarSet),
-			Msgs = [cc_unify_can_fail(GoalInfo, Var, Type,
-				VarSet, GoalContext) | Msgs0]
+			!:Msgs = [cc_unify_can_fail(GoalInfo, Var, Type,
+				VarSet, GoalContext) | !.Msgs]
 		; SolnContext \= first_soln ->
 			proc_info_varset(ProcInfo, VarSet),
-			Msgs = [cc_unify_in_wrong_context(GoalInfo, Var,
-				Type, VarSet, GoalContext) | Msgs0]
+			!:Msgs = [cc_unify_in_wrong_context(GoalInfo, Var,
+				Type, VarSet, GoalContext) | !.Msgs]
 		;
-			Msgs = Msgs0
+			true
 		),
 		( SolnContext = first_soln ->
 			NumSolns = at_most_many_cc
@@ -991,8 +977,7 @@
 			NumSolns = at_most_many
 		)
 	;
-		NumSolns = at_most_one,
-		Msgs = Msgs0
+		NumSolns = at_most_one
 	).
 
 % Return true iff the principal type constructor of the given type
@@ -1000,6 +985,7 @@
 
 :- pred det_type_has_user_defined_equality_pred(det_info::in,
 		(type)::in) is semidet.
+
 det_type_has_user_defined_equality_pred(DetInfo, Type) :-
 	det_info_get_module_info(DetInfo, ModuleInfo),
 	type_has_user_defined_equality_pred(ModuleInfo, Type, _).
@@ -1029,8 +1015,7 @@
 	% But switch_detection.m may set it back to cannot_fail again,
 	% if it moves the functor test into a switch instead.
 
-:- pred det_infer_unify_canfail(unification, can_fail).
-:- mode det_infer_unify_canfail(in, out) is det.
+:- pred det_infer_unify_canfail(unification::in, can_fail::out) is det.
 
 det_infer_unify_canfail(deconstruct(_, _, _, _, CanFail, _), CanFail).
 det_infer_unify_canfail(assign(_, _), cannot_fail).
@@ -1098,8 +1083,8 @@
 % det_disjunction_maxsoln is given in the documentation of the test case
 % invalid/magicbox.m.
 
-:- pred det_conjunction_maxsoln(soln_count, soln_count, soln_count).
-:- mode det_conjunction_maxsoln(in, in, out) is det.
+:- pred det_conjunction_maxsoln(soln_count::in, soln_count::in,
+	soln_count::out) is det.
 
 det_conjunction_maxsoln(at_most_zero,    at_most_zero,    at_most_zero).
 det_conjunction_maxsoln(at_most_zero,    at_most_one,     at_most_zero).
@@ -1124,8 +1109,8 @@
 det_conjunction_maxsoln(at_most_many,    at_most_many_cc, at_most_many).
 det_conjunction_maxsoln(at_most_many,    at_most_many,    at_most_many).
 
-:- pred det_conjunction_canfail(can_fail, can_fail, can_fail).
-:- mode det_conjunction_canfail(in, in, out) is det.
+:- pred det_conjunction_canfail(can_fail::in, can_fail::in, can_fail::out)
+	is det.
 
 det_conjunction_canfail(can_fail,    can_fail,    can_fail).
 det_conjunction_canfail(can_fail,    cannot_fail, can_fail).
@@ -1197,9 +1182,8 @@
 	% returns two lists of procedure ids, the first being those
 	% with determinism declarations, and the second being those without.
 
-:- pred determinism_declarations(module_info, pred_proc_list,
-		pred_proc_list, pred_proc_list).
-:- mode determinism_declarations(in, out, out, out) is det.
+:- pred determinism_declarations(module_info::in, pred_proc_list::out,
+	pred_proc_list::out, pred_proc_list::out) is det.
 
 determinism_declarations(ModuleInfo, DeclaredProcs,
 		UndeclaredProcs, NoInferProcs) :-
@@ -1211,17 +1195,15 @@
 	% of all the procedures ids for that module (except class methods,
 	% which do not need to be checked since we generate the code ourselves).
 
-:- pred get_all_pred_procs(module_info, pred_proc_list).
-:- mode get_all_pred_procs(in, out) is det.
+:- pred get_all_pred_procs(module_info::in, pred_proc_list::out) is det.
 
 get_all_pred_procs(ModuleInfo, PredProcs) :-
 	module_info_predids(ModuleInfo, PredIds),
 	module_info_preds(ModuleInfo, Preds),
 	get_all_pred_procs_2(Preds, PredIds, [], PredProcs).
 
-:- pred get_all_pred_procs_2(pred_table, list(pred_id),
-				pred_proc_list, pred_proc_list).
-:- mode get_all_pred_procs_2(in, in, in, out) is det.
+:- pred get_all_pred_procs_2(pred_table::in, list(pred_id)::in,
+	pred_proc_list::in, pred_proc_list::out) is det.
 
 get_all_pred_procs_2(_Preds, [], PredProcs, PredProcs).
 get_all_pred_procs_2(Preds, [PredId|PredIds], PredProcs0, PredProcs) :-
@@ -1230,8 +1212,8 @@
 	fold_pred_modes(PredId, ProcIds, PredProcs0, PredProcs1),
 	get_all_pred_procs_2(Preds, PredIds, PredProcs1, PredProcs).
 
-:- pred fold_pred_modes(pred_id, list(proc_id), pred_proc_list, pred_proc_list).
-:- mode fold_pred_modes(in, in, in, out) is det.
+:- pred fold_pred_modes(pred_id::in, list(proc_id)::in, pred_proc_list::in,
+	pred_proc_list::out) is det.
 
 fold_pred_modes(_PredId, [], PredProcs, PredProcs).
 fold_pred_modes(PredId, [ProcId|ProcIds], PredProcs0, PredProcs) :-
@@ -1242,19 +1224,18 @@
 	% splits the list of procedures PredProcs into DeclaredProcs and
 	% UndeclaredProcs.
 
-:- pred segregate_procs(module_info, pred_proc_list, pred_proc_list,
-	pred_proc_list, pred_proc_list).
-:- mode segregate_procs(in, in, out, out, out) is det.
+:- pred segregate_procs(module_info::in, pred_proc_list::in,
+	pred_proc_list::out, pred_proc_list::out, pred_proc_list::out) is det.
 
 segregate_procs(ModuleInfo, PredProcs, DeclaredProcs,
 		UndeclaredProcs, NoInferProcs) :-
 	segregate_procs_2(ModuleInfo, PredProcs, [], DeclaredProcs,
 			[], UndeclaredProcs, [], NoInferProcs).
 
-:- pred segregate_procs_2(module_info, pred_proc_list, pred_proc_list,
-			pred_proc_list, pred_proc_list, pred_proc_list,
-			pred_proc_list, pred_proc_list).
-:- mode segregate_procs_2(in, in, in, out, in, out, in, out) is det.
+:- pred segregate_procs_2(module_info::in, pred_proc_list::in,
+	pred_proc_list::in, pred_proc_list::out,
+	pred_proc_list::in, pred_proc_list::out,
+	pred_proc_list::in, pred_proc_list::out) is det.
 
 segregate_procs_2(_ModuleInfo, [], !DeclaredProcs,
 		!UndeclaredProcs, !NoInferProcs).
@@ -1297,9 +1278,8 @@
 	% make_hlds.m since inter-module optimization means that the
 	% import_status of procedures isn't determined until after all
 	% items are processed.
-:- pred set_non_inferred_proc_determinism(pred_proc_id,
-		module_info, module_info).
-:- mode set_non_inferred_proc_determinism(in, in, out) is det.
+:- pred set_non_inferred_proc_determinism(pred_proc_id::in,
+	module_info::in, module_info::out) is det.
 
 set_non_inferred_proc_determinism(proc(PredId, ProcId), !ModuleInfo) :-
 	module_info_pred_info(!.ModuleInfo, PredId, PredInfo0),
Index: compiler/det_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/det_report.m,v
retrieving revision 1.84
diff -u -b -r1.84 det_report.m
--- compiler/det_report.m	31 Oct 2003 03:27:22 -0000	1.84
+++ compiler/det_report.m	4 Apr 2004 10:41:45 -0000
@@ -76,8 +76,7 @@
 	% This is the main predicate exported by this module.
 
 :- pred global_checking_pass(pred_proc_list::in,
-	module_info::in, module_info::out,
-	io__state::di, io__state::uo) is det.
+	module_info::in, module_info::out, io::di, io::uo) is det.
 
 	% Check a lambda goal with the specified declared and inferred
 	% determinisms.
@@ -89,15 +88,14 @@
 	% and update the module info accordingly.
 
 :- pred det_report_and_handle_msgs(list(det_msg)::in,
-	module_info::in, module_info::out, io__state::di, io__state::uo)
-	is det.
+	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__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 
 
 :- type msg_modes
@@ -117,18 +115,16 @@
 	% Call this predicate before rerunning determinism analysis
 	% after an optimization pass to disable all warnings. Errors will
 	% still be reported.
-:- pred disable_det_warnings(options_to_restore::out,
-	io__state::di, io__state::uo) is det.
+:- pred disable_det_warnings(options_to_restore::out, io::di, io::uo) is det.
 
-:- pred restore_det_warnings(options_to_restore::in,
-	io__state::di, io__state::uo) is det.
+:- pred restore_det_warnings(options_to_restore::in, io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 
 :- type det_comparison	--->	tighter ; sameas ; looser.
 
-:- pred compare_determinisms(determinism, determinism, det_comparison).
-:- mode compare_determinisms(in, in, out) is det.
+:- pred compare_determinisms(determinism::in, determinism::in,
+	det_comparison::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -138,12 +134,14 @@
 :- import_module check_hlds__mode_util.
 :- import_module check_hlds__type_util.
 :- import_module hlds__hlds_data.
+:- import_module hlds__hlds_error_util.
 :- import_module hlds__hlds_out.
 :- import_module hlds__passes_aux.
 :- import_module hlds__special_pred.
 :- import_module libs__globals.
 :- import_module libs__options.
 :- import_module parse_tree__mercury_to_mercury.
+:- import_module parse_tree__error_util.
 :- import_module parse_tree__prog_out. 
 
 :- import_module assoc_list, bool, int, map, set, std_util, require, string.
@@ -165,10 +163,9 @@
 
 :- pred check_determinism(pred_id::in, proc_id::in, pred_info::in,
 	proc_info::in, module_info::in, module_info::out,
-	io__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 
-check_determinism(PredId, ProcId, PredInfo0, ProcInfo0,
-		!ModuleInfo, !IO) :-
+check_determinism(PredId, ProcId, PredInfo0, ProcInfo0, !ModuleInfo, !IO) :-
 	proc_info_declared_determinism(ProcInfo0, MaybeDetism),
 	proc_info_inferred_determinism(ProcInfo0, InferredDetism),
 	(
@@ -288,8 +285,7 @@
 		module_info_incr_errors(!ModuleInfo)
 	).
 
-:- pred get_valid_dets(eval_method, determinism).
-:- mode get_valid_dets(in, out) is nondet.
+:- pred get_valid_dets(eval_method::in, determinism::out) is nondet.
 
 get_valid_dets(EvalMethod, Detism) :-
 	determinism(Detism),
@@ -309,8 +305,7 @@
 determinism(erroneous).
 determinism(failure).
 
-:- pred print_dets(list(determinism), io__state, io__state).
-:- mode print_dets(in, di, uo) is det.
+:- pred print_dets(list(determinism)::in, io::di, io::uo) is det.
 
 print_dets([]) --> [].
 print_dets([D|Rest]) -->
@@ -321,7 +316,7 @@
 	
 :- pred check_determinism_of_main(pred_id::in, proc_id::in,
 	pred_info::in, proc_info::in, module_info::in, module_info::out,
-	io__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 
 check_determinism_of_main(_PredId, _ProcId, PredInfo, ProcInfo,
 		!ModuleInfo, !IO) :-
@@ -347,13 +342,13 @@
 		true
 	).
 
-:- pred check_for_multisoln_func(pred_id, proc_id, pred_info, proc_info,
-		module_info, module_info, io__state, io__state).
-:- mode check_for_multisoln_func(in, in, in, in, in, out, di, uo) is det.
-
-check_for_multisoln_func(_PredId, _ProcId, PredInfo, ProcInfo,
-		ModuleInfo0, ModuleInfo) -->
-	{ proc_info_inferred_determinism(ProcInfo, InferredDetism) },
+:- pred check_for_multisoln_func(pred_id::in, proc_id::in, pred_info::in,
+	proc_info::in, module_info::in, module_info::out,
+	io::di, io::uo) is det.
+
+check_for_multisoln_func(PredId, _ProcId, PredInfo, ProcInfo,
+		!ModuleInfo, !IO) :-
+	proc_info_inferred_determinism(ProcInfo, InferredDetism),
 
 	% Functions can only have more than one solution if it is a
 	% non-standard mode.  Otherwise, they would not be referentially
@@ -361,55 +356,55 @@
 	% function are not allowed.)
 	(
 		% if it is a mode for a function...
-		{ pred_info_is_pred_or_func(PredInfo) = function },
+		pred_info_is_pred_or_func(PredInfo) = function,
 		% ... that can succeed more than once ...
-		{ determinism_components(InferredDetism, _CanFail, NumSolns) },
-		{ NumSolns \= at_most_zero },
-		{ NumSolns \= at_most_one },
+		determinism_components(InferredDetism, _CanFail, NumSolns),
+		NumSolns \= at_most_zero,
+		NumSolns \= at_most_one,
 		% ... but for which all the arguments are input ...
-		{ proc_info_argmodes(ProcInfo, PredArgModes) },
-		{ pred_args_to_func_args(PredArgModes,
-			FuncArgModes, _FuncResultMode) },
-		{ \+ (
+		proc_info_argmodes(ProcInfo, PredArgModes),
+		pred_args_to_func_args(PredArgModes,
+			FuncArgModes, _FuncResultMode),
+		\+ (
 			list__member(FuncArgMode, FuncArgModes),
-			\+ mode_is_fully_input(ModuleInfo0, FuncArgMode)
+			\+ mode_is_fully_input(!.ModuleInfo, FuncArgMode)
 		  )
-	 	} 
 	->
 		% ... then it is an error.
-		{ PredName = pred_info_name(PredInfo) },
-
-		{ proc_info_context(ProcInfo, FuncContext) },
-		prog_out__write_context(FuncContext),
-		io__write_string("Error: invalid determinism for function\n"),
-		prog_out__write_context(FuncContext),
-		io__write_string("  `"),
-		report_pred_name_mode(function, PredName, PredArgModes),
-		io__write_string("':\n"),
-		prog_out__write_context(FuncContext),
-		io__write_string(
-			"  the primary mode for a function cannot be `"),
-		mercury_output_det(InferredDetism),
-		io__write_string(
-			"'.\n"),
-		globals__io_lookup_bool_option(verbose_errors, VerboseErrors),
-		( { VerboseErrors = yes } ->
-			io__write_strings([
-"\tIn Mercury, a function is supposed to be a true mathematical function\n",
-"\tof its arguments; that is, the value of the function's result should\n",
-"\tbe determined only by the values of its arguments.\n",
-"\t(Allowing functions to have more than one result for the same\n",
-"\targuments would break referential transparency.)\n",
-"\tMost likely, this procedure should be a predicate, not a function.\n"
-			])
+		proc_info_context(ProcInfo, FuncContext),
+		proc_info_inst_varset(ProcInfo, InstVarSet),
+		describe_one_pred_name_mode(!.ModuleInfo, PredId, InstVarSet,
+			PredArgModes, PredModeDesc),
+		Pieces = [words("Error: invalid determinism for"),
+			fixed(PredModeDesc ++ ":"), nl,
+			words("the primary mode of a function cannot be `" ++
+				mercury_det_to_string(InferredDetism) ++
+				"'.")],
+		write_error_pieces(FuncContext, 0, Pieces, !IO),
+		globals__io_lookup_bool_option(verbose_errors, VerboseErrors,
+			!IO),
+		( VerboseErrors = yes ->
+			ExtMsg = func_primary_mode_det_msg,
+			write_error_pieces_not_first_line(FuncContext, 0,
+				[words(ExtMsg)], !IO)
 		;
-			[]
+			true
 		),
-		{ module_info_incr_errors(ModuleInfo0, ModuleInfo) }
+		module_info_incr_errors(!ModuleInfo)
 	;
-		{ ModuleInfo = ModuleInfo0 }
+		true
 	).
 
+:- func func_primary_mode_det_msg = string.
+
+func_primary_mode_det_msg =
+	"In Mercury, a function is supposed to be a true mathematical" ++
+	"function of its arguments; that is, the value of the function's" ++
+	"result should be determined only by the values of its arguments." ++
+	"(Allowing functions to have more than one result for the same" ++
+	"arguments would break referential transparency.)" ++
+	"Most likely, this procedure should be a predicate, not a function.".
+
 det_check_lambda(DeclaredDetism, InferredDetism, Goal, GoalInfo, DetInfo,
 		Msgs) :-
 	compare_determinisms(DeclaredDetism, InferredDetism, Cmp),
@@ -425,9 +420,8 @@
 		Msgs = []
 	).
 
-:- pred report_determinism_problem(pred_id, proc_id, module_info, string,
-	determinism, determinism, io__state, io__state).
-:- mode report_determinism_problem(in, in, in, in, in, in, di, uo) is det.
+:- pred report_determinism_problem(pred_id::in, proc_id::in, module_info::in,
+	string::in, determinism::in, determinism::in, io::di, io::uo) is det.
 
 report_determinism_problem(PredId, ModeId, ModuleInfo, Message,
 		DeclaredDetism, InferredDetism) -->
@@ -468,16 +462,16 @@
 		CmpDetism = sameas
 	).
 
-:- pred compare_canfails(can_fail, can_fail, det_comparison).
-:- mode compare_canfails(in, in, out) is det.
+:- pred compare_canfails(can_fail::in, can_fail::in, det_comparison::out)
+	is det.
 
 compare_canfails(cannot_fail, cannot_fail, sameas).
 compare_canfails(cannot_fail, can_fail,    tighter).
 compare_canfails(can_fail,    cannot_fail, looser).
 compare_canfails(can_fail,    can_fail,    sameas).
 
-:- pred compare_solncounts(soln_count, soln_count, det_comparison).
-:- mode compare_solncounts(in, in, out) is det.
+:- pred compare_solncounts(soln_count::in, soln_count::in, det_comparison::out)
+	is det.
 
 compare_solncounts(at_most_zero,    at_most_zero,    sameas).
 compare_solncounts(at_most_zero,    at_most_one,     tighter).
@@ -504,51 +498,50 @@
 	% The given goal should have determinism Desired, but doesn't.
 	% Find out what is wrong and print a report of the cause.
 
-:- pred det_diagnose_goal(hlds_goal, determinism, list(switch_context),
-	det_info, bool, io__state, io__state).
-:- mode det_diagnose_goal(in, in, in, in, out, di, uo) is det.
+:- pred det_diagnose_goal(hlds_goal::in, determinism::in,
+	list(switch_context)::in, det_info::in, bool::out, io::di, io::uo)
+	is det.
 
 det_diagnose_goal(Goal - GoalInfo, Desired, SwitchContext, DetInfo,
-		Diagnosed) -->
-	{ goal_info_get_determinism(GoalInfo, Actual) },
-	( { compare_determinisms(Desired, Actual, tighter) } ->
+		Diagnosed, !IO) :-
+	goal_info_get_determinism(GoalInfo, Actual),
+	( compare_determinisms(Desired, Actual, tighter) ->
 		det_diagnose_goal_2(Goal, GoalInfo, Desired, Actual,
-			SwitchContext, DetInfo, Diagnosed)
+			SwitchContext, DetInfo, Diagnosed, !IO)
 	;
-		{ Diagnosed = no }
+		Diagnosed = no
 	).
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_diagnose_goal_2(hlds_goal_expr, hlds_goal_info,
-	determinism, determinism, list(switch_context), det_info, bool,
-	io__state, io__state).
-:- mode det_diagnose_goal_2(in, in, in, in, in, in, out, di, uo) is det.
+:- pred det_diagnose_goal_2(hlds_goal_expr::in, hlds_goal_info::in,
+	determinism::in, determinism::in, list(switch_context)::in,
+	det_info::in, bool::out, io::di, io::uo) is det.
 
 det_diagnose_goal_2(conj(Goals), _GoalInfo, Desired, _Actual, Context, DetInfo,
-		Diagnosed) -->
-	det_diagnose_conj(Goals, Desired, Context, DetInfo, Diagnosed).
+		Diagnosed, !IO) :-
+	det_diagnose_conj(Goals, Desired, Context, DetInfo, Diagnosed, !IO).
 
 det_diagnose_goal_2(par_conj(Goals), _GoalInfo, Desired, _Actual,
-		Context, DetInfo, Diagnosed) -->
-	det_diagnose_conj(Goals, Desired, Context, DetInfo, Diagnosed).
+		Context, DetInfo, Diagnosed, !IO) :-
+	det_diagnose_conj(Goals, Desired, Context, DetInfo, Diagnosed, !IO).
 
 det_diagnose_goal_2(disj(Goals), GoalInfo, Desired, Actual, SwitchContext,
-		DetInfo, Diagnosed) -->
+		DetInfo, Diagnosed, !IO) :-
 	det_diagnose_disj(Goals, Desired, Actual, SwitchContext, DetInfo, 0,
-		ClausesWithSoln, Diagnosed1),
-	{ determinism_components(Desired, _, DesSolns) },
+		ClausesWithSoln, Diagnosed1, !IO),
+	determinism_components(Desired, _, DesSolns),
 	(
-		{ DesSolns \= at_most_many },
-		{ DesSolns \= at_most_many_cc },
-		{ ClausesWithSoln > 1 }
+		DesSolns \= at_most_many,
+		DesSolns \= at_most_many_cc,
+		ClausesWithSoln > 1
 	->
-		{ goal_info_get_context(GoalInfo, Context) },
-		prog_out__write_context(Context),
-		io__write_string("  Disjunction has multiple clauses with solutions.\n"),
-		{ Diagnosed = yes }
+		goal_info_get_context(GoalInfo, Context),
+		Msg = "Disjunction has multiple clauses with solutions.",
+		write_error_pieces(Context, 2, [words(Msg)], !IO),
+		Diagnosed = yes
 	;
-		{ Diagnosed = Diagnosed1 }
+		Diagnosed = Diagnosed1
 	).
 
 	% The determinism of a switch is the worst of the determinism of each of
@@ -557,150 +550,144 @@
 	% in switch_detection.m and handled via the CanFail field.
 
 det_diagnose_goal_2(switch(Var, SwitchCanFail, Cases), GoalInfo,
-		Desired, _Actual, SwitchContext, DetInfo, Diagnosed) -->
+		Desired, _Actual, SwitchContext, DetInfo, Diagnosed, !IO) :-
 	(
-		{ SwitchCanFail = can_fail },
-		{ determinism_components(Desired, cannot_fail, _) }
+		SwitchCanFail = can_fail,
+		determinism_components(Desired, cannot_fail, _)
 	->
-		{ goal_info_get_context(GoalInfo, Context) },
+		goal_info_get_context(GoalInfo, Context),
 		det_diagnose_write_switch_context(Context, SwitchContext,
-			DetInfo),
-		prog_out__write_context(Context),
-		{ det_get_proc_info(DetInfo, ProcInfo) },
-		{ proc_info_varset(ProcInfo, Varset) },
-		{ det_info_get_module_info(DetInfo, ModuleInfo) },
-		(
-			{ det_lookup_var_type(ModuleInfo, ProcInfo, Var,
-				TypeDefn) },
-			{ hlds_data__get_type_defn_body(TypeDefn, TypeBody) },
-			{ ConsTable = TypeBody ^ du_type_cons_tag_values }
+			DetInfo, yes, IsFirst, !IO),
+		det_get_proc_info(DetInfo, ProcInfo),
+		proc_info_varset(ProcInfo, VarSet),
+		det_info_get_module_info(DetInfo, ModuleInfo),
+		VarStr = mercury_var_to_string(Var, VarSet, no),
+		(
+			det_lookup_var_type(ModuleInfo, ProcInfo, Var,
+				TypeDefn),
+			hlds_data__get_type_defn_body(TypeDefn, TypeBody),
+			ConsTable = TypeBody ^ du_type_cons_tag_values
 		->
-			{ map__keys(ConsTable, ConsIds) },
-			{ det_diagnose_missing_consids(ConsIds, Cases,
-				Missing) },
-			io__write_string("  The switch on "),
-			mercury_output_var(Var, Varset, no),
-			io__write_string(" does not cover "),
-			det_output_consid_list(Missing, yes),
-			io__write_string(".\n")
-		;
-			io__write_string("  The switch on "),
-			mercury_output_var(Var, Varset, no),
-			io__write_string(" can fail.\n")
-		),
-		{ Diagnosed1 = yes }
+			map__keys(ConsTable, ConsIds),
+			det_diagnose_missing_consids(ConsIds, Cases, Missing),
+			cons_id_list_to_pieces(Missing, yes, MissingPieces),
+			list__append(MissingPieces, [words(".")],
+				PiecesTail),
+			Pieces = [words("The switch on "), fixed(VarStr),
+				words("does not cover") | PiecesTail]
+		;
+			Pieces = [words("The switch on "), fixed(VarStr),
+				words("can fail.")]
+		),
+		write_error_pieces_maybe_first_line(IsFirst, Context, 0,
+			Pieces, !IO),
+		Diagnosed1 = yes
 	;
-		{ Diagnosed1 = no }
+		Diagnosed1 = no
 	),
 	det_diagnose_switch(Var, Cases, Desired, SwitchContext, DetInfo,
-		Diagnosed2),
-	{ bool__or(Diagnosed1, Diagnosed2, Diagnosed) }.
+		Diagnosed2, !IO),
+	bool__or(Diagnosed1, Diagnosed2, Diagnosed).
 
 det_diagnose_goal_2(call(PredId, ModeId, _, _, CallContext, _), GoalInfo,
-		Desired, Actual, _, DetInfo, yes) -->
-	{ goal_info_get_context(GoalInfo, Context) },
+		Desired, Actual, _, DetInfo, yes, !IO) :-
+	goal_info_get_context(GoalInfo, Context),
 	det_diagnose_atomic_goal(Desired, Actual,
 		det_report_call_context(Context, CallContext, DetInfo,
 			PredId, ModeId),
-		Context).
+		Context, !IO).
 
 det_diagnose_goal_2(generic_call(GenericCall, _, _, _), GoalInfo,
-		Desired, Actual, _, _DetInfo, yes) -->
-	{ goal_info_get_context(GoalInfo, Context) },
+		Desired, Actual, _, _DetInfo, yes, !IO) :-
+	goal_info_get_context(GoalInfo, Context),
 	det_diagnose_atomic_goal(Desired, Actual,
 		report_generic_call_context(Context, GenericCall),
-		Context).
+		Context, !IO).
 
-det_diagnose_goal_2(unify(LT, RT, _, _, UnifyContext), GoalInfo,
-		Desired, Actual, _, DetInfo, yes) -->
-	{ goal_info_get_context(GoalInfo, Context) },
-	{ First = yes, Last = yes },
+det_diagnose_goal_2(unify(LHS, RHS, _, _, UnifyContext), GoalInfo,
+		Desired, Actual, _, DetInfo, yes, !IO) :-
+	goal_info_get_context(GoalInfo, Context),
+	( First = yes, Last = yes ),
 	det_diagnose_atomic_goal(Desired, Actual,
 		det_report_unify_context(First, Last, Context, UnifyContext,
-			DetInfo, LT, RT), Context).
+			DetInfo, LHS, RHS), Context, !IO).
 
 det_diagnose_goal_2(if_then_else(_Vars, Cond, Then, Else), _GoalInfo,
-		Desired, _Actual, SwitchContext, DetInfo, Diagnosed) -->
-	{
+		Desired, _Actual, SwitchContext, DetInfo, Diagnosed, !IO) :-
 		determinism_components(Desired, _DesiredCanFail, DesiredSolns),
 		Cond = _CondGoal - CondInfo,
 		goal_info_get_determinism(CondInfo, CondDetism),
-		determinism_components(CondDetism, _CondCanFail, CondSolns)
-	},
+	determinism_components(CondDetism, _CondCanFail, CondSolns),
 	(
-		{ CondSolns = at_most_many },
-		{ DesiredSolns \= at_most_many }
+		CondSolns = at_most_many,
+		DesiredSolns \= at_most_many
 	->
-		{ determinism_components(DesiredCond, can_fail, DesiredSolns) },
+		determinism_components(DesiredCond, can_fail, DesiredSolns),
 		det_diagnose_goal(Cond, DesiredCond, SwitchContext, DetInfo,
-			Diagnosed1)
+			Diagnosed1, !IO)
 	;
-		{ Diagnosed1 = no }
+		Diagnosed1 = no
 	),
-	det_diagnose_goal(Then, Desired, SwitchContext, DetInfo, Diagnosed2),
-	det_diagnose_goal(Else, Desired, SwitchContext, DetInfo, Diagnosed3),
-	{ bool__or(Diagnosed2, Diagnosed3, Diagnosed23) },
-	{ bool__or(Diagnosed1, Diagnosed23, Diagnosed) }.
+	det_diagnose_goal(Then, Desired, SwitchContext, DetInfo, Diagnosed2,
+		!IO),
+	det_diagnose_goal(Else, Desired, SwitchContext, DetInfo, Diagnosed3,
+		!IO),
+	bool__or(Diagnosed2, Diagnosed3, Diagnosed23),
+	bool__or(Diagnosed1, Diagnosed23, Diagnosed).
 
-det_diagnose_goal_2(not(_), GoalInfo, Desired, Actual, _, _, Diagnosed) -->
-	{ determinism_components(Desired, DesiredCanFail, DesiredSolns) },
-	{ determinism_components(Actual, ActualCanFail, ActualSolns) },
+det_diagnose_goal_2(not(_), GoalInfo, Desired, Actual, _, _, Diagnosed, !IO) :-
+	determinism_components(Desired, DesiredCanFail, DesiredSolns),
+	determinism_components(Actual, ActualCanFail, ActualSolns),
 	(
-		{ DesiredCanFail = cannot_fail },
-		{ ActualCanFail = can_fail }
+		DesiredCanFail = cannot_fail,
+		ActualCanFail = can_fail
 	->
-		{ goal_info_get_context(GoalInfo, Context) },
-		prog_out__write_context(Context),
-		io__write_string("  Negated goal can succeed.\n"),
-		{ Diagnosed = yes }
+		goal_info_get_context(GoalInfo, Context),
+		write_error_pieces(Context, 0,
+			[words("Negated goal can succeed.")], !IO),
+		Diagnosed = yes
 	;
-		{ DesiredSolns = at_most_zero },
-		{ ActualSolns \= at_most_zero }
+		DesiredSolns = at_most_zero,
+		ActualSolns \= at_most_zero
 	->
-		{ goal_info_get_context(GoalInfo, Context) },
-		prog_out__write_context(Context),
-		io__write_string("  Negated goal can fail.\n"),
-		{ Diagnosed = yes }
+		goal_info_get_context(GoalInfo, Context),
+		write_error_pieces(Context, 0,
+			[words("Negated goal can fail.")], !IO),
+		Diagnosed = yes
 	;
-		{ Diagnosed = no }
+		Diagnosed = no
 	).
 
 det_diagnose_goal_2(some(_Vars, _, Goal), _, Desired, Actual,
-		SwitchContext, DetInfo, Diagnosed) -->
-	{ Goal = _ - GoalInfo },
-	{ goal_info_get_determinism(GoalInfo, Internal) },
-	{ Actual = Internal ->
+		SwitchContext, DetInfo, Diagnosed, !IO) :-
+	Goal = _ - GoalInfo,
+	goal_info_get_determinism(GoalInfo, Internal),
+	( Actual = Internal ->
 		InternalDesired = Desired
 	;
 		determinism_components(Desired, CanFail, _),
 		determinism_components(InternalDesired, CanFail, at_most_many)
-	},
+	),
 	det_diagnose_goal(Goal, InternalDesired, SwitchContext, DetInfo,
-		Diagnosed).
+		Diagnosed, !IO).
 
 det_diagnose_goal_2(foreign_proc(_, _, _, _, _, _, _), GoalInfo,
-		Desired, _, _, _, yes) -->
-	{ goal_info_get_context(GoalInfo, Context) },
-	prog_out__write_context(Context),
-	io__write_string("  Determinism declaration not satisfied. Desired \n"),
-	prog_out__write_context(Context),
-	io__write_string("  determinism is "),
-	hlds_out__write_determinism(Desired),
-	io__write_string(".\n").
-	% The "clarification" below is now incorrect.
-	% prog_out__write_context(Context),
-	% io__write_string("  pragma c_code declarations only allowed\n"),
-	% prog_out__write_context(Context),
-	% io__write_string("  for modes which don't succeed more than once.\n").
+		Desired, _, _, _, yes, !IO) :-
+	goal_info_get_context(GoalInfo, Context),
+	DesiredStr = determinism_to_string(Desired),
+	Pieces = [words("Determinism declaration not satisfied."),
+		words("Desired determinism is " ++ DesiredStr ++ ".")],
+	write_error_pieces(Context, 0, Pieces, !IO).
 
-det_diagnose_goal_2(shorthand(_), _, _, _, _, _, _) -->
+det_diagnose_goal_2(shorthand(_), _, _, _, _, _, _, !IO) :-
 	% these should have been expanded out by now
-	{ error("det_diagnose_goal_2: unexpected shorthand") }.
+	error("det_diagnose_goal_2: unexpected shorthand").
 
 %-----------------------------------------------------------------------------%
 
 :- pred report_generic_call_context(prog_context::in,
-		generic_call::in, io__state::di, io__state::uo) is det.
+	generic_call::in, io::di, io::uo) is det.
+
 report_generic_call_context(Context, CallType) -->
 	prog_out__write_context(Context),
 	io__write_string("  "),
@@ -709,11 +696,9 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_diagnose_atomic_goal(determinism, determinism, 
-		pred(io__state, io__state), prog_context,
-		io__state, io__state).
-:- mode det_diagnose_atomic_goal(in, in, pred(di, uo) is det, in,
-		di, uo) is det.
+:- pred det_diagnose_atomic_goal(determinism::in, determinism::in,
+	pred(io, io)::in(pred(di, uo) is det), prog_context::in,
+	io::di, io::uo) is det.
 
 det_diagnose_atomic_goal(Desired, Actual, WriteContext, Context) -->
 	{ determinism_components(Desired, DesiredCanFail, DesiredSolns) },
@@ -757,9 +742,9 @@
 	% det_diagnose_conj is used for both normal [sequential]
 	% conjunction and parallel conjunction.
 
-:- pred det_diagnose_conj(list(hlds_goal), determinism,
-	list(switch_context), det_info, bool, io__state, io__state).
-:- mode det_diagnose_conj(in, in, in, in, out, di, uo) is det.
+:- pred det_diagnose_conj(list(hlds_goal)::in, determinism::in,
+	list(switch_context)::in, det_info::in, bool::out, io::di, io::uo)
+	is det.
 
 det_diagnose_conj([], _Desired, _SwitchContext, _DetInfo, no) --> [].
 det_diagnose_conj([Goal | Goals], Desired, SwitchContext, DetInfo,
@@ -768,17 +753,17 @@
 	det_diagnose_conj(Goals, Desired, SwitchContext, DetInfo, Diagnosed2),
 	{ bool__or(Diagnosed1, Diagnosed2, Diagnosed) }.
 
-:- pred det_diagnose_disj(list(hlds_goal), determinism, determinism,
-	list(switch_context), det_info, int, int, bool, io__state, io__state).
-:- mode det_diagnose_disj(in, in, in, in, in, in, out, out, di, uo) is det.
+:- pred det_diagnose_disj(list(hlds_goal)::in, determinism::in, determinism::in,
+	list(switch_context)::in, det_info::in, int::in, int::out, bool::out,
+	io::di, io::uo) is det.
 
 det_diagnose_disj([], _Desired, _Actual, _SwitchContext, _DetInfo,
-		ClausesWithSoln, ClausesWithSoln, no) --> [].
+		!ClausesWithSoln, no, !IO).
 det_diagnose_disj([Goal | Goals], Desired, Actual, SwitchContext, DetInfo,
-		ClausesWithSoln0, ClausesWithSoln, Diagnosed) -->
-	{ determinism_components(Actual, ActualCanFail, _) },
-	{ determinism_components(Desired, DesiredCanFail, DesiredSolns) },
-	{ DesiredCanFail = cannot_fail, ActualCanFail = can_fail ->
+		!ClausesWithSoln, Diagnosed, !IO) :-
+	determinism_components(Actual, ActualCanFail, _),
+	determinism_components(Desired, DesiredCanFail, DesiredSolns),
+	( DesiredCanFail = cannot_fail, ActualCanFail = can_fail ->
 		% if the disjunction was declared to never fail,
 		% but we inferred that it might fail, then we
 		% want to print an error message for every disjunct
@@ -790,40 +775,41 @@
 		% inferred won't fail, so we don't want any error
 		% messages for the disjuncts that might fail
 		ClauseCanFail = can_fail
-	},
-	{ determinism_components(ClauseDesired, ClauseCanFail, DesiredSolns) },
+	),
+	determinism_components(ClauseDesired, ClauseCanFail, DesiredSolns),
 	det_diagnose_goal(Goal, ClauseDesired, SwitchContext, DetInfo,
-		Diagnosed1),
+		Diagnosed1, !IO),
 	(
-		{ Goal = _ - GoalInfo },
-		{ goal_info_get_determinism(GoalInfo, GoalDetism) },
-		{ determinism_components(GoalDetism, _, at_most_zero) }
+		Goal = _ - GoalInfo,
+		goal_info_get_determinism(GoalInfo, GoalDetism),
+		determinism_components(GoalDetism, _, at_most_zero)
 	->
-		{ ClausesWithSoln1 = ClausesWithSoln0 }
+		true
 	;
-		{ ClausesWithSoln1 = ClausesWithSoln0 + 1 }
+		!:ClausesWithSoln = !.ClausesWithSoln + 1
 	),
 	det_diagnose_disj(Goals, Desired, Actual, SwitchContext, DetInfo,
-		ClausesWithSoln1, ClausesWithSoln, Diagnosed2),
-	{ bool__or(Diagnosed1, Diagnosed2, Diagnosed) }.
+		!ClausesWithSoln, Diagnosed2, !IO),
+	bool__or(Diagnosed1, Diagnosed2, Diagnosed).
 
-:- pred det_diagnose_switch(prog_var, list(case), determinism,
-	list(switch_context), det_info, bool, io__state, io__state).
-:- mode det_diagnose_switch(in, in, in, in, in, out, di, uo) is det.
+:- pred det_diagnose_switch(prog_var::in, list(case)::in, determinism::in,
+	list(switch_context)::in, det_info::in, bool::out,
+	io::di, io::uo) is det.
 
-det_diagnose_switch(_Var, [], _Desired, _SwitchContext, _DetInfo, no) --> [].
+det_diagnose_switch(_Var, [], _Desired, _SwitchContext, _DetInfo, no, !IO).
 det_diagnose_switch(Var, [case(ConsId, Goal) | Cases], Desired,
-		SwitchContext0, DetInfo, Diagnosed) -->
-	{ SwitchContext1 = [switch_context(Var, ConsId) | SwitchContext0] },
-	det_diagnose_goal(Goal, Desired, SwitchContext1, DetInfo, Diagnosed1),
+		SwitchContext0, DetInfo, Diagnosed, !IO) :-
+	SwitchContext1 = [switch_context(Var, ConsId) | SwitchContext0],
+	det_diagnose_goal(Goal, Desired, SwitchContext1, DetInfo, Diagnosed1,
+		!IO),
 	det_diagnose_switch(Var, Cases, Desired, SwitchContext0, DetInfo,
-		Diagnosed2),
-	{ bool__or(Diagnosed1, Diagnosed2, Diagnosed) }.
+		Diagnosed2, !IO),
+	bool__or(Diagnosed1, Diagnosed2, Diagnosed).
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_diagnose_missing_consids(list(cons_id), list(case), list(cons_id)).
-:- mode det_diagnose_missing_consids(in, in, out) is det.
+:- pred det_diagnose_missing_consids(list(cons_id)::in, list(case)::in,
+	list(cons_id)::out) is det.
 
 det_diagnose_missing_consids([], _, []).
 det_diagnose_missing_consids([ConsId | ConsIds], Cases, Missing) :-
@@ -837,55 +823,59 @@
 		Missing = [ConsId | Missing0]
 	).
 
-:- pred det_output_consid_list(list(cons_id), bool, io__state, io__state).
-:- mode det_output_consid_list(in, in, di, uo) is det.
+:- pred cons_id_list_to_pieces(list(cons_id)::in, bool::in,
+	list(format_component)::out) is det.
 
-det_output_consid_list([], _) --> [].
-det_output_consid_list([ConsId | ConsIds], First) -->
-	( { First = yes } ->
-		[]
-	; { ConsIds = [] } ->
-		io__write_string(" and/or ")
+cons_id_list_to_pieces([], _, []).
+cons_id_list_to_pieces([ConsId | ConsIds], First, Pieces) :-
+	ConsIdStr = cons_id_to_string(ConsId),
+	( First = yes ->
+		PiecesHead = [words(ConsIdStr)]
+	; ConsIds = [] ->
+		PiecesHead = [words(ConsIdStr), words(" and/or ")]
 	;
-		io__write_string(", ")
+		PiecesHead = [words(ConsIdStr ++ ",")]
 	),
-	hlds_out__write_cons_id(ConsId),
-	det_output_consid_list(ConsIds, no).
+	cons_id_list_to_pieces(ConsIds, no, PiecesTail),
+	list__append(PiecesHead, PiecesTail, Pieces).
 
 %-----------------------------------------------------------------------------%
 
 :- type switch_context --->	switch_context(prog_var, cons_id).
 
-:- pred det_diagnose_write_switch_context(prog_context, list(switch_context),
-	det_info, io__state, io__state).
-:- mode det_diagnose_write_switch_context(in, in, in, di, uo) is det.
+:- pred det_diagnose_write_switch_context(prog_context::in,
+	list(switch_context)::in, det_info::in, bool::in, bool::out,
+	io::di, io::uo) is det.
 
-det_diagnose_write_switch_context(_Context, [], _MiscInco) --> [].
+det_diagnose_write_switch_context(_Context, [], _, !IsFirst, !IO).
 det_diagnose_write_switch_context(Context, [SwitchContext | SwitchContexts],
-		DetInfo) -->
-	prog_out__write_context(Context),
-	{ det_get_proc_info(DetInfo, ProcInfo) },
-	{ proc_info_varset(ProcInfo, Varset) },
-	{ SwitchContext = switch_context(Var, ConsId) },
-	io__write_string("  Inside the case "),
-	hlds_out__write_cons_id(ConsId),
-	io__write_string(" of the switch on "),
-	mercury_output_var(Var, Varset, no),
-	io__write_string(":\n"),
-	det_diagnose_write_switch_context(Context, SwitchContexts, DetInfo).
+		DetInfo, !IsFirst, !IO) :-
+	det_get_proc_info(DetInfo, ProcInfo),
+	proc_info_varset(ProcInfo, VarSet),
+	SwitchContext = switch_context(Var, ConsId),
+	ConsIdStr = cons_id_to_string(ConsId),
+	VarStr = mercury_var_to_string(Var, VarSet, no),
+	Pieces = [words("Inside the case"), fixed(ConsIdStr),
+		words("of the switch on"), fixed(VarStr), words(":")],
+	write_error_pieces_maybe_first_line(!.IsFirst, Context, 0, Pieces,
+		!IO),
+	!:IsFirst = no,
+	det_diagnose_write_switch_context(Context, SwitchContexts, DetInfo,
+		!IsFirst, !IO).
 
 %-----------------------------------------------------------------------------%
 
-:- pred det_report_call_context(prog_context, maybe(call_unify_context),
-	det_info, pred_id, proc_id, io__state, io__state).
-:- mode det_report_call_context(in, in, in, in, in, di, uo) is det.
-
-det_report_call_context(Context, CallUnifyContext, DetInfo, PredId, ModeId) -->
-	{ det_info_get_module_info(DetInfo, ModuleInfo) },
-	{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
-	{ PredName = pred_info_name(PredInfo) },
-	{ PredOrFunc = pred_info_is_pred_or_func(PredInfo) },
-	{ pred_info_get_maybe_special_pred(PredInfo, MaybeSpecial) },
+:- pred det_report_call_context(prog_context::in,
+	maybe(call_unify_context)::in, det_info::in, pred_id::in, proc_id::in,
+	io::di, io::uo) is det.
+
+det_report_call_context(Context, CallUnifyContext, DetInfo, PredId, ProcId,
+		!IO) :-
+	det_info_get_module_info(DetInfo, ModuleInfo),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	PredName = pred_info_name(PredInfo),
+	PredOrFunc = pred_info_is_pred_or_func(PredInfo),
+	pred_info_get_maybe_special_pred(PredInfo, MaybeSpecial),
 	%
 	% if the error was in a call to a type-specific unification predicate
 	% (i.e. in the unification itself), then don't print out the predicate
@@ -893,40 +883,42 @@
 	% both out. (The latter can happen if there is a determinism error
 	% in a function call inside some unification.)
 	%
-	( { MaybeSpecial = yes(unify - _) } ->
+	( MaybeSpecial = yes(unify - _) ->
 		(
-			{ CallUnifyContext = yes(
-					call_unify_context(LT, RT, UC)) },
-			{ First = yes, Last = yes },
-			det_report_unify_context(First, Last,
-				Context, UC, DetInfo, LT, RT)
+			CallUnifyContext = yes(
+				call_unify_context(LHS, RHS, UC)),
+			First = yes, Last = yes,
+			det_report_unify_context(First, Last, Context, UC,
+				DetInfo, LHS, RHS, !IO)
 		;
 			% this shouldn't happen; every call to a compiler
 			% generated type-specific unification predicate
 			% should have a unify_context
-			{ CallUnifyContext = no },
-			prog_out__write_context(Context),
-			io__write_string(
-	"  Some weird unification (or explicit call to a type-specific unify predicate?)")
+			CallUnifyContext = no,
+			prog_out__write_context(Context, !IO),
+			io__write_string("  Some weird unification " ++
+				"(or explicit call to a type-specific " ++
+				"unify predicate?)", !IO)
 		)
 	;
 		(
-			{ CallUnifyContext = yes(
-					call_unify_context(LT, RT, UC)) },
-			{ First = yes, Last = no },
-			det_report_unify_context(First, Last,
-				Context, UC, DetInfo, LT, RT),
-			io__write_string(":\n")
-		;
-			{ CallUnifyContext = no }
-		),
-		{ pred_info_procedures(PredInfo, ProcTable) },
-		{ map__lookup(ProcTable, ModeId, ProcInfo) },
-		{ proc_info_declared_argmodes(ProcInfo, ArgModes) },
-		prog_out__write_context(Context),
-		io__write_string("  call to `"),
-		report_pred_name_mode(PredOrFunc, PredName, ArgModes),
-		io__write_string("'")
+			CallUnifyContext = yes(
+				call_unify_context(LHS, RHS, UC)),
+			First = yes,
+			Last = no,
+			det_report_unify_context(First, Last, Context, UC,
+				DetInfo, LHS, RHS, !IO),
+			io__write_string(":\n", !IO)
+		;
+			CallUnifyContext = no
+		),
+		pred_info_procedures(PredInfo, ProcTable),
+		map__lookup(ProcTable, ProcId, ProcInfo),
+		proc_info_declared_argmodes(ProcInfo, ArgModes),
+		prog_out__write_context(Context, !IO),
+		io__write_string("  call to `", !IO),
+		report_pred_name_mode(PredOrFunc, PredName, ArgModes, !IO),
+		io__write_string("'", !IO)
 	).
 
 %-----------------------------------------------------------------------------%
@@ -938,125 +930,119 @@
 % with a capital letter) and whether it is the last part (in which case we
 % omit the word "in" on the final "... in unification ...").
 
-:- pred det_report_unify_context(bool, bool, prog_context, unify_context,
-	det_info, prog_var, unify_rhs, io__state, io__state).
-:- mode det_report_unify_context(in, in, in, in, in, in, in, di, uo) is det.
-
-det_report_unify_context(First0, Last, Context, UnifyContext, DetInfo, LT, RT)
-		-->
-	hlds_out__write_unify_context(First0, UnifyContext, Context, First),
-	prog_out__write_context(Context),
-	{ det_get_proc_info(DetInfo, ProcInfo) },
-	{ proc_info_varset(ProcInfo, Varset) },
-	{ det_info_get_module_info(DetInfo, ModuleInfo) },
+:- pred det_report_unify_context(bool::in, bool::in, prog_context::in,
+	unify_context::in, det_info::in, prog_var::in, unify_rhs::in,
+	io::di, io::uo) is det.
+
+det_report_unify_context(First0, Last, Context, UnifyContext, DetInfo,
+		LHS, RHS, !IO) :-
+	hlds_out__write_unify_context(First0, UnifyContext, Context, First,
+		!IO),
+	prog_out__write_context(Context, !IO),
+	det_get_proc_info(DetInfo, ProcInfo),
+	proc_info_varset(ProcInfo, VarSet),
+	det_info_get_module_info(DetInfo, ModuleInfo),
 		% We don't have the inst varset - it's not in the
 		% proc_info, so we'll just make one up....
-	{ varset__init(InstVarSet) },
-	( { First = yes } ->
-		( { Last = yes } ->
-			io__write_string("  Unification ")
+	varset__init(InstVarSet),
+	( First = yes ->
+		( Last = yes ->
+			io__write_string("  Unification ", !IO)
 		;
-			io__write_string("  In unification ")
+			io__write_string("  In unification ", !IO)
 		)
 	;
-		( { Last = yes } ->
-			io__write_string("  unification ")
+		( Last = yes ->
+			io__write_string("  unification ", !IO)
 		;
-			io__write_string("  in unification ")
+			io__write_string("  in unification ", !IO)
 		)
 	),
+	( varset__search_name(VarSet, LHS, _) ->
 	(
-		{ varset__search_name(Varset, LT, _) }
-	->
-		(
-			{ RT = var(RV) },
-			\+ { varset__search_name(Varset, RV, _) }
+			RHS = var(RV),
+			\+ varset__search_name(VarSet, RV, _)
 		->
-			io__write_string("with `"),
-			mercury_output_var(LT, Varset, no)
-		;
-			io__write_string("of `"),
-			mercury_output_var(LT, Varset, no),
-			io__write_string("' and `"),
-			hlds_out__write_unify_rhs(RT, ModuleInfo, Varset,
-				InstVarSet, no, 3)
+			io__write_string("with `", !IO),
+			mercury_output_var(LHS, VarSet, no, !IO),
+			io__write_string("'", !IO)
+		;
+			io__write_string("of `", !IO),
+			mercury_output_var(LHS, VarSet, no, !IO),
+			io__write_string("' and `", !IO),
+			hlds_out__write_unify_rhs(RHS, ModuleInfo, VarSet,
+				InstVarSet, no, 3, !IO),
+			io__write_string("'", !IO)
 		)
 	;
-		io__write_string("with `"),
-		hlds_out__write_unify_rhs(RT, ModuleInfo, Varset, InstVarSet,
-			no, 3)
-	),
-	io__write_string("'").
-
+		io__write_string("with `", !IO),
+		hlds_out__write_unify_rhs(RHS, ModuleInfo, VarSet, InstVarSet,
+			no, 3, !IO),
+		io__write_string("'", !IO)
+	).
 
 %-----------------------------------------------------------------------------%
 
 :- type det_msg_type	--->	simple_code_warning ; call_warning ; error.
 
-det_report_and_handle_msgs(Msgs, ModuleInfo0, ModuleInfo) -->
-	( { Msgs = [] } ->
+det_report_and_handle_msgs(Msgs, !ModuleInfo, !IO) :-
+	( Msgs = [] ->
 		% fast path for the usual case
-		{ ModuleInfo = ModuleInfo0 }
+		true
 	;
-		det_report_msgs(Msgs, ModuleInfo0, WarnCnt, ErrCnt),
-		globals__io_lookup_bool_option(halt_at_warn, HaltAtWarn),
+		det_report_msgs(Msgs, !.ModuleInfo, WarnCnt, ErrCnt, !IO),
+		globals__io_lookup_bool_option(halt_at_warn, HaltAtWarn, !IO),
+		(
 		(
-			{
 				ErrCnt > 0
 			;
 				WarnCnt > 0,
 				HaltAtWarn = yes
-			}
+			)
 		->
-			io__set_exit_status(1),
-			{ module_info_incr_errors(ModuleInfo0, ModuleInfo) }
+			io__set_exit_status(1, !IO),
+			module_info_incr_errors(!ModuleInfo)
 		;
-			{ ModuleInfo = ModuleInfo0 }
+			true
 		)
 	).
 
-det_report_msgs(Msgs, ModuleInfo, WarnCnt, ErrCnt) -->
-	globals__io_lookup_bool_option(warn_simple_code, WarnSimple),
-	globals__io_lookup_bool_option(warn_duplicate_calls, WarnCalls),
+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,
-		0, WarnCnt, 0, ErrCnt).
+		0, WarnCnt, 0, ErrCnt, !IO).
 
-:- pred det_report_msgs_2(list(det_msg), bool, bool, module_info, int, int,
-	int, int, io__state, io__state).
-:- mode det_report_msgs_2(in, in, in, in, in, out, in, out, di, uo) is det.
+:- 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.
 
 det_report_msgs_2([], _, _, _ModuleInfo,
-		WarnCnt, WarnCnt, ErrCnt, ErrCnt) --> [].
+		!WarnCnt, !ErrCnt, !IO).
 det_report_msgs_2([Msg | Msgs], WarnSimple, WarnCalls, ModuleInfo,
-		WarnCnt0, WarnCnt, ErrCnt0, ErrCnt) -->
-	{ det_msg_get_type(Msg, MsgType) },
-	( { WarnSimple = no, MsgType = simple_code_warning } ->
-		{ WarnCnt1 = WarnCnt0 },
-		{ ErrCnt1 = ErrCnt0 }
-	; { WarnCalls = no, MsgType = call_warning } ->
-		{ WarnCnt1 = WarnCnt0 },
-		{ ErrCnt1 = ErrCnt0 }
-	;
-		det_report_msg(Msg, ModuleInfo),
-		(
-			{ MsgType = simple_code_warning },
-			{ WarnCnt1 = WarnCnt0 + 1 },
-			{ ErrCnt1 = ErrCnt0 }
-		;
-			{ MsgType = call_warning },
-			{ WarnCnt1 = WarnCnt0 + 1 },
-			{ ErrCnt1 = ErrCnt0 }
-		;
-			{ MsgType = error },
-			{ ErrCnt1 = ErrCnt0 + 1 },
-			{ WarnCnt1 = WarnCnt0 }
+		!WarnCnt, !ErrCnt, !IO) :-
+	det_msg_get_type(Msg, MsgType),
+	( WarnSimple = no, MsgType = simple_code_warning ->
+		true
+	; WarnCalls = no, MsgType = call_warning ->
+		true
+	;
+		det_report_msg(Msg, ModuleInfo, !IO),
+		(
+			MsgType = simple_code_warning,
+			!:WarnCnt = !.WarnCnt + 1
+		;
+			MsgType = call_warning,
+			!:WarnCnt = !.WarnCnt + 1
+		;
+			MsgType = error,
+			!:ErrCnt = !.ErrCnt + 1
 		)
 	),
 	det_report_msgs_2(Msgs, WarnSimple, WarnCalls, ModuleInfo,
-		WarnCnt1, WarnCnt, ErrCnt1, ErrCnt).
+		!WarnCnt, !ErrCnt, !IO).
 
-:- pred det_msg_get_type(det_msg, det_msg_type).
-:- mode det_msg_get_type(in, out) is det.
+:- 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).
@@ -1104,8 +1090,7 @@
 det_msg_is_any_mode_msg(par_conj_not_det(_, _, _, _, _), any_mode).
 det_msg_is_any_mode_msg(pragma_c_code_without_det_decl(_, _), any_mode).
 
-:- pred det_report_msg(det_msg, module_info, io__state, io__state).
-:- mode det_report_msg(in, in, di, uo) is det.
+:- pred det_report_msg(det_msg::in, module_info::in, io::di, io::uo) is det.
 
 det_report_msg(multidet_disj(Context, DisjunctContexts), _) -->
 	prog_out__write_context(Context),
@@ -1385,7 +1370,7 @@
 %-----------------------------------------------------------------------------%
 
 :- pred det_report_seen_call_id(seen_call_id::in, module_info::in,
-		io__state::di, io__state::uo) is det.
+	io::di, io::uo) is det.
 	
 det_report_seen_call_id(SeenCall, ModuleInfo) -->
 	(
@@ -1396,11 +1381,11 @@
 		{ SeenCall = higher_order_call },
 		io__write_string("higher-order call")
 	).
+
 %-----------------------------------------------------------------------------%
 
-:- pred det_report_context_lines(list(prog_context), bool, 
-		io__state, io__state).
-:- mode det_report_context_lines(in, in, di, uo) is det.
+:- pred det_report_context_lines(list(prog_context)::in, bool::in,
+	io::di, io::uo) is det.
 
 det_report_context_lines([], _) --> [].
 det_report_context_lines([Context | Contexts], First) -->
Index: compiler/error_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/error_util.m,v
retrieving revision 1.26
diff -u -b -r1.26 error_util.m
--- compiler/error_util.m	19 Mar 2004 10:19:19 -0000	1.26
+++ compiler/error_util.m	4 Apr 2004 10:11:56 -0000
@@ -37,7 +37,7 @@
 
 :- import_module parse_tree__prog_data.
 
-:- import_module char, io, list, std_util.
+:- import_module bool, char, io, list, std_util.
 
 :- type format_component
 	--->	fixed(string)	% This string should appear in the output
@@ -82,6 +82,11 @@
 :- pred write_error_pieces_not_first_line(prog_context::in, int::in,
 	list(format_component)::in, io::di, io::uo) is det.
 
+	% Display the given error message. The bool is true iff
+	% this is the first line.
+:- pred write_error_pieces_maybe_first_line(bool::in, prog_context::in,
+	int::in, list(format_component)::in, io::di, io::uo) is det.
+
 :- pred write_error_pieces_maybe_with_context(maybe(prog_context)::in, int::in,
 	list(format_component)::in, io::di, io::uo) is det.
 
@@ -146,7 +151,7 @@
 :- import_module libs__globals.
 :- import_module libs__options.
 
-:- import_module bool, io, list, term, char, string, int, require.
+:- import_module io, list, term, char, string, int, require.
 
 list_to_pieces([], []).
 list_to_pieces([Elem], [words(Elem)]).
@@ -177,6 +182,17 @@
 write_error_pieces_not_first_line(Context, Indent, Components, !IO) :-
 	write_error_pieces_maybe_with_context(no, yes(Context),
 		Indent, Components, !IO).
+
+write_error_pieces_maybe_first_line(IsFirst, Context, Indent, Components,
+		!IO) :-
+	(
+		IsFirst = yes,
+		write_error_pieces(Context, Indent, Components, !IO)
+	;
+		IsFirst = no,
+		write_error_pieces_not_first_line(Context, Indent, Components,
+			!IO)
+	).
 
 write_error_pieces_maybe_with_context(MaybeContext, Indent, Components, !IO) :-
 	write_error_pieces_maybe_with_context(yes, MaybeContext,
Index: compiler/export.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/export.m,v
retrieving revision 1.76
diff -u -b -r1.76 export.m
--- compiler/export.m	24 Mar 2004 00:39:27 -0000	1.76
+++ compiler/export.m	3 Apr 2004 14:54:34 -0000
@@ -29,21 +29,20 @@
 	% of a foreign function named in a `pragma export' declaration,
 	% which is used to allow a call to be made to a Mercury
 	% procedure from the foreign language.
-:- pred export__get_foreign_export_decls(module_info, foreign_export_decls).
-:- mode export__get_foreign_export_decls(in, out) is det.
+:- pred export__get_foreign_export_decls(module_info::in,
+	foreign_export_decls::out) is det.
 
 	% From the module_info, get a list of foreign_export_defns,
 	% each of which is a string containing the foreign code
 	% for defining a foreign function named in a `pragma export' decl.
-:- pred export__get_foreign_export_defns(module_info, foreign_export_defns).
-:- mode export__get_foreign_export_defns(in, out) is det.
+:- pred export__get_foreign_export_defns(module_info::in,
+	foreign_export_defns::out) is det.
 
 	% Produce an interface file containing declarations for the
 	% exported foreign functions (if required in this foreign
 	% language).
-:- pred export__produce_header_file(foreign_export_decls, module_name,
-					io__state, io__state).
-:- mode export__produce_header_file(in, in, di, uo) is det.
+:- pred export__produce_header_file(foreign_export_decls::in, module_name::in,
+	io::di, io::uo) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -53,14 +52,12 @@
 	% Generate C code to convert an rval (represented as a string), from
 	% a C type to a mercury C type (ie. convert strings and floats to
 	% words) and return the resulting C code as a string.
-:- pred convert_type_to_mercury(string, type, string).
-:- mode convert_type_to_mercury(in, in, out) is det.
+:- pred convert_type_to_mercury(string::in, (type)::in, string::out) is det.
 
 	% Generate C code to convert an rval (represented as a string), from
 	% a mercury C type to a C type. (ie. convert words to strings and
 	% floats if required) and return the resulting C code as a string.
-:- pred convert_type_from_mercury(string, type, string).
-:- mode convert_type_from_mercury(in, in, out) is det.
+:- pred convert_type_from_mercury(string::in, (type)::in, string::out) is det.
 
 	% Succeeds iff the given C type is known by the compiler to be
 	% an integer or pointer type the same size as MR_Word.
@@ -104,13 +101,12 @@
 
 	ForeignExportDecls = foreign_export_decls(ForeignDecls, C_ExportDecls).
 
-:- pred export__get_foreign_export_decls_2(pred_table,
-		list(pragma_exported_proc), globals,
-		module_info, list(foreign_export_decl)).
-:- mode export__get_foreign_export_decls_2(in, in, in, in, out) is det.
+:- pred export__get_foreign_export_decls_2(pred_table::in,
+	list(pragma_exported_proc)::in, globals::in, module_info::in,
+	list(foreign_export_decl)::out) is det.
 
 export__get_foreign_export_decls_2(_Preds, [], _, _, []).
-export__get_foreign_export_decls_2(Preds, [E|ExportedProcs], Globals, Module,
+export__get_foreign_export_decls_2(Preds, [E | ExportedProcs], Globals, Module,
 		C_ExportDecls) :-
 	E = pragma_exported_proc(PredId, ProcId, C_Function, _Ctxt),
 	get_export_info(Preds, PredId, ProcId, Globals, Module, _HowToDeclare,
@@ -224,9 +220,8 @@
 	%	return retval;
 	% #endif
 	% }
-:- pred export__to_c(pred_table, list(pragma_exported_proc), module_info,
-		list(string)).
-:- mode export__to_c(in, in, in, out) is det.
+:- pred export__to_c(pred_table::in, list(pragma_exported_proc)::in,
+	module_info::in, list(string)::out) is det.
 
 export__to_c(_Preds, [], _Module, []).
 export__to_c(Preds, [E|ExportedProcs], Module, ExportedProcsCode) :-
@@ -297,7 +292,6 @@
 	export__to_c(Preds, ExportedProcs, Module, TheRest),
 	ExportedProcsCode = [Code|TheRest].
 
-
 	% get_export_info(Preds, PredId, ProcId, Globals, DeclareString,
 	%		C_RetType, MaybeDeclareRetval, MaybeFail, MaybeSuccess,
 	%		ArgInfoTypes):
@@ -309,11 +303,9 @@
 	%	- the actions on success and failure, and
 	%	- the argument locations/modes/types.
 
-:- pred get_export_info(pred_table, pred_id, proc_id, globals, module_info,
-			string, string, string, string, string,
-			assoc_list(arg_info, type)).
-:- mode get_export_info(in, in, in, in, in,
-		out, out, out, out, out, out) is det.
+:- pred get_export_info(pred_table::in, pred_id::in, proc_id::in, globals::in,
+	module_info::in, string::out, string::out, string::out, string::out,
+	string::out, assoc_list(arg_info, type)::out) is det.
 
 get_export_info(Preds, PredId, ProcId, Globals, Module,
 		HowToDeclareLabel, C_RetType, MaybeDeclareRetval,
@@ -420,6 +412,7 @@
 	%	the arguments of the exported C function.
 	%
 :- pred export__include_arg(pair(arg_info, type)::in) is semidet.
+
 export__include_arg(arg_info(_Loc, Mode) - Type) :-
 	Mode \= top_unused,
 	\+ type_util__is_dummy_argument_type(Type).
@@ -428,17 +421,15 @@
 	% build a string to declare the argument types (and if
 	% NameThem = yes, the argument names) of a C function.
 
-:- pred get_argument_declarations(assoc_list(arg_info, type), bool,
-		module_info, string).
-:- mode get_argument_declarations(in, in, in, out) is det.
+:- pred get_argument_declarations(assoc_list(arg_info, type)::in, bool::in,
+	module_info::in, string::out) is det.
 
 get_argument_declarations([], _, _, "void").
 get_argument_declarations([X|Xs], NameThem, Module, Result) :-
 	get_argument_declarations_2([X|Xs], 0, NameThem, Module, Result).
 
-:- pred get_argument_declarations_2(assoc_list(arg_info, type), int, bool,
-				module_info, string).
-:- mode get_argument_declarations_2(in, in, in, in, out) is det.
+:- pred get_argument_declarations_2(assoc_list(arg_info, type)::in, int::in,
+	bool::in, module_info::in, string::out) is det.
 
 get_argument_declarations_2([], _, _, _, "").
 get_argument_declarations_2([AT|ATs], Num0, NameThem, Module, Result) :-
@@ -457,9 +448,8 @@
 			Result)
 	).
 
-:- pred get_argument_declaration(arg_info, type, int, bool, module_info,
-		string, string).
-:- mode get_argument_declaration(in, in, in, in, in, out, out) is det.
+:- pred get_argument_declaration(arg_info::in, (type)::in, int::in, bool::in,
+	module_info::in, string::out, string::out) is det.
 
 get_argument_declaration(ArgInfo, Type, Num, NameThem, Module,
 		TypeString, ArgName) :-
@@ -519,8 +509,8 @@
 	get_input_args(ATs, Num, ModuleInfo, TheRest),
 	string__append(InputArg, TheRest, Result).
 
-:- pred copy_output_args(assoc_list(arg_info, type), int, module_info, string).
-:- mode copy_output_args(in, in, in, out) is det.
+:- pred copy_output_args(assoc_list(arg_info, type)::in, int::in,
+	module_info::in, string::out) is det.
 
 copy_output_args([], _, _, "").
 copy_output_args([AT|ATs], Num0, ModuleInfo, Result) :-
@@ -559,8 +549,7 @@
 
 	% convert an argument location (currently just a register number)
 	% to a string representing a C code fragment that names it.
-:- pred argloc_to_string(arg_loc, string).
-:- mode argloc_to_string(in, out) is det.
+:- pred argloc_to_string(arg_loc::in, string::out) is det.
 
 argloc_to_string(RegNum, RegName) :-
 	string__int_to_string(RegNum, RegNumString),
@@ -613,29 +602,34 @@
 
 % This procedure is used for both the MLDS and LLDS back-ends.
 
-export__produce_header_file(ForeignExportDecls, ModuleName) -->
+export__produce_header_file(ForeignExportDecls, ModuleName, !IO) :-
 		% We always produce a .mh file because with intermodule
 		% optimization enabled the .o file depends on all the
 		% .mh files of the imported modules so we always need to
 		% produce a .mh file even if it contains nothing.
-	{ ForeignExportDecls = foreign_export_decls(ForeignDecls,
-			C_ExportDecls) },
-	{ HeaderExt = ".mh" },
-	module_name_to_file_name(ModuleName, HeaderExt, yes, FileName),
-	io__open_output(FileName ++ ".tmp", Result),
+	ForeignExportDecls = foreign_export_decls(ForeignDecls,
+			C_ExportDecls),
+	HeaderExt = ".mh",
+	module_name_to_file_name(ModuleName, HeaderExt, yes, FileName, !IO),
+	io__open_output(FileName ++ ".tmp", Result, !IO),
 	(
-		{ Result = ok(FileStream) }
+		Result = ok(FileStream)
 	->
-		io__set_output_stream(FileStream, OutputStream),
-		module_name_to_file_name(ModuleName, ".m", no, SourceFileName),
-		{ library__version(Version) },
-		io__write_strings(["/*\n** Automatically generated from `",
-			SourceFileName,
-			"' by the\n** Mercury compiler, version ", Version,
-			".\n** Do not edit.\n*/\n"]),
-		{ MangledModuleName = sym_name_mangle(ModuleName) },
-		{ string__to_upper(MangledModuleName, UppercaseModuleName) },
-		{ string__append(UppercaseModuleName, "_H", GuardMacroName) },
+		io__set_output_stream(FileStream, OutputStream, !IO),
+		module_name_to_file_name(ModuleName, ".m", no, SourceFileName,
+			!IO),
+		library__version(Version),
+		io__write_strings([
+			"/*\n",
+			"** Automatically generated from `",
+				SourceFileName, "'\n",
+			"** by the Mercury compiler,\n",
+			"** version ", Version, ".\n",
+			"** Do not edit.\n",
+			"*/\n"], !IO),
+		MangledModuleName = sym_name_mangle(ModuleName),
+		string__to_upper(MangledModuleName, UppercaseModuleName),
+		string__append(UppercaseModuleName, "_H", GuardMacroName),
 		io__write_strings([
 			"#ifndef ", GuardMacroName, "\n",
 			"#define ", GuardMacroName, "\n",
@@ -654,38 +648,40 @@
 			"#ifdef MR_DEEP_PROFILING\n",
 			"#include ""mercury_deep_profiling.h""\n",
 			"#endif\n",
-			"\n"]),
+			"\n"], !IO),
 
-		io__write_strings(["#ifndef ", decl_guard(ModuleName),
-				 "\n#define ", decl_guard(ModuleName), "\n"]),
-		list__foldl(output_foreign_decl, ForeignDecls),
-		io__write_string("\n#endif\n"),
+		io__write_strings([
+			"#ifndef ", decl_guard(ModuleName), "\n",
+			"#define ", decl_guard(ModuleName), "\n"],
+			!IO),
+		list__foldl(output_foreign_decl, ForeignDecls, !IO),
+		io__write_string("\n#endif\n", !IO),
 
-		export__produce_header_file_2(C_ExportDecls),
+		export__produce_header_file_2(C_ExportDecls, !IO),
 		io__write_strings([
 			"\n",
 			"#ifdef __cplusplus\n",
 			"}\n",
 			"#endif\n",
 			"\n",
-			"#endif /* ", GuardMacroName, " */\n"]),
-		io__set_output_stream(OutputStream, _),
-		io__close_output(FileStream),
+			"#endif /* ", GuardMacroName, " */\n"], !IO),
+		io__set_output_stream(OutputStream, _, !IO),
+		io__close_output(FileStream, !IO),
 		% rename "<ModuleName>.mh.tmp" to "<ModuleName>.mh".
-		update_interface(FileName)
+		update_interface(FileName, !IO)
 	;
-		io__progname_base("export.m", ProgName),
-		io__write_string("\n"),
-		io__write_string(ProgName),
-		io__write_string(": can't open `"),
-		io__write_string(FileName ++ ".tmp"),
-		io__write_string("' for output\n"),
-		io__set_exit_status(1)
+		io__progname_base("export.m", ProgName, !IO),
+		io__write_string("\n", !IO),
+		io__write_string(ProgName, !IO),
+		io__write_string(": can't open `", !IO),
+		io__write_string(FileName ++ ".tmp", !IO),
+		io__write_string("' for output\n", !IO),
+		io__set_exit_status(1, !IO)
 	).
 
-:- pred export__produce_header_file_2(list(foreign_export_decl),
-		io__state, io__state).
-:- mode export__produce_header_file_2(in, di, uo) is det.
+:- pred export__produce_header_file_2(list(foreign_export_decl)::in,
+	io::di, io::uo) is det.
+
 export__produce_header_file_2([]) --> [].
 export__produce_header_file_2([E|ExportedProcs]) -->
 	{ E = foreign_export_decl(Lang, C_RetType, C_Function, ArgDecls) },
Index: compiler/fact_table.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/fact_table.m,v
retrieving revision 1.52
diff -u -b -r1.52 fact_table.m
--- compiler/fact_table.m	23 Mar 2004 10:52:02 -0000	1.52
+++ compiler/fact_table.m	4 Apr 2004 07:58:03 -0000
@@ -400,7 +400,7 @@
 				ProcStreams, MaybeOutput, FactNum, Result,
 				!Errors, !IO)
 		;
-			hlds_out__pred_or_func_to_full_str(PredOrFunc, PFStr),
+			PFStr = hlds_out__pred_or_func_to_full_str(PredOrFunc),
 			string__format("Error: invalid clause for %s `%s/%d'.",
 				[s(PFStr), s(PredString), i(Arity0)], Msg),
 			add_error_report(Context, [words(Msg)], !Errors),
Index: compiler/follow_code.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/follow_code.m,v
retrieving revision 1.67
diff -u -b -r1.67 follow_code.m
--- compiler/follow_code.m	24 Oct 2003 06:17:37 -0000	1.67
+++ compiler/follow_code.m	3 Apr 2004 15:03:28 -0000
@@ -81,48 +81,45 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_in_goal(hlds_goal, hlds_goal, pair(bool),
-	bool, bool).
-:- mode move_follow_code_in_goal(in, out, in, in, out) is det.
+:- pred move_follow_code_in_goal(hlds_goal::in, hlds_goal::out, pair(bool)::in,
+	bool::in, bool::out) is det.
 
-move_follow_code_in_goal(Goal0 - GoalInfo, Goal - GoalInfo, Flags, R0, R) :-
-	move_follow_code_in_goal_2(Goal0, Goal, Flags, R0, R).
+move_follow_code_in_goal(Goal0 - GoalInfo, Goal - GoalInfo, Flags, !R) :-
+	move_follow_code_in_goal_2(Goal0, Goal, Flags, !R).
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_in_goal_2(hlds_goal_expr, hlds_goal_expr,
-	pair(bool), bool, bool).
-:- mode move_follow_code_in_goal_2(in, out, in, in, out) is det.
+:- pred move_follow_code_in_goal_2(hlds_goal_expr::in, hlds_goal_expr::out,
+	pair(bool)::in, bool::in, bool::out) is det.
 
-move_follow_code_in_goal_2(conj(Goals0), conj(Goals), Flags, R0, R) :-
-	move_follow_code_in_conj(Goals0, Goals, Flags, R0, R).
+move_follow_code_in_goal_2(conj(Goals0), conj(Goals), Flags, !R) :-
+	move_follow_code_in_conj(Goals0, Goals, Flags, !R).
 
-move_follow_code_in_goal_2(par_conj(Goals0), par_conj(Goals),
-		Flags, R0, R) :-
+move_follow_code_in_goal_2(par_conj(Goals0), par_conj(Goals), Flags, !R) :-
 		% move_follow_code_in_disj treats its list of goals as
 		% independent goals, so we can use it to process the
 		% independent parallel conjuncts.
-	move_follow_code_in_disj(Goals0, Goals, Flags, R0, R).
+	move_follow_code_in_disj(Goals0, Goals, Flags, !R).
 
-move_follow_code_in_goal_2(disj(Goals0), disj(Goals), Flags, R0, R) :-
-	move_follow_code_in_disj(Goals0, Goals, Flags, R0, R).
+move_follow_code_in_goal_2(disj(Goals0), disj(Goals), Flags, !R) :-
+	move_follow_code_in_disj(Goals0, Goals, Flags, !R).
 
-move_follow_code_in_goal_2(not(Goal0), not(Goal), Flags, R0, R) :-
-	move_follow_code_in_goal(Goal0, Goal, Flags, R0, R).
+move_follow_code_in_goal_2(not(Goal0), not(Goal), Flags, !R) :-
+	move_follow_code_in_goal(Goal0, Goal, Flags, !R).
 
 move_follow_code_in_goal_2(switch(Var, Det, Cases0),
-		switch(Var, Det, Cases), Flags, R0, R) :-
-	move_follow_code_in_cases(Cases0, Cases, Flags, R0, R).
+		switch(Var, Det, Cases), Flags, !R) :-
+	move_follow_code_in_cases(Cases0, Cases, Flags, !R).
 
 move_follow_code_in_goal_2(if_then_else(Vars, Cond0, Then0, Else0),
-		if_then_else(Vars, Cond, Then, Else), Flags, R0, R) :-
-	move_follow_code_in_goal(Cond0, Cond, Flags, R0, R1),
-	move_follow_code_in_goal(Then0, Then, Flags, R1, R2),
-	move_follow_code_in_goal(Else0, Else, Flags, R2, R).
+		if_then_else(Vars, Cond, Then, Else), Flags, !R) :-
+	move_follow_code_in_goal(Cond0, Cond, Flags, !R),
+	move_follow_code_in_goal(Then0, Then, Flags, !R),
+	move_follow_code_in_goal(Else0, Else, Flags, !R).
 
 move_follow_code_in_goal_2(some(Vars, CanRemove, Goal0),
-		some(Vars, CanRemove, Goal), Flags, R0, R) :-
-	move_follow_code_in_goal(Goal0, Goal, Flags, R0, R).
+		some(Vars, CanRemove, Goal), Flags, !R) :-
+	move_follow_code_in_goal(Goal0, Goal, Flags, !R).
 
 move_follow_code_in_goal_2(generic_call(A,B,C,D),
 			generic_call(A,B,C,D), _, R, R).
@@ -143,48 +140,44 @@
 	% move_follow_code_in_disj is used both for disjunction and
 	% parallel conjunction.
 
-:- pred move_follow_code_in_disj(list(hlds_goal), list(hlds_goal),
-	pair(bool), bool, bool).
-:- mode move_follow_code_in_disj(in, out, in, in, out) is det.
+:- pred move_follow_code_in_disj(list(hlds_goal)::in, list(hlds_goal)::out,
+	pair(bool)::in, bool::in, bool::out) is det.
 
-move_follow_code_in_disj([], [], _, R, R).
-move_follow_code_in_disj([Goal0|Goals0], [Goal|Goals], Flags, R0, R) :-
-	move_follow_code_in_goal(Goal0, Goal, Flags, R0, R1),
-	move_follow_code_in_disj(Goals0, Goals, Flags, R1, R).
+move_follow_code_in_disj([], [], _, !R).
+move_follow_code_in_disj([Goal0|Goals0], [Goal|Goals], Flags, !R) :-
+	move_follow_code_in_goal(Goal0, Goal, Flags, !R),
+	move_follow_code_in_disj(Goals0, Goals, Flags, !R).
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_in_cases(list(case), list(case), pair(bool),
-	bool, bool).
-:- mode move_follow_code_in_cases(in, out, in, in, out) is det.
+:- pred move_follow_code_in_cases(list(case)::in, list(case)::out,
+	pair(bool)::in, bool::in, bool::out) is det.
 
 move_follow_code_in_cases([], [], _, R, R).
 move_follow_code_in_cases([case(Cons, Goal0)|Goals0], [case(Cons, Goal)|Goals],
-		Flags, R0, R) :-
-	move_follow_code_in_goal(Goal0, Goal, Flags, R0, R1),
-	move_follow_code_in_cases(Goals0, Goals, Flags, R1, R).
+		Flags, !R) :-
+	move_follow_code_in_goal(Goal0, Goal, Flags, !R),
+	move_follow_code_in_cases(Goals0, Goals, Flags, !R).
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_in_conj(list(hlds_goal), list(hlds_goal),
-	pair(bool), bool, bool).
-:- mode move_follow_code_in_conj(in, out, in, in, out) is det.
+:- pred move_follow_code_in_conj(list(hlds_goal)::in, list(hlds_goal)::out,
+	pair(bool)::in, bool::in, bool::out) is det.
 
 	% Find the first branched structure, and split the
 	% conj into those goals before and after it.
 
-move_follow_code_in_conj(Goals0, Goals, Flags, R0, R) :-
-	move_follow_code_in_conj_2(Goals0, [], RevGoals, Flags, R0, R),
+move_follow_code_in_conj(Goals0, Goals, Flags, !R) :-
+	move_follow_code_in_conj_2(Goals0, [], RevGoals, Flags, !R),
 	list__reverse(RevGoals, Goals).
 
-:- pred move_follow_code_in_conj_2(list(hlds_goal), list(hlds_goal),
-	list(hlds_goal), pair(bool), bool, bool).
-:- mode move_follow_code_in_conj_2(in, in, out, in, in, out) is det.
-
-move_follow_code_in_conj_2([], RevPrevGoals, RevPrevGoals, _, R, R).
-move_follow_code_in_conj_2([Goal0 | Goals0], RevPrevGoals0, RevPrevGoals,
-		Flags, R0, R) :-
-	Flags = PushFollowCode - PushPrevCode,
+:- pred move_follow_code_in_conj_2(list(hlds_goal)::in, list(hlds_goal)::in,
+	list(hlds_goal)::out, pair(bool)::in, bool::in, bool::out) is det.
+
+move_follow_code_in_conj_2([], !RevPrevGoals, _, !R).
+move_follow_code_in_conj_2([Goal0 | Goals0], !RevPrevGoals,
+		Flags, !R) :-
+	Flags = PushFollowCode - _PushPrevCode,
 	(
 		PushFollowCode = yes,
 		Goal0 = GoalExpr0 - _,
@@ -193,29 +186,16 @@
 		FollowGoals \= [],
 		move_follow_code_move_goals(Goal0, FollowGoals, Goal1Prime)
 	->
-		R1 = yes,
+		!:R = yes,
 		Goal1 = Goal1Prime,
 		RestGoals = RestGoalsPrime
 	;
-		R1 = R0,
 		Goal1 = Goal0,
 		RestGoals = Goals0
 	),
-	(
-		PushPrevCode = yes
-	->
-		move_prev_code_forbidden_vars(RestGoals, ForbiddenVars),
-		move_prev_code(Goal1, Goal2, ForbiddenVars,
-			RevPrevGoals0, RevPrevGoals1, R1, R2)
-	;
-		RevPrevGoals1 = RevPrevGoals0,
-		Goal2 = Goal1,
-		R2 = R1
-	),
-	move_follow_code_in_goal(Goal2, Goal, Flags, R2, R3),
-	RevPrevGoals2 = [Goal | RevPrevGoals1],
-	move_follow_code_in_conj_2(RestGoals, RevPrevGoals2, RevPrevGoals,
-		Flags, R3, R).
+	move_follow_code_in_goal(Goal1, Goal, Flags, !R),
+	!:RevPrevGoals = [Goal | !.RevPrevGoals],
+	move_follow_code_in_conj_2(RestGoals, !RevPrevGoals, Flags, !R).
 
 %-----------------------------------------------------------------------------%
 
@@ -231,8 +211,8 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_move_goals(hlds_goal, list(hlds_goal), hlds_goal).
-:- mode move_follow_code_move_goals(in, in, out) is semidet.
+:- pred move_follow_code_move_goals(hlds_goal::in, list(hlds_goal)::in,
+	hlds_goal::out) is semidet.
 
 move_follow_code_move_goals(Goal0 - GoalInfo, FollowGoals, Goal - GoalInfo) :-
 	(
@@ -254,9 +234,8 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_move_goals_cases(list(case), list(hlds_goal),
-	list(case)).
-:- mode move_follow_code_move_goals_cases(in, in, out) is semidet.
+:- pred move_follow_code_move_goals_cases(list(case)::in, list(hlds_goal)::in,
+	list(case)::out) is semidet.
 
 move_follow_code_move_goals_cases([], _FollowGoals, []).
 move_follow_code_move_goals_cases([Case0|Cases0], FollowGoals, [Case|Cases]) :-
@@ -267,9 +246,8 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_move_goals_disj(list(hlds_goal), list(hlds_goal),
-	list(hlds_goal)).
-:- mode move_follow_code_move_goals_disj(in, in, out) is semidet.
+:- pred move_follow_code_move_goals_disj(list(hlds_goal)::in,
+	list(hlds_goal)::in, list(hlds_goal)::out) is semidet.
 
 move_follow_code_move_goals_disj([], _FollowGoals, []).
 move_follow_code_move_goals_disj([Goal0|Goals0], FollowGoals, [Goal|Goals]) :-
@@ -282,9 +260,8 @@
 	% (with a potentially blank goal_info), checking that the
 	% determinism of the goal is not changed.
 
-:- pred follow_code__conjoin_goal_and_goal_list(hlds_goal, list(hlds_goal),
-	hlds_goal).
-:- mode follow_code__conjoin_goal_and_goal_list(in, in, out) is semidet.
+:- pred follow_code__conjoin_goal_and_goal_list(hlds_goal::in,
+	list(hlds_goal)::in, hlds_goal::out) is semidet.
 
 follow_code__conjoin_goal_and_goal_list(Goal0, FollowGoals, Goal) :-
 	Goal0 = GoalExpr0 - GoalInfo0,
@@ -306,8 +283,8 @@
 	% This check is necessary to make sure that follow_code
 	% doesn't change the determinism of the goal.
 
-:- pred check_follow_code_detism(list(hlds_goal), determinism).
-:- mode check_follow_code_detism(in, in) is semidet.
+:- pred check_follow_code_detism(list(hlds_goal)::in, determinism::in)
+	is semidet.
 
 check_follow_code_detism([], _).
 check_follow_code_detism([_ - GoalInfo | Goals], Detism0) :-
@@ -317,8 +294,7 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred move_follow_code_is_builtin(hlds_goal).
-:- mode move_follow_code_is_builtin(in) is semidet.
+:- pred move_follow_code_is_builtin(hlds_goal::in) is semidet.
 
 move_follow_code_is_builtin(unify(_, _, _, Unification, _) - _GoalInfo) :-
 	Unification \= complicated_unify(_, _, _).
@@ -328,15 +304,8 @@
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- pred move_prev_code(hlds_goal, hlds_goal, set(prog_var),
-	list(hlds_goal), list(hlds_goal), bool, bool).
-% :- mode move_prev_code(di, uo, in, di, uo, in, out) is det.
-:- mode move_prev_code(in, out, in, in, out, in, out) is det.
-
-move_prev_code(Goal, Goal, _, RevPrevGoals, RevPrevGoals, R, R).
-
 % move_prev_code(Goal0, Goal, ForbiddenVars0, RevPrevGoals0, RevPrevGoals,
-% 		R0, R) :-
+% 		!R) :-
 % 	(
 % 		move_prev_code_breakup_branched(Goal0, Cond0, First0, Rest0)
 % 	->
@@ -349,12 +318,12 @@
 % 				RevPrevGoals0, RevPrevGoals1)
 % 		->
 % 			move_prev_code(Rest0, Rest, ForbiddenVars1,
-% 				RevPrevGoals1, RevPrevGoals, R0, R),
+% 				RevPrevGoals1, RevPrevGoals, !R),
 % 			move_prev_code_replace_first(Goal0,
 % 				Producers, Rest, Goal)
 % 		;
 % 			move_prev_code(Rest0, Rest, ForbiddenVars1,
-% 				RevPrevGoals0, RevPrevGoals, R0, R)
+% 				RevPrevGoals0, RevPrevGoals, !R)
 % 		)
 % 	;
 % 		R = R0,
@@ -366,8 +335,8 @@
 % 	hlds_goal).
 % :- mode move_prev_code_breakup_branched(in, out, out, out) is semidet.
 
-:- pred move_prev_code_forbidden_vars(list(hlds_goal), set(prog_var)).
-:- mode move_prev_code_forbidden_vars(in, out) is det.
+:- pred move_prev_code_forbidden_vars(list(hlds_goal)::in, set(prog_var)::out)
+	is det.
 
 move_prev_code_forbidden_vars([], Empty) :-
 	set__init(Empty).
Index: compiler/graph_colour.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/graph_colour.m,v
retrieving revision 1.11
diff -u -b -r1.11 graph_colour.m
--- compiler/graph_colour.m	20 Mar 2002 12:36:13 -0000	1.11
+++ compiler/graph_colour.m	3 Apr 2004 15:15:31 -0000
@@ -23,8 +23,7 @@
 
 :- import_module set.
 
-:- pred graph_colour__group_elements(set(set(T)), set(set(T))).
-:- mode graph_colour__group_elements(in, out) is det.
+:- pred graph_colour__group_elements(set(set(T))::in, set(set(T))::out) is det.
 
 :- implementation.
 
@@ -36,8 +35,8 @@
 	set__delete(Constraints, EmptySet, Constraints1),
 	set__to_sorted_list(Constraints1, ConstraintList),
 	graph_colour__find_all_colours(ConstraintList, AllVars, ColourList),
-	set__list_to_set(ColourList, Colours),
-	true.
+	set__list_to_set(ColourList, Colours).
+
 %	% performance reducing sanity check....
 %	(
 %		set__power_union(Colours, AllColours),
@@ -50,15 +49,13 @@
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__find_all_colours(list(set(T)), set(T), list(set(T))).
-:- mode graph_colour__find_all_colours(in, in, out) is det.
+:- pred graph_colour__find_all_colours(list(set(T))::in, set(T)::in,
+	list(set(T))::out) is det.
 
 	% Iterate the assignment of a new colour untill all constraints
 	% are satisfied.
 graph_colour__find_all_colours(ConstraintList, Vars, ColourList) :-
-	(
-		ConstraintList = []
-	->
+	( ConstraintList = [] ->
 		ColourList = []
 	;
 		graph_colour__next_colour(Vars, ConstraintList,
@@ -66,44 +63,44 @@
 		set__difference(Vars, Colour, RestVars),
 		graph_colour__find_all_colours(RemainingConstraints, RestVars,
 					ColourList0),
-		ColourList = [Colour|ColourList0]
+		ColourList = [Colour | ColourList0]
 	).
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__next_colour(set(T), list(set(T)), list(set(T)), set(T)).
-:- mode graph_colour__next_colour(in, in, out, out) is det.
+:- pred graph_colour__next_colour(set(T)::in, list(set(T))::in,
+	list(set(T))::out, set(T)::out) is det.
 
-graph_colour__next_colour(Vars, ConstraintList, Remainder, SameColour) :-
+graph_colour__next_colour(Vars0, ConstraintList, Remainder, SameColour) :-
+	% Check if there are any constraints left to be satisfied.
 	(
-			% If there are any constraints left to be
-			% satisfied,
-		ConstraintList \= []
-	->
-			% Select a variable to assign a colour,
-		graph_colour__choose_var(Vars, Var, Vars1),
-			% and divide the constraints into those that
+		ConstraintList = [_ | _],
+			% Select a variable to assign a colour, ...
+		graph_colour__choose_var(Vars0, Var, Vars1),
+			% ... and divide the constraints into those that
 			% may be the same colour as that var and those
 			% that may not.
 		graph_colour__divide_constraints(Var, ConstraintList,
 				WereContaining, NotContaining, Vars1, RestVars),
 		(
-				% if there are sets that can
-				% share a colour with the selected var,
-			NotContaining \= []
-		->
-			(
-					% and if there is at least
-					% one variable that can share
-					% a colour with the selected
-					% variable,
-				\+ set__empty(RestVars)
-			->
-					% then recusively use the remaining
-					% constraints to assign a colour
-					% to one of the remaining vars,
-					% and assemble the constraint
-					% residues.
+				% See if there are sets that can
+				% share a colour with the selected var.
+			NotContaining = [_ | _],
+			( set__empty(RestVars) ->
+					% There were no variables left
+					% that could share a colour, so
+					% create a singleton set containing
+					% this variable.
+				set__singleton_set(SameColour, Var),
+				ResidueSets = NotContaining
+			;
+					% If there is at least one variable
+					% that can share a colour with the
+					% selected variable, then recursively
+					% use the remaining constraints to
+					% assign a colour to one of the
+					% remaining vars, and assemble the
+					% constraint residues.
 				graph_colour__next_colour(RestVars,
 					NotContaining, ResidueSets,
 							SameColour0),
@@ -111,15 +108,9 @@
 					% variables of the current
 					% colour.
 				set__insert(SameColour0, Var, SameColour)
-			;
-					% There were no variables left
-					% that could share a colour, so
-					% create a singleton set containing
-					% this variable.
-				set__singleton_set(SameColour, Var),
-				ResidueSets = NotContaining
 			)
 		;
+			NotContaining = [],
 				% There were no more constraints
 				% which could be satisfied by assigning
 				% any variable a colour the same as the
@@ -139,16 +130,13 @@
 	;
 			% If there were no constraints, then no colours
 			% were needed.
+		ConstraintList = [],
 		Remainder = [],
 		set__init(SameColour)
 	).
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__divide_constraints(T, list(set(T)), list(set(T)),
-				list(set(T)), set(T), set(T)).
-:- mode graph_colour__divide_constraints(in, in, out, out, in, out) is det.
-
 % graph_colour__divide_constraints takes a var and a list of sets of var,
 % and divides the list into two lists: a list of sets containing the
 % given variable and a list of sets not containing that variable. The
@@ -157,45 +145,38 @@
 % and any variables that were in sets that also contained the given
 % variables are removed from the threaded set.
 
-graph_colour__divide_constraints(_Var, [], [], [], Vars, Vars).
-graph_colour__divide_constraints(Var, [S|Ss], C, NC, Vars0, Vars) :-
-	graph_colour__divide_constraints(Var, Ss, C0, NC0, Vars0, Vars1),
-	(
-		set__member(Var, S)
-	->
+:- pred graph_colour__divide_constraints(T::in,
+	list(set(T))::in, list(set(T))::out, list(set(T))::out,
+	set(T)::in, set(T)::out) is det.
+
+graph_colour__divide_constraints(_Var, [], [], [], !Vars).
+graph_colour__divide_constraints(Var, [S | Ss], C, NC, !Vars) :-
+	graph_colour__divide_constraints(Var, Ss, C0, NC0, !Vars),
+	( set__member(Var, S) ->
 		set__delete(S, Var, T),
-		(
-			set__empty(T)
-		->
+		( set__empty(T) ->
 			C = C0
 		;
-			C = [T|C0]
+			C = [T | C0]
 		),
 		NC = NC0,
-		set__difference(Vars1, T, Vars)
+		set__difference(!.Vars, T, !:Vars)
 	;
 		C = C0,
-		NC = [S|NC0],
-		Vars = Vars1
+		NC = [S | NC0]
 	).
 
 %------------------------------------------------------------------------------%
 
-:- pred graph_colour__choose_var(set(T), T, set(T)).
-:- mode graph_colour__choose_var(in, out, out) is det.
-
 % graph_colour__choose_var/3, given a set of variables, chooses
-% one, returns it and the set with that variable removed. The
-% use of higher order preds could be used to make the heuristic
-% for which variable to choose user-defined.
+% one, returns it and the set with that variable removed.
 
-graph_colour__choose_var(Vars, Var, Vars1) :-
-	set__to_sorted_list(Vars, VarList),
-	(
-		VarList = [VarA|Vars1A]
-	->
-		Var = VarA,
-		set__list_to_set(Vars1A, Vars1)
+:- pred graph_colour__choose_var(set(T)::in, T::out, set(T)::out) is det.
+
+graph_colour__choose_var(Vars0, Var, Vars) :-
+	( set__remove_least(Vars0, VarPrime, VarsPrime) ->
+		Var = VarPrime,
+		Vars = VarsPrime
 	;
 		error("graph_colour__choose_var: no vars!")
 	).
Index: compiler/hlds_error_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_error_util.m,v
retrieving revision 1.1
diff -u -b -r1.1 hlds_error_util.m
--- compiler/hlds_error_util.m	19 Mar 2004 10:19:20 -0000	1.1
+++ compiler/hlds_error_util.m	3 Apr 2004 22:08:20 -0000
@@ -29,6 +29,9 @@
 :- pred describe_one_pred_name(module_info::in, pred_id::in,
 	string::out) is det.
 
+:- pred describe_one_pred_name_mode(module_info::in, pred_id::in,
+	inst_varset::in, list(mode)::in, string::out) is det.
+
 :- pred describe_several_pred_names(module_info::in,
 	list(pred_id)::in, list(format_component)::out) is det.
 
@@ -47,6 +50,8 @@
 
 :- implementation.
 
+:- import_module check_hlds__mode_util.
+:- import_module parse_tree__mercury_to_mercury.
 :- import_module parse_tree__prog_out.
 :- import_module parse_tree__prog_util.
 
@@ -69,7 +74,8 @@
 	(
 		pred_info_get_goal_type(PredInfo, promise(PromiseType))
 	->
-		Piece = "`" ++ promise_to_string(PromiseType) ++ "' declaration"
+		Piece = "`" ++ promise_to_string(PromiseType)
+			++ "' declaration"
 	;
 		string__int_to_string(OrigArity, ArityPart),
 		string__append_list([
@@ -82,6 +88,41 @@
 			ArityPart,
 			"'"], Piece)
 	).
+
+describe_one_pred_name_mode(Module, PredId, InstVarSet, ArgModes, Piece) :-
+	module_info_pred_info(Module, PredId, PredInfo),
+	ModuleName = pred_info_module(PredInfo),
+	prog_out__sym_name_to_string(ModuleName, ModuleNameString),
+	PredName = pred_info_name(PredInfo),
+	PredOrFunc = pred_info_is_pred_or_func(PredInfo),
+	PredOrFuncPart = pred_or_func_to_string(PredOrFunc),
+	strip_builtin_qualifiers_from_mode_list(ArgModes, StrippedArgModes),
+	(
+		PredOrFunc = predicate,
+		ArgModesPart =
+			"(" ++
+			mercury_mode_list_to_string(StrippedArgModes,
+				InstVarSet) ++
+			")"
+	;
+		PredOrFunc = function,
+		pred_args_to_func_args(StrippedArgModes, FuncArgModes,
+			FuncRetMode),
+		ArgModesPart =
+			"(" ++
+			mercury_mode_list_to_string(FuncArgModes,
+				InstVarSet) ++
+			") = " ++
+			mercury_mode_to_string(FuncRetMode, InstVarSet)
+	),
+	string__append_list([
+		PredOrFuncPart,
+		" `",
+		ModuleNameString,
+		".",
+		PredName,
+		ArgModesPart,
+		"'"], Piece).
 
 describe_several_pred_names(Module, PredId, Pieces) :-
 	list__map(describe_one_pred_name(Module), PredId, Pieces0),
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_module.m,v
retrieving revision 1.97
diff -u -b -r1.97 hlds_module.m
--- compiler/hlds_module.m	23 Mar 2004 10:52:03 -0000	1.97
+++ compiler/hlds_module.m	4 Apr 2004 07:57:38 -0000
@@ -1941,7 +1941,7 @@
                 % Undefined/invalid pred or func.
 		% the type-checker should ensure that this never happens
 		list__length(ArgTypes, Arity),
-		hlds_out__pred_or_func_to_str(PredOrFunc, PredOrFuncStr),
+		PredOrFuncStr = hlds_out__pred_or_func_to_str(PredOrFunc),
 		prog_out__sym_name_to_string(SymName, Name2),
 		string__int_to_string(Arity, ArityString),
 		string__append_list(["get_pred_id_and_proc_id: ", 
@@ -1961,7 +1961,7 @@
 		Name = pred_info_name(PredInfo),
 		PredOrFunc = pred_info_is_pred_or_func(PredInfo),
 		Arity = pred_info_arity(PredInfo),
-		hlds_out__pred_or_func_to_str(PredOrFunc, PredOrFuncStr),
+		PredOrFuncStr = hlds_out__pred_or_func_to_str(PredOrFunc),
 		string__int_to_string(Arity, ArityString),
 		( ProcIds = [] ->
 			string__append_list([
Index: compiler/hlds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_out.m,v
retrieving revision 1.326
diff -u -b -r1.326 hlds_out.m
--- compiler/hlds_out.m	23 Mar 2004 10:52:03 -0000	1.326
+++ compiler/hlds_out.m	4 Apr 2004 07:56:46 -0000
@@ -51,8 +51,7 @@
 :- pred hlds_out__write_class_id(class_id::in, io::di, io::uo) is det.
 
 :- pred hlds_out__write_cons_id(cons_id::in, io::di, io::uo) is det.
-
-:- pred hlds_out__cons_id_to_string(cons_id::in, string::out) is det.
+:- func hlds_out__cons_id_to_string(cons_id) = string.
 
 :- pred hlds_out__aditi_builtin_name(aditi_builtin::in, string::out) is det.
 
@@ -75,15 +74,17 @@
 
 :- pred hlds_out__write_simple_call_id(simple_call_id::in, io::di, io::uo)
 	is det.
+:- func hlds_out__simple_call_id_to_string(simple_call_id) = string.
 
 :- pred hlds_out__write_simple_call_id(pred_or_func::in,
 	sym_name_and_arity::in, io::di, io::uo) is det.
+:- func hlds_out__simple_call_id_to_string(pred_or_func, sym_name_and_arity)
+	= string.
 
 :- pred hlds_out__write_simple_call_id(pred_or_func::in, sym_name::in,
 	arity::in, io::di, io::uo) is det.
-
-:- pred hlds_out__simple_call_id_to_string(simple_call_id::in, string::out)
-	is det.
+:- func hlds_out__simple_call_id_to_string(pred_or_func, sym_name, arity)
+	= string.
 
 	% Write "argument %i of call to pred_or_func `foo/n'".
 	% The pred_markers argument is used to tell if the calling
@@ -97,11 +98,10 @@
 :- pred hlds_out__write_pred_or_func(pred_or_func::in, io::di, io::uo) is det.
 
 	% Return "predicate" or "function" depending on the given value.
-:- pred hlds_out__pred_or_func_to_full_str(pred_or_func::in, string::out)
-	is det.
+:- func hlds_out__pred_or_func_to_full_str(pred_or_func) = string.
 
 	% Return "pred" or "func" depending on the given value.
-:- pred hlds_out__pred_or_func_to_str(pred_or_func::in, string::out) is det.
+:- func hlds_out__pred_or_func_to_str(pred_or_func) = string.
 
 	% hlds_out__write_unify_context/5 writes out a message such as
 	%	foo.m:123:   in argument 3 of functor `foo/5':
@@ -126,13 +126,16 @@
 	prog_context::in, bool::out, io::di, io::uo) is det.
 
 :- pred hlds_out__write_determinism(determinism::in, io::di, io::uo) is det.
+:- func hlds_out__determinism_to_string(determinism) = string.
 
 :- pred hlds_out__write_can_fail(can_fail::in, io::di, io::uo) is det.
+:- func hlds_out__can_fail_to_string(can_fail) = string.
 
 :- pred hlds_out__write_eval_method(eval_method::in, io::di, io::uo) is det.
 
 :- pred hlds_out__write_import_status(import_status::in, io::di, io::uo)
 	is det.
+:- func hlds_out__import_status_to_string(import_status) = string.
 
 %-----------------------------------------------------------------------------%
 
@@ -277,7 +280,7 @@
 hlds_out__write_class_id(class_id(Name, Arity), !IO) :-
 	prog_out__write_sym_name_and_arity(Name / Arity, !IO).
 
-hlds_out__cons_id_to_string(cons(SymName, Arity), String) :-
+hlds_out__cons_id_to_string(cons(SymName, Arity)) = String :-
 	prog_out__sym_name_to_string(SymName, SymNameString0),
 	( string__contains_char(SymNameString0, '*') ->
 		% We need to protect against the * appearing next to a /
@@ -296,26 +299,27 @@
 	string__int_to_string(Arity, ArityString),
 	string__append_list([SymNameString, "/", ArityString], String).
 
-hlds_out__cons_id_to_string(int_const(Int), String) :-
+hlds_out__cons_id_to_string(int_const(Int)) = String :-
 	string__int_to_string(Int, String).
 
-hlds_out__cons_id_to_string(string_const(String), S) :-
+hlds_out__cons_id_to_string(string_const(String)) = S :-
 	string__append_list(["""", String, """"], S).
 
-hlds_out__cons_id_to_string(float_const(_), "<float>").
-hlds_out__cons_id_to_string(pred_const(_, _, _), "<pred>").
-hlds_out__cons_id_to_string(type_ctor_info_const(_, _, _), "<type_ctor_info>").
-hlds_out__cons_id_to_string(base_typeclass_info_const(_, _, _, _),
-	"<base_typeclass_info>").
-hlds_out__cons_id_to_string(type_info_cell_constructor(_),
-	"<type_info_cell_constructor>").
-hlds_out__cons_id_to_string(typeclass_info_cell_constructor,
-	"<typeclass_info_cell_constructor>").
-hlds_out__cons_id_to_string(tabling_pointer_const(_, _),
-	"<tabling_pointer>").
-hlds_out__cons_id_to_string(deep_profiling_proc_static(_),
-	"<deep_profiling_proc_static>").
-hlds_out__cons_id_to_string(table_io_decl(_), "<table_io_decl>").
+hlds_out__cons_id_to_string(float_const(_)) = "<float>".
+hlds_out__cons_id_to_string(pred_const(_, _, _)) = "<pred>".
+hlds_out__cons_id_to_string(type_ctor_info_const(_, _, _)) =
+	"<type_ctor_info>".
+hlds_out__cons_id_to_string(base_typeclass_info_const(_, _, _, _)) =
+	"<base_typeclass_info>".
+hlds_out__cons_id_to_string(type_info_cell_constructor(_)) =
+	"<type_info_cell_constructor>".
+hlds_out__cons_id_to_string(typeclass_info_cell_constructor) =
+	"<typeclass_info_cell_constructor>".
+hlds_out__cons_id_to_string(tabling_pointer_const(_, _)) =
+	"<tabling_pointer>".
+hlds_out__cons_id_to_string(deep_profiling_proc_static(_)) =
+	"<deep_profiling_proc_static>".
+hlds_out__cons_id_to_string(table_io_decl(_)) = "<table_io_decl>".
 
 hlds_out__write_cons_id(cons(SymName, Arity)) -->
 	prog_out__write_sym_name_and_arity(SymName / Arity).
@@ -387,12 +391,24 @@
 	io__write_int(ModeNum, !IO).
 
 hlds_out__write_simple_call_id(PredOrFunc - Name/Arity, !IO) :-
-	hlds_out__write_simple_call_id(PredOrFunc, Name, Arity, !IO).
+	Str = hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity),
+	io__write_string(Str, !IO).
 
 hlds_out__write_simple_call_id(PredOrFunc, Name/Arity, !IO) :-
-	hlds_out__write_simple_call_id(PredOrFunc, Name, Arity, !IO).
+	Str = hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity),
+	io__write_string(Str, !IO).
 
 hlds_out__write_simple_call_id(PredOrFunc, Name, Arity, !IO) :-
+	Str = hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity),
+	io__write_string(Str, !IO).
+
+hlds_out__simple_call_id_to_string(PredOrFunc - Name/Arity) =
+	hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity).
+
+hlds_out__simple_call_id_to_string(PredOrFunc, Name/Arity) =
+	hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity).
+
+hlds_out__simple_call_id_to_string(PredOrFunc, Name, Arity) = Str :-
 		% XXX when printed, promises are differentiated from
 		%     predicates or functions by module name, so the module
 		%     names `promise', `promise_exclusive', etc. should be
@@ -415,20 +431,17 @@
 	;
 		Promise = none	% no, it is really a pred or func
 	),
-
 	(
-		Promise = promise(PromiseType)
-	->
-		io__write_string("`", !IO),
-		prog_out__write_promise_type(PromiseType, !IO),
-		io__write_string("' declaration", !IO)
+		Promise = promise(PromiseType),
+		PromiseStr = promise_to_string(PromiseType),
+		Str = "`" ++ PromiseStr ++ "' declaration"
 	;
-		hlds_out__write_pred_or_func(PredOrFunc, !IO),
-		io__write_string(" `", !IO),
+		Promise = none,
+		PredOrFuncStr = pred_or_func_to_full_str(PredOrFunc),
 		hlds_out__simple_call_id_to_sym_name_and_arity(
 			PredOrFunc - Name/Arity, SymArity),
-		prog_out__write_sym_name_and_arity(SymArity, !IO),
-		io__write_string("'", !IO)
+		sym_name_and_arity_to_string(SymArity, SymArityStr),
+		Str = PredOrFuncStr ++ " `" ++ SymArityStr ++ "'"
 	).
 
 :- pred hlds_out__simple_call_id_to_sym_name_and_arity(simple_call_id::in,
@@ -438,15 +451,6 @@
 		SymName/OrigArity) :-
 	adjust_func_arity(PredOrFunc, OrigArity, Arity).
 
-hlds_out__simple_call_id_to_string(CallId, String) :-
-	hlds_out__simple_call_id_to_sym_name_and_arity(CallId, NameArity),
-	CallId = PredOrFunc - _,
-	( PredOrFunc = predicate, PorFString = "predicate"
-	; PredOrFunc = function, PorFString = "function"
-	),
-	prog_out__sym_name_and_arity_to_string(NameArity, NameArityString),
-	string__append_list([PorFString, " `", NameArityString, "'"], String).
-
 hlds_out__write_call_id(call(PredCallId), !IO) :-
 	hlds_out__write_simple_call_id(PredCallId, !IO).
 hlds_out__write_call_id(generic_call(GenericCallId), !IO) :-
@@ -599,11 +603,11 @@
 hlds_out__write_pred_or_func(function, !IO) :-
 	io__write_string("function", !IO).
 
-hlds_out__pred_or_func_to_full_str(predicate, "predicate").
-hlds_out__pred_or_func_to_full_str(function, "function").
+hlds_out__pred_or_func_to_full_str(predicate) = "predicate".
+hlds_out__pred_or_func_to_full_str(function) = "function".
 
-hlds_out__pred_or_func_to_str(predicate, "pred").
-hlds_out__pred_or_func_to_str(function, "func").
+hlds_out__pred_or_func_to_str(predicate) = "pred".
+hlds_out__pred_or_func_to_str(function) = "func".
 
 %-----------------------------------------------------------------------------%
 
@@ -2086,7 +2090,7 @@
 	io__write_string(UpdateName, !IO),
 	io__write_string("(", !IO),
 	CallId = PredOrFunc - _,
-	hlds_out__pred_or_func_to_str(PredOrFunc, PredOrFuncStr),
+	PredOrFuncStr = hlds_out__pred_or_func_to_str(PredOrFunc),
 	io__write_string(PredOrFuncStr, !IO),
 	io__write_string(" ", !IO),
 	hlds_out__simple_call_id_to_sym_name_and_arity(CallId, SymArity),
@@ -2696,39 +2700,41 @@
 		hlds_out__write_vars(Vars, VarSet, AppendVarnums, !IO)
 	).
 
-hlds_out__write_import_status(local) -->
-	io__write_string("local").
-hlds_out__write_import_status(exported) -->
-	io__write_string("exported").
-hlds_out__write_import_status(opt_exported) -->
-	io__write_string("opt_exported").
-hlds_out__write_import_status(abstract_exported) -->
-	io__write_string("abstract_exported").
-hlds_out__write_import_status(pseudo_exported) -->
-	io__write_string("pseudo_exported").
-hlds_out__write_import_status(imported(interface)) -->
-	io__write_string("imported in the interface").
-hlds_out__write_import_status(imported(implementation)) -->
-	io__write_string("imported in the implementation").
-hlds_out__write_import_status(imported(ancestor_private_interface)) -->
-	io__write_string("imported from an ancestor's private interface").
-hlds_out__write_import_status(imported(ancestor)) -->
-	io__write_string("imported by an ancestor").
-hlds_out__write_import_status(external(Status)) -->
-	io__write_string("external (and "),
-	hlds_out__write_import_status(Status),
-	io__write_string(")").
-hlds_out__write_import_status(abstract_imported) -->
-	io__write_string("abstract_imported").
-hlds_out__write_import_status(opt_imported) -->
-	io__write_string("opt_imported").
-hlds_out__write_import_status(pseudo_imported) -->
-	io__write_string("pseudo_imported").
-hlds_out__write_import_status(exported_to_submodules) -->
-	io__write_string("exported_to_submodules").
+hlds_out__write_import_status(Status, !IO) :-
+	io__write_string(hlds_out__import_status_to_string(Status), !IO).
+
+hlds_out__import_status_to_string(local) =
+	"local".
+hlds_out__import_status_to_string(exported) =
+	"exported".
+hlds_out__import_status_to_string(opt_exported) =
+	"opt_exported".
+hlds_out__import_status_to_string(abstract_exported) =
+	"abstract_exported".
+hlds_out__import_status_to_string(pseudo_exported) =
+	"pseudo_exported".
+hlds_out__import_status_to_string(imported(interface)) =
+	"imported in the interface".
+hlds_out__import_status_to_string(imported(implementation)) =
+	"imported in the implementation".
+hlds_out__import_status_to_string(imported(ancestor_private_interface)) =
+	"imported from an ancestor's private interface".
+hlds_out__import_status_to_string(imported(ancestor)) =
+	"imported by an ancestor".
+hlds_out__import_status_to_string(external(Status)) =
+	"external (and " ++ hlds_out__import_status_to_string(Status) ++ ")".
+hlds_out__import_status_to_string(abstract_imported) =
+	"abstract_imported".
+hlds_out__import_status_to_string(opt_imported) =
+	"opt_imported".
+hlds_out__import_status_to_string(pseudo_imported) =
+	"pseudo_imported".
+hlds_out__import_status_to_string(exported_to_submodules) =
+	"exported_to_submodules".
 
 :- pred hlds_out__write_type_list(list(type)::in, tvarset::in, bool::in,
 		io::di, io::uo) is det.
+
 hlds_out__write_type_list(Types, TypeVarSet, AppendVarNums) -->
 	list__foldl((pred(Type::in, di, uo) is det -->
 		mercury_output_term(Type, TypeVarSet, AppendVarNums),
@@ -3565,53 +3571,26 @@
 %		{ error("This cannot happen") }
 %	).
 
-hlds_out__write_determinism(det) -->
-	io__write_string("det").
-hlds_out__write_determinism(semidet) -->
-	io__write_string("semidet").
-hlds_out__write_determinism(nondet) -->
-	io__write_string("nondet").
-hlds_out__write_determinism(multidet) -->
-	io__write_string("multi").
-hlds_out__write_determinism(cc_nondet) -->
-	io__write_string("cc_nondet").
-hlds_out__write_determinism(cc_multidet) -->
-	io__write_string("cc_multi").
-hlds_out__write_determinism(erroneous) -->
-	io__write_string("erroneous").
-hlds_out__write_determinism(failure) -->
-	io__write_string("failure").
-
-hlds_out__write_can_fail(can_fail) -->
-	io__write_string("can_fail").
-hlds_out__write_can_fail(cannot_fail) -->
-	io__write_string("cannot_fail").
-
-hlds_out__write_eval_method(eval_normal) -->
-	io__write_string("normal").
-hlds_out__write_eval_method(eval_loop_check) -->
-	io__write_string("loop_check").
-hlds_out__write_eval_method(eval_memo) -->
-	io__write_string("memo").
-hlds_out__write_eval_method(eval_minimal) -->
-	io__write_string("minimal").
-hlds_out__write_eval_method(eval_table_io(IsDecl, IsUnitize)) -->
-	io__write_string("table_io("),
-	(
-		{ IsDecl = table_io_decl },
-		io__write_string("decl, ")
-	;
-		{ IsDecl = table_io_proc },
-		io__write_string("proc, ")
-	),
-	(
-		{ IsUnitize = table_io_unitize },
-		io__write_string("unitize")
-	;
-		{ IsUnitize = table_io_alone },
-		io__write_string("alone")
-	),
-	io__write_string(")").
+hlds_out__write_determinism(Detism, !IO) :-
+	io__write_string(hlds_out__determinism_to_string(Detism), !IO).
+
+hlds_out__determinism_to_string(det) = "det".
+hlds_out__determinism_to_string(semidet) = "semidet".
+hlds_out__determinism_to_string(nondet) = "nondet".
+hlds_out__determinism_to_string(multidet) = "multi".
+hlds_out__determinism_to_string(cc_nondet) = "cc_nondet".
+hlds_out__determinism_to_string(cc_multidet) = "cc_multi".
+hlds_out__determinism_to_string(erroneous) = "erroneous".
+hlds_out__determinism_to_string(failure) = "failure".
+
+hlds_out__write_can_fail(CanFail, !IO) :-
+	io__write_string(hlds_out__can_fail_to_string(CanFail), !IO).
+
+hlds_out__can_fail_to_string(can_fail) = "can_fail".
+hlds_out__can_fail_to_string(cannot_fail) = "cannot_fail".
+
+hlds_out__write_eval_method(EvalMethod, !IO) :-
+	io__write_string(eval_method_to_string(EvalMethod), !IO).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/inlining.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inlining.m,v
retrieving revision 1.116
diff -u -b -r1.116 inlining.m
--- compiler/inlining.m	23 Mar 2004 10:52:04 -0000	1.116
+++ compiler/inlining.m	3 Apr 2004 15:43:46 -0000
@@ -90,14 +90,11 @@
 
 :- import_module bool, io, list, map.
 
-:- pred inlining(module_info, module_info, io__state, io__state).
-:- mode inlining(in, out, di, uo) is det.
+:- pred inlining(module_info::in, module_info::out, io::di, io::uo) is det.
 
-:- pred inlining__is_simple_clause_list(list(clause), int).
-:- mode inlining__is_simple_clause_list(in, in) is semidet.
+:- pred inlining__is_simple_clause_list(list(clause)::in, int::in) is semidet.
 
-:- pred inlining__is_simple_goal(hlds_goal, int).
-:- mode inlining__is_simple_goal(in, in) is semidet.
+:- pred inlining__is_simple_goal(hlds_goal::in, int::in) is semidet.
 
 	% inlining__do_inline_call(UnivQVars, Args,
 	%	CalledPredInfo, CalledProcInfo,
@@ -109,41 +106,35 @@
 	% for the called goal and various information about the variables
 	% and types in the procedure currently being analysed, rename the
 	% goal for the called procedure so that it can be inlined.
-:- pred inlining__do_inline_call(list(tvar), list(prog_var),
-		pred_info, proc_info, prog_varset, prog_varset,
-		map(prog_var, type), map(prog_var, type),
-		tvarset, tvarset, map(tvar, type_info_locn), 
-		map(tvar, type_info_locn), hlds_goal).
-:- mode inlining__do_inline_call(in, in, in, in, in, out, in, out,
-	in, out, in, out, out) is det.
+:- pred inlining__do_inline_call(list(tvar)::in, list(prog_var)::in,
+	pred_info::in, proc_info::in, prog_varset::in, prog_varset::out,
+	vartypes::in, vartypes::out, tvarset::in, tvarset::out,
+	map(tvar, type_info_locn)::in, map(tvar, type_info_locn)::out,
+	hlds_goal::out) is det.
 
 	% inlining__get_type_substitution(CalleeArgTypes, CallerArgTypes,
 	%	HeadTypeParams, CalleeExistQTVars, TypeSubn).
 	%
 	% Work out a type substitution to map the callee's argument
 	% types into the caller's.
-:- pred inlining__get_type_substitution(list(type), list(type),
-		head_type_params, list(tvar), map(tvar, type)).
-:- mode inlining__get_type_substitution(in, in, in, in, out) is det.
+:- pred inlining__get_type_substitution(list(type)::in, list(type)::in,
+	head_type_params::in, list(tvar)::in, map(tvar, type)::out) is det.
 
 	% inlining__rename_goal(CalledProcHeadVars, CallArgs,
 	%	CallerVarSet0, CalleeVarSet, CallerVarSet,
 	%	CallerVarTypes0, CalleeVarTypes, CallerVarTypes,
 	%	VarRenaming, CalledGoal, RenamedGoal).
-:- pred inlining__rename_goal(list(prog_var), list(prog_var), prog_varset,
-		prog_varset, prog_varset, map(prog_var, type),
-		map(prog_var, type), map(prog_var, type),
-		map(prog_var, prog_var), hlds_goal, hlds_goal). 
-:- mode inlining__rename_goal(in, in, in, in, out,
-		in, in, out, out, in, out) is det.
+:- pred inlining__rename_goal(list(prog_var)::in, list(prog_var)::in,
+	prog_varset::in, prog_varset::in, prog_varset::out,
+	vartypes::in, vartypes::in, vartypes::out,
+	map(prog_var, prog_var)::out, hlds_goal::in, hlds_goal::out) is det.
 
 	% inlining__can_inline_proc(PredId, ProcId, BuiltinState,
 	% 	InlinePromisedPure, CallingPredMarkers, ModuleInfo).
 	%
 	% Determine whether a predicate can be inlined.
-:- pred inlining__can_inline_proc(pred_id, proc_id, builtin_state,
-		bool, pred_markers, module_info).
-:- mode inlining__can_inline_proc(in, in, in, in, in, in) is semidet.
+:- pred inlining__can_inline_proc(pred_id::in, proc_id::in, builtin_state::in,
+	bool::in, pred_markers::in, module_info::in) is semidet.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -191,7 +182,7 @@
 						
 		).
 
-inlining(ModuleInfo0, ModuleInfo) -->
+inlining(!ModuleInfo, !IO) :-
 		%
 		% Package up all the inlining options
 		% - whether to inline simple conj's of builtins
@@ -207,17 +198,20 @@
 		%   this threshold then we don't inline it.
 		% - whether we're in an MLDS grade
 		%
-	globals__io_lookup_bool_option(inline_simple, Simple),
-	globals__io_lookup_bool_option(inline_single_use, SingleUse),
-	globals__io_lookup_int_option(inline_compound_threshold,
+	globals__io_get_globals(Globals, !IO),
+	globals__lookup_bool_option(Globals, inline_simple, Simple),
+	globals__lookup_bool_option(Globals, inline_single_use, SingleUse),
+	globals__lookup_int_option(Globals, inline_compound_threshold,
 							CompoundThreshold),
-	globals__io_lookup_int_option(inline_simple_threshold, SimpleThreshold),
-	globals__io_lookup_int_option(inline_vars_threshold, VarThreshold),
-	globals__io_lookup_bool_option(highlevel_code, HighLevelCode),
-	globals__io_get_trace_level(TraceLevel),
-	{ AnyTracing = bool__not(given_trace_level_is_none(TraceLevel)) },
-	{ Params = params(Simple, SingleUse, CompoundThreshold,
-		SimpleThreshold, VarThreshold, HighLevelCode, AnyTracing) },
+	globals__lookup_int_option(Globals, inline_simple_threshold,
+		SimpleThreshold),
+	globals__lookup_int_option(Globals, inline_vars_threshold,
+		VarThreshold),
+	globals__lookup_bool_option(Globals, highlevel_code, HighLevelCode),
+	globals__io_get_trace_level(TraceLevel, !IO),
+	AnyTracing = bool__not(given_trace_level_is_none(TraceLevel)),
+	Params = params(Simple, SingleUse, CompoundThreshold,
+		SimpleThreshold, VarThreshold, HighLevelCode, AnyTracing),
 
 		%
 		% Get the usage counts for predicates
@@ -225,13 +219,13 @@
 		% or --inline-compound-threshold has been specified)
 		%
 	(
-		( { SingleUse = yes }
-		; { CompoundThreshold > 0 }
+		( SingleUse = yes
+		; CompoundThreshold > 0
 		)
 	->
-		{ dead_proc_elim__analyze(ModuleInfo0, NeededMap) }
+		dead_proc_elim__analyze(!.ModuleInfo, NeededMap)
 	;
-		{ map__init(NeededMap) }
+		map__init(NeededMap)
 	),
 
 		% build the call graph and extract the topological sort
@@ -245,35 +239,32 @@
 		% to break the cycle so that the procedure(s) that are called
 		% by higher SCCs are processed last, but we do not implement
 		% that yet.
-	{ module_info_ensure_dependency_info(ModuleInfo0, ModuleInfo1) },
-	{ module_info_dependency_info(ModuleInfo1, DepInfo) },
-	{ hlds_dependency_info_get_dependency_ordering(DepInfo, SCCs) },
-	{ list__condense(SCCs, PredProcs) },
-	{ set__init(InlinedProcs0) },
+	module_info_ensure_dependency_info(!ModuleInfo),
+	module_info_dependency_info(!.ModuleInfo, DepInfo),
+	hlds_dependency_info_get_dependency_ordering(DepInfo, SCCs),
+	list__condense(SCCs, PredProcs),
+	set__init(InlinedProcs0),
 	inlining__do_inlining(PredProcs, NeededMap, Params, InlinedProcs0,
-		ModuleInfo1, ModuleInfo2),
+		!ModuleInfo, !IO),
 
 		% The dependency graph is now out of date and 
 		% needs to be rebuilt.
-	{ module_info_clobber_dependency_info(ModuleInfo2, ModuleInfo) }.
+	module_info_clobber_dependency_info(!ModuleInfo).
 
-:- pred inlining__do_inlining(list(pred_proc_id), needed_map, inline_params,
-		set(pred_proc_id), module_info, module_info,
-		io__state, io__state).
-:- mode inlining__do_inlining(in, in, in, in, in, out, di, uo) is det.
-
-inlining__do_inlining([], _Needed, _Params, _Inlined, Module, Module) --> [].
-inlining__do_inlining([PPId | PPIds], Needed, Params, Inlined0,
-		Module0, Module) -->
-	inlining__in_predproc(PPId, Inlined0, Params, Module0, Module1),
-	inlining__mark_predproc(PPId, Needed, Params, Module1,
-		Inlined0, Inlined1),
-	inlining__do_inlining(PPIds, Needed, Params, Inlined1, Module1, Module).
-
-:- pred inlining__mark_predproc(pred_proc_id, needed_map, inline_params,
-		module_info, set(pred_proc_id), set(pred_proc_id),
-		io__state, io__state).
-:- mode inlining__mark_predproc(in, in, in, in, in, out, di, uo) is det.
+:- pred inlining__do_inlining(list(pred_proc_id)::in, needed_map::in,
+	inline_params::in, set(pred_proc_id)::in,
+	module_info::in, module_info::out, io::di, io::uo) is det.
+
+inlining__do_inlining([], _Needed, _Params, _Inlined, !Module, !IO).
+inlining__do_inlining([PPId | PPIds], Needed, Params, !.Inlined, !Module,
+		!IO) :-
+	inlining__in_predproc(PPId, !.Inlined, Params, !Module, !IO),
+	inlining__mark_predproc(PPId, Needed, Params, !.Module, !Inlined, !IO),
+	inlining__do_inlining(PPIds, Needed, Params, !.Inlined, !Module, !IO).
+
+:- pred inlining__mark_predproc(pred_proc_id::in, needed_map::in,
+	inline_params::in, module_info::in,
+	set(pred_proc_id)::in, set(pred_proc_id)::out, io::di, io::uo) is det.
 
 %
 % This predicate effectively adds implicit `pragma inline'
@@ -281,47 +272,47 @@
 %
 
 inlining__mark_predproc(PredProcId, NeededMap, Params, ModuleInfo, 
-		InlinedProcs0, InlinedProcs) -->
+		!InlinedProcs, !IO) :-
 	(
-		{ Simple = Params ^ simple },
-		{ SingleUse = Params ^ single_use },
-		{ CompoundThreshold = Params ^ size_threshold },
-		{ SimpleThreshold = Params ^ simple_goal_threshold },
-		{ PredProcId = proc(PredId, ProcId) },
-		{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
-		{ pred_info_procedures(PredInfo, Procs) },
-		{ map__lookup(Procs, ProcId, ProcInfo) },
-		{ proc_info_goal(ProcInfo, CalledGoal) },
-		{ Entity = proc(PredId, ProcId) },
+		Simple = Params ^ simple,
+		SingleUse = Params ^ single_use,
+		CompoundThreshold = Params ^ size_threshold,
+		SimpleThreshold = Params ^ simple_goal_threshold,
+		PredProcId = proc(PredId, ProcId),
+		module_info_pred_info(ModuleInfo, PredId, PredInfo),
+		pred_info_procedures(PredInfo, Procs),
+		map__lookup(Procs, ProcId, ProcInfo),
+		proc_info_goal(ProcInfo, CalledGoal),
+		Entity = proc(PredId, ProcId),
 
 		%
 		% the heuristic represented by the following code
 		% could be improved
 		%
 		(
-			{ Simple = yes },
-			{ inlining__is_simple_goal(CalledGoal,
-				SimpleThreshold) }
-		;
-			{ CompoundThreshold > 0 },
-			{ map__search(NeededMap, Entity, Needed) },
-			{ Needed = yes(NumUses) },
-			{ goal_size(CalledGoal, Size) },
-			{ Size * NumUses =< CompoundThreshold }
-		;
-			{ SingleUse = yes },
-			{ map__search(NeededMap, Entity, Needed) },
-			{ Needed = yes(NumUses) },
-			{ NumUses = 1 }
+			Simple = yes,
+			inlining__is_simple_goal(CalledGoal,
+				SimpleThreshold)
+		;
+			CompoundThreshold > 0,
+			map__search(NeededMap, Entity, Needed),
+			Needed = yes(NumUses),
+			goal_size(CalledGoal, Size),
+			Size * NumUses =< CompoundThreshold
+		;
+			SingleUse = yes,
+			map__search(NeededMap, Entity, Needed),
+			Needed = yes(NumUses),
+			NumUses = 1
 		),
 		% Don't inline recursive predicates
 		% (unless explicitly requested)
-		{ \+ goal_calls(CalledGoal, PredProcId) }
+		\+ goal_calls(CalledGoal, PredProcId)
 	->
 		inlining__mark_proc_as_inlined(PredProcId, ModuleInfo,
-			InlinedProcs0, InlinedProcs)
+			!InlinedProcs, !IO)
 	;
-		{ InlinedProcs = InlinedProcs0 }
+		true
 	).
 
 	% this heuristic is used for both local and intermodule inlining
@@ -376,19 +367,18 @@
 	inlining__is_flat_simple_goal(Goal),
 	inlining__is_flat_simple_goal_list(Goals).
 
-:- pred inlining__mark_proc_as_inlined(pred_proc_id, module_info,
-	set(pred_proc_id), set(pred_proc_id), io__state, io__state).
-:- mode inlining__mark_proc_as_inlined(in, in, in, out, di, uo) is det.
+:- pred inlining__mark_proc_as_inlined(pred_proc_id::in, module_info::in,
+	set(pred_proc_id)::in, set(pred_proc_id)::out, io::di, io::uo) is det.
 
 inlining__mark_proc_as_inlined(proc(PredId, ProcId), ModuleInfo,
-		InlinedProcs0, InlinedProcs) -->
-	{ set__insert(InlinedProcs0, proc(PredId, ProcId), InlinedProcs) },
-	{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
-	( { pred_info_requested_inlining(PredInfo) } ->
-		[]
+		!InlinedProcs, !IO) :-
+	set__insert(!.InlinedProcs, proc(PredId, ProcId), !:InlinedProcs),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	( pred_info_requested_inlining(PredInfo) ->
+		true
 	;
 		write_proc_progress_message("% Inlining ", PredId, ProcId,
-			ModuleInfo)
+			ModuleInfo, !IO)
 	).
 
 %-----------------------------------------------------------------------------%
@@ -418,7 +408,7 @@
 			% the following fields are updated as a result
 			% of inlining
 		prog_varset,		% varset
-		map(prog_var, type),	% variable types
+		vartypes,		% variable types
 		tvarset,		% type variables
 		map(tvar, type_info_locn),% type_info varset, a mapping from 
 					% type variables to variables
@@ -433,9 +423,9 @@
 					% any subgoal.
 	).
 
-:- pred inlining__in_predproc(pred_proc_id, set(pred_proc_id), inline_params,
-		module_info, module_info, io__state, io__state).
-:- mode inlining__in_predproc(in, in, in, in, out, di, uo) is det.
+:- pred inlining__in_predproc(pred_proc_id::in, set(pred_proc_id)::in,
+	inline_params::in, module_info::in, module_info::out,
+	io::di, io::uo) is det.
 
 inlining__in_predproc(PredProcId, InlinedProcs, Params, !ModuleInfo, !IO) :-
 	VarThresh = Params ^ var_threshold,
@@ -527,45 +517,81 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred inlining__inlining_in_goal(hlds_goal, hlds_goal, inline_info,
-		inline_info).
-:- mode inlining__inlining_in_goal(in, out, in, out) is det.
-
-inlining__inlining_in_goal(conj(Goals0) - GoalInfo, conj(Goals) - GoalInfo) -->
-	inlining__inlining_in_conj(Goals0, Goals).
-
-inlining__inlining_in_goal(par_conj(Goals0) - GoalInfo,
-		par_conj(Goals) - GoalInfo) -->
-	inlining__inlining_in_disj(Goals0, Goals).
-
-inlining__inlining_in_goal(disj(Goals0) - GoalInfo, disj(Goals) - GoalInfo) -->
-	inlining__inlining_in_disj(Goals0, Goals).
-
-inlining__inlining_in_goal(switch(Var, Det, Cases0) - GoalInfo,
-		switch(Var, Det, Cases) - GoalInfo) -->
-	inlining__inlining_in_cases(Cases0, Cases).
-
-inlining__inlining_in_goal(
-		if_then_else(Vars, Cond0, Then0, Else0) - GoalInfo,
-		if_then_else(Vars, Cond, Then, Else) - GoalInfo) -->
-	inlining__inlining_in_goal(Cond0, Cond),
-	inlining__inlining_in_goal(Then0, Then),
-	inlining__inlining_in_goal(Else0, Else).
-
-inlining__inlining_in_goal(not(Goal0) - GoalInfo, not(Goal) - GoalInfo) -->
-	inlining__inlining_in_goal(Goal0, Goal).
-
-inlining__inlining_in_goal(some(Vars, CanRemove, Goal0) - GoalInfo,
-		some(Vars, CanRemove, Goal) - GoalInfo) -->
-	inlining__inlining_in_goal(Goal0, Goal).
+:- pred inlining__inlining_in_goal(hlds_goal::in, hlds_goal::out,
+	inline_info::in, inline_info::out) is det.
 
-inlining__inlining_in_goal(call(PredId, ProcId, ArgVars, Builtin, Context,
-		Sym) - GoalInfo0, Goal - GoalInfo, InlineInfo0, InlineInfo) :-
+inlining__inlining_in_goal(Goal0 - GoalInfo0, Goal - GoalInfo, !Info) :-
+	(
+		Goal0 = conj(Goals0),
+		inlining__inlining_in_conj(Goals0, Goals, !Info),
+		Goal = conj(Goals),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = par_conj(Goals0),
+		inlining__inlining_in_disj(Goals0, Goals, !Info),
+		Goal = par_conj(Goals),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = disj(Goals0),
+		inlining__inlining_in_disj(Goals0, Goals, !Info),
+		Goal = disj(Goals),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = switch(Var, Det, Cases0),
+		inlining__inlining_in_cases(Cases0, Cases, !Info),
+		Goal = switch(Var, Det, Cases),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = if_then_else(Vars, Cond0, Then0, Else0),
+		inlining__inlining_in_goal(Cond0, Cond, !Info),
+		inlining__inlining_in_goal(Then0, Then, !Info),
+		inlining__inlining_in_goal(Else0, Else, !Info),
+		Goal = if_then_else(Vars, Cond, Then, Else),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = not(SubGoal0),
+		inlining__inlining_in_goal(SubGoal0, SubGoal, !Info),
+		Goal = not(SubGoal),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = some(Vars, CanRemove, SubGoal0),
+		inlining__inlining_in_goal(SubGoal0, SubGoal, !Info),
+		Goal = some(Vars, CanRemove, SubGoal),
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = generic_call(_, _, _, _),
+		Goal = Goal0,
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = unify(_, _, _, _, _),
+		Goal = Goal0,
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = foreign_proc(_, _, _, _, _, _, _),
+		Goal = Goal0,
+		GoalInfo = GoalInfo0
+	;
+		Goal0 = shorthand(_),
+		% these should have been expanded out by now
+		error("inlining__inlining_in_goal: unexpected shorthand")
+	;
+		Goal0 = call(PredId, ProcId, ArgVars, Builtin, Context, Sym),
+		inlining__inlining_in_call(PredId, ProcId, ArgVars, Builtin,
+			Context, Sym, Goal, GoalInfo0, GoalInfo, !Info)
+	).
 
-	InlineInfo0 = inline_info(VarThresh, HighLevelCode, AnyTracing,
+:- pred inlining__inlining_in_call(pred_id::in, proc_id::in,
+	list(prog_var)::in, builtin_state::in, maybe(call_unify_context)::in,
+	sym_name::in, hlds_goal_expr::out,
+	hlds_goal_info::in, hlds_goal_info::out,
+	inline_info::in, inline_info::out) is det.
+
+inlining__inlining_in_call(PredId, ProcId, ArgVars, Builtin,
+		Context, Sym, Goal, GoalInfo0, GoalInfo, !Info) :-
+	!.Info = inline_info(VarThresh, HighLevelCode, AnyTracing,
 		InlinedProcs, ModuleInfo, HeadTypeParams, Markers,
 		VarSet0, VarTypes0, TypeVarSet0, TypeInfoVarMap0,
-		DidInlining0, Requantify0, DetChanged0, PurityChanged0),
+		_DidInlining0, Requantify0, DetChanged0, PurityChanged0),
 
 	% should we inline this call?
 	(
@@ -622,37 +648,15 @@
 			DetChanged = DetChanged0
 		;
 			DetChanged = yes
-		)
-	;
-		Goal = call(PredId, ProcId, ArgVars, Builtin, Context, Sym),
-		GoalInfo = GoalInfo0,
-		VarSet = VarSet0,
-		VarTypes = VarTypes0,
-		TypeVarSet = TypeVarSet0,
-		TypeInfoVarMap = TypeInfoVarMap0,
-		DidInlining = DidInlining0,
-		Requantify = Requantify0,
-		DetChanged = DetChanged0,
-		PurityChanged = PurityChanged0
 	),
-	InlineInfo = inline_info(VarThresh, HighLevelCode, AnyTracing,
+		!:Info = inline_info(VarThresh, HighLevelCode, AnyTracing,
 		InlinedProcs, ModuleInfo, HeadTypeParams, Markers,
-		VarSet, VarTypes, TypeVarSet, TypeInfoVarMap, DidInlining,
-		Requantify, DetChanged, PurityChanged).
-
-inlining__inlining_in_goal(generic_call(A, B, C, D) - GoalInfo,
-		generic_call(A, B, C, D) - GoalInfo) --> [].
-
-inlining__inlining_in_goal(unify(A, B, C, D, E) - GoalInfo,
-		unify(A, B, C, D, E) - GoalInfo) --> [].
-
-inlining__inlining_in_goal(
-		foreign_proc(A, B, C, D, E, F, G) - GoalInfo,
-		foreign_proc(A, B, C, D, E, F, G) - GoalInfo) --> [].
-
-inlining__inlining_in_goal(shorthand(_) - _, _) -->
-	% these should have been expanded out by now
-	{ error("inlining__inlining_in_goal: unexpected shorthand") }.
+			VarSet, VarTypes, TypeVarSet, TypeInfoVarMap,
+			DidInlining, Requantify, DetChanged, PurityChanged)
+	;
+		Goal = call(PredId, ProcId, ArgVars, Builtin, Context, Sym),
+		GoalInfo = GoalInfo0
+	).
 
 %-----------------------------------------------------------------------------%
 
@@ -792,42 +796,39 @@
 	% inlining__inlining_in_disj is used for both disjunctions and
 	% parallel conjunctions.
 
-:- pred inlining__inlining_in_disj(list(hlds_goal), list(hlds_goal), 
-		inline_info, inline_info).
-:- mode inlining__inlining_in_disj(in, out, in, out) is det.
+:- pred inlining__inlining_in_disj(list(hlds_goal)::in, list(hlds_goal)::out,
+	inline_info::in, inline_info::out) is det.
 
-inlining__inlining_in_disj([], []) --> [].
-inlining__inlining_in_disj([Goal0 | Goals0], [Goal | Goals]) -->
-	inlining__inlining_in_goal(Goal0, Goal),
-	inlining__inlining_in_disj(Goals0, Goals).
+inlining__inlining_in_disj([], [], !Info).
+inlining__inlining_in_disj([Goal0 | Goals0], [Goal | Goals], !Info) :-
+	inlining__inlining_in_goal(Goal0, Goal, !Info),
+	inlining__inlining_in_disj(Goals0, Goals, !Info).
 
 %-----------------------------------------------------------------------------%
 
-:- pred inlining__inlining_in_cases(list(case), list(case), inline_info, 
-		inline_info).
-:- mode inlining__inlining_in_cases(in, out, in, out) is det.
+:- pred inlining__inlining_in_cases(list(case)::in, list(case)::out,
+	inline_info::in, inline_info::out) is det.
 
-inlining__inlining_in_cases([], []) --> [].
+inlining__inlining_in_cases([], [], !Info).
 inlining__inlining_in_cases([case(Cons, Goal0) | Goals0],
-		[case(Cons, Goal) | Goals]) -->
-	inlining__inlining_in_goal(Goal0, Goal),
-	inlining__inlining_in_cases(Goals0, Goals).
+		[case(Cons, Goal) | Goals], !Info) :-
+	inlining__inlining_in_goal(Goal0, Goal, !Info),
+	inlining__inlining_in_cases(Goals0, Goals, !Info).
 
 %-----------------------------------------------------------------------------%
 
-:- pred inlining__inlining_in_conj(list(hlds_goal), list(hlds_goal),
-		inline_info, inline_info).
-:- mode inlining__inlining_in_conj(in, out, in, out) is det.
+:- pred inlining__inlining_in_conj(list(hlds_goal)::in, list(hlds_goal)::out,
+	inline_info::in, inline_info::out) is det.
 
 	% Since a single goal may become a conjunction,
 	% we flatten the conjunction as we go.
 
-inlining__inlining_in_conj([], []) --> [].
-inlining__inlining_in_conj([Goal0 | Goals0], Goals) -->
-	inlining__inlining_in_goal(Goal0, Goal1),
-	{ goal_to_conj_list(Goal1, Goal1List) },
-	inlining__inlining_in_conj(Goals0, Goals1),
-	{ list__append(Goal1List, Goals1, Goals) }.
+inlining__inlining_in_conj([], [], !Info).
+inlining__inlining_in_conj([Goal0 | Goals0], Goals, !Info) :-
+	inlining__inlining_in_goal(Goal0, Goal1, !Info),
+	goal_to_conj_list(Goal1, Goal1List),
+	inlining__inlining_in_conj(Goals0, Goals1, !Info),
+	list__append(Goal1List, Goals1, Goals).
 
 %-----------------------------------------------------------------------------%
 
@@ -842,10 +843,9 @@
 	% for this procedure, or the procedure was marked by
 	% inlining__mark_predproc as having met its heuristic.
 
-:- pred inlining__should_inline_proc(pred_id, proc_id, builtin_state,
-	bool, bool, set(pred_proc_id), pred_markers, module_info).
-:- mode inlining__should_inline_proc(in, in, in, in, in, in, in, in)
-	is semidet.
+:- pred inlining__should_inline_proc(pred_id::in, proc_id::in,
+	builtin_state::in, bool::in, bool::in, set(pred_proc_id)::in,
+	pred_markers::in, module_info::in) is semidet.
 
 inlining__should_inline_proc(PredId, ProcId, BuiltinState, HighLevelCode,
 		_Tracing, InlinedProcs, CallingPredMarkers, ModuleInfo) :-
@@ -871,9 +871,8 @@
 		HighLevelCode, InlinePromisedPure,
 		CallingPredMarkers, ModuleInfo).
 
-:- pred inlining__can_inline_proc(pred_id, proc_id, builtin_state, bool,
-	bool, pred_markers, module_info).
-:- mode inlining__can_inline_proc(in, in, in, in, in, in, in) is semidet.
+:- pred inlining__can_inline_proc(pred_id::in, proc_id::in, builtin_state::in,
+	bool::in, bool::in, pred_markers::in, module_info::in) is semidet.
 
 inlining__can_inline_proc(PredId, ProcId, BuiltinState, HighLevelCode,
 		InlinePromisedPure, CallingPredMarkers, ModuleInfo) :-
@@ -965,7 +964,9 @@
 	% supports inline code in that language.
 :- pred ok_to_inline_language(foreign_language::in, compilation_target::in)
 	is semidet.
+
 ok_to_inline_language(c, c).
+
 % ok_to_inline_language(il, il). % 
 % XXX we need to fix the handling of parameter marhsalling for inlined code
 % before we can enable this -- see the comments in
Index: compiler/llds.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds.m,v
retrieving revision 1.298
diff -u -b -r1.298 llds.m
--- compiler/llds.m	23 Mar 2004 10:52:05 -0000	1.298
+++ compiler/llds.m	3 Apr 2004 11:53:37 -0000
@@ -53,13 +53,13 @@
 %
 :- type c_file	
 	--->	c_file(
-			module_name,
-			foreign_decl_info,
-			list(user_foreign_code),
-			list(foreign_export),
-			list(comp_gen_c_var),
-			list(comp_gen_c_data),
-			list(comp_gen_c_module)
+			cfile_modulename	:: module_name,
+			cfile_foreign_decl	:: foreign_decl_info,
+			cfile_foreign_code	:: list(user_foreign_code),
+			cfile_foreign_export	:: list(foreign_export),
+			cfile_vars		:: list(comp_gen_c_var),
+			cfile_data		:: list(comp_gen_c_data),
+			cfile_code		:: list(comp_gen_c_module)
 		).
 
 	% Global variables generated by the compiler.
@@ -138,13 +138,19 @@
 
 :- type c_procedure
 	--->	c_procedure(
-			string,			% predicate name
-			int,			% arity
-			pred_proc_id,		% the pred_proc_id this code
-			list(instruction),	% the code for this procedure
-			proc_label,		% proc_label of this procedure
-			counter,		% source for new label numbers
-			may_alter_rtti		% The compiler is allowed to
+			cproc_name		:: string,
+						% predicate name
+			cproc_arity		:: int,
+			cproc_id		:: pred_proc_id,
+						% the pred_proc_id this code
+			cproc_code		:: list(instruction),
+						% the code for this procedure
+			cproc_proc_label	:: proc_label,
+						% proc_label of this procedure
+			cproc_label_nums	:: counter,
+						% source for new label numbers
+			cproc_may_alter_rtti	:: may_alter_rtti
+						% The compiler is allowed to
 						% perform optimizations on this
 						% c_procedure that could alter
 						% RTTI information (e.g. the
@@ -456,12 +462,11 @@
 			% and runtime/mercury_context.{c,h} for further
 			% information about synchronisation terms.)
 
-	;	join_and_continue(lval, label)
+	;	join_and_continue(lval, label).
 			% Signal that this thread of execution has finished
 			% in the current parallel conjunction, then branch to
 			% the given label. The synchronisation
 			% term is specified by the given lval.
-	.
 
 :- type nondet_frame_info
 	--->	temp_frame(
@@ -572,8 +577,7 @@
 	;	solve
 	;	exception
 	;	retry
-	;	gc
-	.
+	;	gc.
 
 	% Each call instruction has a list of liveinfo, which stores
 	% information about which variables are live after the call
--------------------------------------------------------------------------
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