[m-dev.] for review: consistency about typeinfo liveness

Zoltan Somogyi zs at cs.mu.OZ.AU
Mon Aug 7 18:46:01 AEST 2000


This diff is the clean fix for the problem that broke debugging over the
weekend. For review by Tyson.

Make sure that all parts of the compiler use a consistent idea of which
predicates should have typeinfo liveness applied to their bodies when the
relevant option is set. This set is all predicates except the few in
the builtin modules which do not have the required arguments.

compiler/hlds_pred.m:
	Expand the interface of the should_use_typeinfo_liveness family of
	predicates to include an id of the predicate in question, to enable
	them to test whether the pred is a no_type_info_builtin.

compiler/hlds_pred.m:
compiler/polymorphism.m:
	Move the list of no_type_info_builtins from polymorphism to hlds_pred,
	since body_should_use_typeinfo_liveness also needs it now.

compiler/*.m:
	Minor changes to pass the right arguments to predicates of the
	should_use_typeinfo_liveness family, directly or indirectly.

cvs diff: Diffing .
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/accumulator.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/accumulator.m,v
retrieving revision 1.15
diff -u -b -r1.15 accumulator.m
--- compiler/accumulator.m	2000/08/03 08:46:10	1.15
+++ compiler/accumulator.m	2000/08/07 00:07:56
@@ -1555,7 +1555,8 @@
 	proc_info_set_vartypes(OrigProcInfo2, VarTypes, OrigProcInfo3),
 
 	module_info_globals(ModuleInfo1, Globals),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+	body_should_use_typeinfo_liveness(OrigPredInfo, Globals,
+		TypeInfoLiveness),
 	OrigProcInfo = requantify_procedure(TypeInfoLiveness, OrigProcInfo3),
 
 	update_accumulator_pred(AccPredId, AccProcId, AccGoal,
@@ -1964,7 +1965,7 @@
 	proc_info_set_goal(ProcInfo0, AccGoal, ProcInfo),
 
 	module_info_globals(ModuleInfo0, Globals),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeInfoLiveness),
 	module_info_set_pred_proc_info(ModuleInfo0, NewPredId, NewProcId,
 		PredInfo, requantify_procedure(TypeInfoLiveness, ProcInfo),
 		ModuleInfo).
Index: compiler/call_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/call_gen.m,v
retrieving revision 1.141
diff -u -b -r1.141 call_gen.m
--- compiler/call_gen.m	2000/08/03 08:46:11	1.141
+++ compiler/call_gen.m	2000/08/07 00:09:46
@@ -583,8 +583,12 @@
 call_gen__save_variables(OutArgs, Code) -->
 	code_info__get_known_variables(Variables0),
 	{ set__list_to_set(Variables0, Vars0) },
+	code_info__get_module_info(ModuleInfo),
+	code_info__get_pred_id(PredId),
+	{ module_info_pred_info(ModuleInfo, PredId, PredInfo) },
 	code_info__get_globals(Globals),
-	{ body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness) },
+	{ body_should_use_typeinfo_liveness(PredInfo, Globals,
+		TypeInfoLiveness) },
 	code_info__get_proc_info(ProcInfo),
 	{ proc_info_vartypes(ProcInfo, VarTypes) },
 	{ proc_info_typeinfo_varmap(ProcInfo, TVarMap) },
Index: compiler/cse_detection.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/cse_detection.m,v
retrieving revision 1.60
diff -u -b -r1.60 cse_detection.m
--- compiler/cse_detection.m	2000/08/03 08:46:13	1.60
+++ compiler/cse_detection.m	2000/08/07 00:10:00
@@ -155,7 +155,8 @@
 		proc_info_typeinfo_varmap(ProcInfo0, TVarMap),
 
 		module_info_globals(ModuleInfo0, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo0, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_clause_body(HeadVars, Goal1, Varset1,
 			VarTypes1, TVarMap, TypeInfoLiveness,
 			Goal, Varset, VarTypes, _Warnings),
Index: compiler/deforest.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/deforest.m,v
retrieving revision 1.13
diff -u -b -r1.13 deforest.m
--- compiler/deforest.m	2000/08/03 08:46:14	1.13
+++ compiler/deforest.m	2000/08/07 00:58:01
@@ -118,7 +118,7 @@
 	( { Changed = yes } ->
 		pd_info_get_module_info(ModuleInfo2),
 		{ module_info_globals(ModuleInfo2, Globals0) },
-		{ body_should_use_typeinfo_liveness(Globals0,
+		{ body_should_use_typeinfo_liveness(PredInfo0, Globals0,
 			TypeInfoLiveness) },
 		{ requantify_proc(TypeInfoLiveness, ProcInfo2, ProcInfo3) },
 		{ proc_info_goal(ProcInfo3, Goal3) },
@@ -126,8 +126,9 @@
 			ModuleInfo2, InstMap0) },
 		{ proc_info_vartypes(ProcInfo3, VarTypes) },
 		{ proc_info_typeinfo_varmap(ProcInfo3, TVarMap) },
-		{ recompute_instmap_delta(yes, Goal3, Goal, VarTypes,
-			TVarMap, InstMap0, ModuleInfo2, ModuleInfo3) },
+		{ recompute_instmap_delta(yes, PredInfo0, Goal3, Goal,
+			VarTypes, TVarMap, InstMap0,
+			ModuleInfo2, ModuleInfo3) },
 		pd_info_set_module_info(ModuleInfo3),
 
 		pd_info_get_pred_info(PredInfo),
Index: compiler/follow_code.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/follow_code.m,v
retrieving revision 1.55
diff -u -b -r1.55 follow_code.m
--- compiler/follow_code.m	2000/08/03 08:46:14	1.55
+++ compiler/follow_code.m	2000/08/07 00:44:42
@@ -16,15 +16,12 @@
 :- import_module hlds_module, hlds_pred, hlds_goal.
 :- import_module list.
 
-:- pred move_follow_code_in_proc(proc_info, proc_info,
-	module_info, module_info).
-% :- mode move_follow_code_in_proc(di, uo, di, uo) is det.
-:- mode move_follow_code_in_proc(in, out, in, out) is det.
+:- pred move_follow_code_in_proc(pred_info::in, proc_info::in, proc_info::out,
+	module_info::in, module_info::out) is det.
 
 	% Split a list of goals into the prefix of builtins and the rest.
-:- pred move_follow_code_select(list(hlds_goal), list(hlds_goal),
-	list(hlds_goal)).
-:- mode move_follow_code_select(in, out, out) is det.
+:- pred move_follow_code_select(list(hlds_goal)::in, list(hlds_goal)::out,
+	list(hlds_goal)::out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -37,7 +34,8 @@
 
 %-----------------------------------------------------------------------------%
 
-move_follow_code_in_proc(ProcInfo0, ProcInfo, ModuleInfo0, ModuleInfo) :-
+move_follow_code_in_proc(PredInfo, ProcInfo0, ProcInfo,
+		ModuleInfo0, ModuleInfo) :-
 	module_info_globals(ModuleInfo0, Globals),
 	globals__lookup_bool_option(Globals, follow_code, FollowCode),
 	globals__lookup_bool_option(Globals, prev_code, PrevCode),
@@ -54,14 +52,15 @@
 			% the nonlocal vars and the non-atomic instmap deltas.
 		proc_info_headvars(ProcInfo0, HeadVars),
 		proc_info_typeinfo_varmap(ProcInfo0, TVarMap),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_clause_body(HeadVars, Goal1,
 			Varset0, VarTypes0, TVarMap, TypeInfoLiveness,
 			Goal2, Varset, VarTypes, _Warnings),
 		proc_info_get_initial_instmap(ProcInfo0,
 			ModuleInfo0, InstMap0),
-		recompute_instmap_delta(no, Goal2, Goal, VarTypes, TVarMap,
-			InstMap0, ModuleInfo0, ModuleInfo)
+		recompute_instmap_delta(no, PredInfo, Goal2, Goal,
+			VarTypes, TVarMap, InstMap0, ModuleInfo0, ModuleInfo)
 	;
 		Goal = Goal0,
 		Varset = Varset0,
Index: compiler/higher_order.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/higher_order.m,v
retrieving revision 1.65
diff -u -b -r1.65 higher_order.m
--- compiler/higher_order.m	2000/08/03 08:46:15	1.65
+++ compiler/higher_order.m	2000/08/07 00:25:20
@@ -384,21 +384,24 @@
 		higher_order_info::in, higher_order_info::out) is det.
 
 fixup_proc_info(MustRecompute, Goal0, Info0, Info) :-
-	Info0 = info(A, B, C, D, E, ProcInfo0, ModuleInfo0, H, Changed),
+	Info0 = info(A, B, C, D, PredInfo, ProcInfo0, ModuleInfo0, H, Changed),
 	( (Changed = changed ; MustRecompute = yes) ->
 		proc_info_set_goal(ProcInfo0, Goal0, ProcInfo1),
 		module_info_globals(ModuleInfo0, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo, Globals,
+			TypeInfoLiveness),
 		requantify_proc(TypeInfoLiveness, ProcInfo1, ProcInfo2),
 		proc_info_goal(ProcInfo2, Goal2),
 		RecomputeAtomic = no,
 		proc_info_get_initial_instmap(ProcInfo2, ModuleInfo0, InstMap),
 		proc_info_vartypes(ProcInfo2, VarTypes),
 		proc_info_typeinfo_varmap(ProcInfo2, TVarMap),
-		recompute_instmap_delta(RecomputeAtomic, Goal2, Goal3,
-			VarTypes, TVarMap, InstMap, ModuleInfo0, ModuleInfo),
+		recompute_instmap_delta(RecomputeAtomic, PredInfo,
+			Goal2, Goal3, VarTypes, TVarMap, InstMap,
+			ModuleInfo0, ModuleInfo),
 		proc_info_set_goal(ProcInfo2, Goal3, ProcInfo),
-		Info = info(A, B, C, D, E, ProcInfo, ModuleInfo, H, Changed)
+		Info = info(A, B, C, D, PredInfo, ProcInfo, ModuleInfo,
+			H, Changed)
 	;
 		Info = Info0
 	).
Index: compiler/hlds_pred.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/hlds_pred.m,v
retrieving revision 1.78
diff -u -b -r1.78 hlds_pred.m
--- compiler/hlds_pred.m	2000/08/03 08:46:18	1.78
+++ compiler/hlds_pred.m	2000/08/07 00:42:40
@@ -1136,7 +1136,7 @@
 	% so that we can copy the closure.
 	module_info_globals(ModuleInfo0, Globals),
 	ExportStatus = local,
-	interface_should_use_typeinfo_liveness(ExportStatus,
+	non_special_interface_should_use_typeinfo_liveness(ExportStatus,
 		IsAddressTaken, Globals, TypeInfoLiveness),
 	( TypeInfoLiveness = yes ->
 		goal_info_get_nonlocals(GoalInfo, NonLocals),
@@ -1427,25 +1427,43 @@
 
 	% Return true if the interface of the given procedure must include
 	% typeinfos for all the type variables in the types of the arguments.
-:- pred proc_interface_should_use_typeinfo_liveness(pred_info, proc_id,
-	globals, bool).
-:- mode proc_interface_should_use_typeinfo_liveness(in, in, in, out) is det.
-
-	% Return true if the interface of a procedure with the given
-	% characteristics (import/export/local status, address taken status)
-	% must include typeinfos for all the type variables in the types
-	% of the arguments.
-:- pred interface_should_use_typeinfo_liveness(import_status, is_address_taken,
-		globals, bool).
-:- mode interface_should_use_typeinfo_liveness(in, in, in, out) is det.
-
-	% Return true if the body of the procedure must keep a typeinfo
-	% variable alive during the lifetime of all variables whose type
-	% includes the corresponding type variable. Note that body typeinfo
-	% liveness implies interface typeinfo liveness, but not vice versa.
-:- pred body_should_use_typeinfo_liveness(globals, bool).
-:- mode body_should_use_typeinfo_liveness(in, out) is det.
+:- pred proc_interface_should_use_typeinfo_liveness(pred_info::in, proc_id::in,
+	globals::in, bool::out) is det.
 
+	% Return true if the interface of a procedure in a non-special
+	% predicate with the given characteristics (import/export/local
+	% status, address taken status) must include typeinfos for
+	% all the type variables in the types of the arguments.
+	% Note that only a few predicates in the builtin modules are special
+	% in this sense, and that compiler-generated predicates are never
+	% special.
+:- pred non_special_interface_should_use_typeinfo_liveness(import_status::in,
+	is_address_taken::in, globals::in, bool::out) is det.
+
+	% Return true if the body of a procedure from the given predicate
+	% must keep a typeinfo variable alive during the lifetime of all
+	% variables whose type includes the corresponding type variable.
+	% Note that body typeinfo liveness implies interface typeinfo liveness,
+	% but not vice versa.
+:- pred body_should_use_typeinfo_liveness(pred_info::in, globals::in,
+	bool::out) is det.
+
+	% Return true if the body of a procedure in a non-special predicate
+	% must keep a typeinfo variable alive during the lifetime of all
+	% variables whose type includes the corresponding type variable.
+:- pred non_special_body_should_use_typeinfo_liveness(globals::in,
+	bool::out) is det.
+
+	% unsafe_type_cast and unsafe_promise_unique are polymorphic
+	% builtins which do not need their type_infos. unsafe_type_cast
+	% can be introduced by common.m after polymorphism is run, so it
+	% is much simpler to avoid introducing type_info arguments for it.
+	% Since both of these are really just assignment unifications, it
+	% is desirable to generate them inline.
+	% There are also some predicates in private_builtin.m to
+	% manipulate typeclass_infos which don't need their type_infos.
+:- pred no_type_info_builtin(module_name::in, string::in, int::in) is semidet.
+
 :- implementation.
 
 :- type proc_info
@@ -1795,15 +1813,22 @@
 
 proc_interface_should_use_typeinfo_liveness(PredInfo, ProcId, Globals,
 		InterfaceTypeInfoLiveness) :-
+	pred_info_module(PredInfo, PredModule),
+	pred_info_name(PredInfo, PredName),
+	pred_info_arity(PredInfo, PredArity),
+	( no_type_info_builtin(PredModule, PredName, PredArity) ->
+		InterfaceTypeInfoLiveness = no
+	;
 	pred_info_import_status(PredInfo, Status),
 	pred_info_procedures(PredInfo, ProcTable),
 	map__lookup(ProcTable, ProcId, ProcInfo),
 	proc_info_is_address_taken(ProcInfo, IsAddressTaken),
-	interface_should_use_typeinfo_liveness(Status, IsAddressTaken, Globals,
-		InterfaceTypeInfoLiveness).
+		non_special_interface_should_use_typeinfo_liveness(Status,
+			IsAddressTaken, Globals, InterfaceTypeInfoLiveness)
+	).
 
-interface_should_use_typeinfo_liveness(Status, IsAddressTaken, Globals,
-		InterfaceTypeInfoLiveness) :-
+non_special_interface_should_use_typeinfo_liveness(Status, IsAddressTaken,
+		Globals, InterfaceTypeInfoLiveness) :-
 	(
 		(
 			IsAddressTaken = address_is_taken
@@ -1813,17 +1838,53 @@
 			% follows that it must be exported somewhere.
 			Status \= local
 		;
-			body_should_use_typeinfo_liveness(Globals, yes)
+			non_special_body_should_use_typeinfo_liveness(Globals,
+				yes)
 		)
 	->
 		InterfaceTypeInfoLiveness = yes
 	;
 		InterfaceTypeInfoLiveness = no
 	).
+
+body_should_use_typeinfo_liveness(PredInfo, Globals, BodyTypeInfoLiveness) :-
+	pred_info_module(PredInfo, PredModule),
+	pred_info_name(PredInfo, PredName),
+	pred_info_arity(PredInfo, PredArity),
+	( no_type_info_builtin(PredModule, PredName, PredArity) ->
+		BodyTypeInfoLiveness = no
+	;
+		non_special_body_should_use_typeinfo_liveness(Globals,
+			BodyTypeInfoLiveness)
+	).
 
-body_should_use_typeinfo_liveness(Globals, BodyTypeInfoLiveness) :-
+non_special_body_should_use_typeinfo_liveness(Globals, BodyTypeInfoLiveness) :-
 	globals__lookup_bool_option(Globals, body_typeinfo_liveness,
 		BodyTypeInfoLiveness).
+
+no_type_info_builtin(ModuleName, PredName, Arity) :-
+	no_type_info_builtin_2(ModuleNameType, PredName, Arity),
+	(
+		ModuleNameType = builtin,
+		mercury_public_builtin_module(ModuleName)
+	;
+		ModuleNameType = private_builtin,
+		mercury_private_builtin_module(ModuleName)
+	).
+
+:- type builtin_mod ---> builtin ; private_builtin.
+
+:- pred no_type_info_builtin_2(builtin_mod::out, string::in, int::in)
+	is semidet.
+
+no_type_info_builtin_2(private_builtin, "unsafe_type_cast", 2).
+no_type_info_builtin_2(builtin, "unsafe_promise_unique", 2).
+no_type_info_builtin_2(private_builtin, "superclass_from_typeclass_info", 3).
+no_type_info_builtin_2(private_builtin,
+				"instance_constraint_from_typeclass_info", 3).
+no_type_info_builtin_2(private_builtin, "type_info_from_typeclass_info", 3).
+no_type_info_builtin_2(private_builtin, "table_restore_any_ans", 3).
+no_type_info_builtin_2(private_builtin, "table_lookup_insert_enum", 4).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/lambda.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/lambda.m,v
retrieving revision 1.63
diff -u -b -r1.63 lambda.m
--- compiler/lambda.m	2000/08/03 08:46:20	1.63
+++ compiler/lambda.m	2000/08/07 00:33:38
@@ -192,7 +192,8 @@
 	% check if we need to requantify
 	( MustRecomputeNonLocals = yes ->
 		module_info_globals(ModuleInfo, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo0, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_clause_body(HeadVars,
 			Goal1, VarSet1, VarTypes1, TVarMap, TypeInfoLiveness,
 			Goal, VarSet, VarTypes, _Warnings)
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.87
diff -u -b -r1.87 live_vars.m
--- compiler/live_vars.m	2000/08/03 08:46:21	1.87
+++ compiler/live_vars.m	2000/08/07 00:34:33
@@ -58,7 +58,8 @@
 		LiveSets1 = LiveSets0
 	),
 	trace__reserved_slots(ProcInfo0, Globals, NumReservedSlots),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeInfoLiveness),
 	build_live_sets_in_goal(Goal0, Liveness0, ResumeVars0, LiveSets1,
 		ModuleInfo, ProcInfo0, TypeInfoLiveness,
 		_Liveness, _ResumeVars, LiveSets),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.106
diff -u -b -r1.106 liveness.m
--- compiler/liveness.m	2000/08/06 11:20:52	1.106
+++ compiler/liveness.m	2000/08/07 00:16:22
@@ -153,36 +153,14 @@
 
 detect_liveness_proc(ProcInfo0, PredId, ModuleInfo, ProcInfo) :-
 	module_info_globals(ModuleInfo, Globals),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness0),
-	(
-		pred_info_module(PredInfo, PredModule),
-		( mercury_public_builtin_module(PredModule)
-		; mercury_private_builtin_module(PredModule)
-		)
-	->
-		TypeInfoLiveness1 = no
-	;
-		TypeInfoLiveness1 = TypeInfoLiveness0
-	),
-	requantify_proc(TypeInfoLiveness1, ProcInfo0, ProcInfo1),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo),
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeInfoLiveness),
+	requantify_proc(TypeInfoLiveness, ProcInfo0, ProcInfo1),
 
 	proc_info_goal(ProcInfo1, Goal0),
 	proc_info_varset(ProcInfo1, Varset),
 	proc_info_vartypes(ProcInfo1, VarTypes),
 	proc_info_typeinfo_varmap(ProcInfo1, TVarMap),
-
-	module_info_pred_info(ModuleInfo, PredId, PredInfo),
-	pred_info_module(PredInfo, PredModule),
-	pred_info_name(PredInfo, PredName),
-	pred_info_arity(PredInfo, PredArity),
-	(
-		polymorphism__no_type_info_builtin(PredModule,
-			PredName, PredArity)
-	->
-		TypeInfoLiveness = no
-	;
-		TypeInfoLiveness = TypeInfoLiveness0
-	),
 	live_info_init(ModuleInfo, TypeInfoLiveness, VarTypes, TVarMap, Varset,
 		LiveInfo),
 
@@ -1013,22 +991,10 @@
 	proc_info_goal(ProcInfo, _Goal - GoalInfo),
 	goal_info_get_code_gen_nonlocals(GoalInfo, NonLocals0),
 	module_info_pred_info(ModuleInfo, PredId, PredInfo),
-	body_should_use_typeinfo_liveness(Globals, TypeinfoLiveness),
-	pred_info_module(PredInfo, PredModule),
-	pred_info_name(PredInfo, PredName),
-	pred_info_arity(PredInfo, PredArity),
-	( 	
-		TypeinfoLiveness = yes,
-		\+ polymorphism__no_type_info_builtin(PredModule,
-			PredName, PredArity)
-	->
 		proc_info_typeinfo_varmap(ProcInfo, TVarMap),
-		proc_info_get_typeinfo_vars(NonLocals0, VarTypes, TVarMap,
-			TypeInfoNonLocals),
-		set__union(NonLocals0, TypeInfoNonLocals, NonLocals)
-	;
-		NonLocals = NonLocals0
-	),
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeinfoLiveness),
+	proc_info_maybe_complete_with_typeinfo_vars(NonLocals0,
+		TypeinfoLiveness, VarTypes, TVarMap, NonLocals),
 	set__intersect(Liveness2, NonLocals, Liveness).
 
 :- pred initial_liveness_2(list(prog_var), list(mode), list(type), module_info,
@@ -1070,16 +1036,9 @@
 
 		% If doing alternate liveness, the corresponding
 		% typeinfos need to be added to these.
-	( 
-		LiveInfo^typeinfo_liveness = yes
-	->
 		proc_info_typeinfo_varmap(ProcInfo, TVarMap),
-		proc_info_get_typeinfo_vars(Deadness2, VarTypes, TVarMap,
-			TypeInfoVars),
-		set__union(Deadness2, TypeInfoVars, Deadness)
-	;
-		Deadness = Deadness2
-	).
+	proc_info_maybe_complete_with_typeinfo_vars(Deadness2,
+		LiveInfo^typeinfo_liveness, VarTypes, TVarMap, Deadness).
 
 :- pred initial_deadness_2(list(prog_var), list(mode), list(type),
 		module_info, set(prog_var), set(prog_var)).
Index: compiler/magic.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/magic.m,v
retrieving revision 1.20
diff -u -b -r1.20 magic.m
--- compiler/magic.m	2000/08/03 08:46:24	1.20
+++ compiler/magic.m	2000/08/07 00:35:05
@@ -276,8 +276,10 @@
 
 		% Requantify the goal to rename apart the variables
 		% in the copies of the condition.
+		module_info_pred_info(ModuleInfo0, PredId, PredInfo),
 		module_info_globals(ModuleInfo0, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo, Globals,
+			TypeInfoLiveness),
 		requantify_proc(TypeInfoLiveness, ProcInfo1, ProcInfo3),
 		ModuleInfo1 = ModuleInfo0
 	; Goal0 = switch(Var, _Canfail, Cases, _SM) - GoalInfo ->
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.168
diff -u -b -r1.168 mercury_compile.m
--- compiler/mercury_compile.m	2000/07/25 09:27:22	1.168
+++ compiler/mercury_compile.m	2000/08/07 00:25:53
@@ -1291,7 +1291,7 @@
 	{ globals__lookup_bool_option(Globals, follow_code, FollowCode) },
 	{ globals__lookup_bool_option(Globals, prev_code, PrevCode) },
 	( { FollowCode = yes ; PrevCode = yes } ->
-		{ move_follow_code_in_proc(ProcInfo0, ProcInfo1,
+		{ move_follow_code_in_proc(PredInfo, ProcInfo0, ProcInfo1,
 			ModuleInfo0, ModuleInfo1) }
 	;
 		{ ProcInfo1 = ProcInfo0 },
Index: compiler/mode_info.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mode_info.m,v
retrieving revision 1.54
diff -u -b -r1.54 mode_info.m
--- compiler/mode_info.m	2000/08/06 11:20:53	1.54
+++ compiler/mode_info.m	2000/08/07 00:01:56
@@ -474,18 +474,7 @@
 	CheckingExtraGoals = no,
 
 	module_info_globals(ModuleInfo, Globals),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness0),
-	(
-		pred_info_module(PredInfo, PredModule),
-		( mercury_public_builtin_module(PredModule)
-		; mercury_private_builtin_module(PredModule)
-		)
-	->
-		TypeInfoLiveness = no
-	;
-		TypeInfoLiveness = TypeInfoLiveness0
-	),
-
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeInfoLiveness),
 	ModeInfo = mode_info(
 		IOState, ModuleInfo, PredId, ProcId, VarSet, VarTypes,
 		Context, ModeContext, InstMapping0, LockedVars, DelayInfo,
Index: compiler/mode_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/mode_util.m,v
retrieving revision 1.124
diff -u -b -r1.124 mode_util.m
--- compiler/mode_util.m	2000/08/03 08:46:29	1.124
+++ compiler/mode_util.m	2000/08/07 00:33:16
@@ -112,13 +112,13 @@
 	% may need to insert new merge_insts into the merge_inst table.
 	% If the first argument is yes, the instmap_deltas for calls
 	% and deconstruction unifications are also recomputed.
-:- pred recompute_instmap_delta_proc(bool, proc_info, proc_info,
-				module_info, module_info).
-:- mode recompute_instmap_delta_proc(in, in, out, in, out) is det.
-
-:- pred recompute_instmap_delta(bool, hlds_goal, hlds_goal, vartypes,
-		type_info_varmap, instmap, module_info, module_info).
-:- mode recompute_instmap_delta(in, in, out, in, in, in, in, out) is det.
+:- pred recompute_instmap_delta_proc(bool::in, pred_info::in,
+	proc_info::in, proc_info::out, module_info::in, module_info::out)
+	is det.
+
+:- pred recompute_instmap_delta(bool::in, pred_info::in,
+	hlds_goal::in, hlds_goal::out, vartypes::in, type_info_varmap::in,
+	instmap::in, module_info::in, module_info::out) is det.
 
 	% Given corresponding lists of types and modes, produce a new
 	% list of modes which includes the information provided by the
@@ -1104,23 +1104,26 @@
 	% and deconstructions may become non-local (XXX does this require
 	% rerunning mode analysis rather than just recompute_instmap_delta?).
 
-recompute_instmap_delta_proc(RecomputeAtomic, ProcInfo0, ProcInfo) -->
+recompute_instmap_delta_proc(RecomputeAtomic, PredInfo, ProcInfo0, ProcInfo)
+		-->
 	=(ModuleInfo0),
 	{ proc_info_get_initial_instmap(ProcInfo0, ModuleInfo0, InstMap0) },
 	{ proc_info_vartypes(ProcInfo0, VarTypes) },
 	{ proc_info_typeinfo_varmap(ProcInfo0, TVarMap) },
 	{ proc_info_goal(ProcInfo0, Goal0) },
 	{ module_info_globals(ModuleInfo0, Globals) },
-	{ body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness) },
+	{ body_should_use_typeinfo_liveness(PredInfo, Globals,
+		TypeInfoLiveness) },
 	recompute_instmap_delta(RecomputeAtomic, Goal0, Goal,
 		VarTypes, TVarMap, InstMap0, TypeInfoLiveness, _),
 	{ proc_info_set_goal(ProcInfo0, Goal, ProcInfo) }.
 
-recompute_instmap_delta(RecomputeAtomic, Goal0, Goal, VarTypes, TVarMap,
-		InstMap0) -->
+recompute_instmap_delta(RecomputeAtomic, PredInfo, Goal0, Goal,
+		VarTypes, TVarMap, InstMap0) -->
 	=(ModuleInfo0),
 	{ module_info_globals(ModuleInfo0, Globals) },
-	{ body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness) },
+	{ body_should_use_typeinfo_liveness(PredInfo, Globals,
+		TypeInfoLiveness) },
 	recompute_instmap_delta(RecomputeAtomic, Goal0, Goal, VarTypes,
 		TVarMap, InstMap0, TypeInfoLiveness, _).
 
Index: compiler/passes_aux.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/passes_aux.m,v
retrieving revision 1.36
diff -u -b -r1.36 passes_aux.m
--- compiler/passes_aux.m	2000/06/14 14:54:08	1.36
+++ compiler/passes_aux.m	2000/08/07 00:22:48
@@ -34,7 +34,7 @@
 				io__state, io__state))
 		;	update_pred_error(pred_error_task)
 		;	update_module(pred(
-				proc_info, proc_info,
+				pred_info, proc_info, proc_info,
 				module_info, module_info))
 		;	update_module_io(pred(
 				pred_id, proc_id, proc_info, proc_info,
@@ -93,7 +93,7 @@
 				out, out, di, uo) is det)
 		;	update_pred_error(pred(in, in, out, in, out,
 				out, out, di, uo) is det)
-		;	update_module(pred(in, out, in, out) is det)
+		;	update_module(pred(in, in, out, in, out) is det)
 		;	update_module_io(pred(in, in, in, out,
 				in, out, di, uo) is det)
 		;	update_module_cookie(pred(in, in, in, out, in, out,
@@ -279,7 +279,7 @@
 
 	(
 		Task0 = update_module(Closure),
-		call(Closure, Proc0, Proc, ModuleInfo0, ModuleInfo8),
+		call(Closure, Pred0, Proc0, Proc, ModuleInfo0, ModuleInfo8),
 		Task1 = Task0,
 		State9 = State0
 	;
Index: compiler/pd_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/pd_util.m,v
retrieving revision 1.9
diff -u -b -r1.9 pd_util.m
--- compiler/pd_util.m	2000/08/03 08:46:34	1.9
+++ compiler/pd_util.m	2000/08/07 01:10:47
@@ -664,13 +664,15 @@
 %-----------------------------------------------------------------------------%
 
 pd_util__requantify_goal(Goal0, NonLocals, Goal) -->
+	pd_info_get_pred_info(PredInfo),
 	pd_info_get_proc_info(ProcInfo0),
 	{ proc_info_varset(ProcInfo0, VarSet0) },
 	{ proc_info_vartypes(ProcInfo0, VarTypes0) },
 	{ proc_info_typeinfo_varmap(ProcInfo0, TVarMap) },
 	pd_info_get_module_info(ModuleInfo0),
 	{ module_info_globals(ModuleInfo0, Globals) },
-	{ body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness) },
+	{ body_should_use_typeinfo_liveness(PredInfo, Globals,
+		TypeInfoLiveness) },
 	{ implicitly_quantify_goal(Goal0, VarSet0, VarTypes0,
 		TVarMap, TypeInfoLiveness, NonLocals,
 		Goal, VarSet, VarTypes, _) },
@@ -681,11 +683,12 @@
 pd_util__recompute_instmap_delta(Goal0, Goal) -->
 	pd_info_get_module_info(ModuleInfo0),
 	pd_info_get_instmap(InstMap),
+	pd_info_get_pred_info(PredInfo),
 	pd_info_get_proc_info(ProcInfo),
 	{ proc_info_vartypes(ProcInfo, VarTypes) },
 	{ proc_info_typeinfo_varmap(ProcInfo, TVarMap) },
-	{ recompute_instmap_delta(yes, Goal0, Goal, VarTypes, TVarMap, InstMap, 
-		ModuleInfo0, ModuleInfo) },
+	{ recompute_instmap_delta(yes, PredInfo, Goal0, Goal,
+		VarTypes, TVarMap, InstMap, ModuleInfo0, ModuleInfo) },
 	pd_info_set_module_info(ModuleInfo).
 
 %-----------------------------------------------------------------------------%
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/polymorphism.m,v
retrieving revision 1.191
diff -u -b -r1.191 polymorphism.m
--- compiler/polymorphism.m	2000/08/03 08:46:35	1.191
+++ compiler/polymorphism.m	2000/08/07 01:11:42
@@ -238,17 +238,6 @@
 		proc_info, proc_info, module_info).
 :- mode poly_info_extract(in, in, out, in, out, out) is det.
 
-	% unsafe_type_cast and unsafe_promise_unique are polymorphic
-	% builtins which do not need their type_infos. unsafe_type_cast
-	% can be introduced by common.m after polymorphism is run, so it
-	% is much simpler to avoid introducing type_info arguments for it.
-	% Since both of these are really just assignment unifications, it
-	% is desirable to generate them inline.
-	% There are also some predicates in private_builtin.m to
-	% manipulate typeclass_infos which don't need their type_infos.
-:- pred polymorphism__no_type_info_builtin(module_name, string, int).
-:- mode polymorphism__no_type_info_builtin(in, in, out) is semidet.
-
 	% Build the type describing the typeclass_info for the
 	% given class_constraint.
 :- pred polymorphism__build_typeclass_info_type(class_constraint, (type)).
@@ -367,8 +356,7 @@
 			pred_info_module(PredInfo, PredModule),
 			pred_info_name(PredInfo, PredName),
 			pred_info_arity(PredInfo, PredArity),
-			polymorphism__no_type_info_builtin(PredModule,
-				PredName, PredArity) 
+			no_type_info_builtin(PredModule, PredName, PredArity) 
 		}
 	->
 		% just copy the clauses to the proc_infos
@@ -380,34 +368,6 @@
 
 %---------------------------------------------------------------------------%
 
-polymorphism__no_type_info_builtin(ModuleName, PredName, Arity) :-
-	no_type_info_builtin_2(ModuleNameType, PredName, Arity),
-	check_module_name(ModuleNameType, ModuleName).
-
-:- type builtin_mod ---> builtin ; private_builtin.
-
-:- pred check_module_name(builtin_mod, module_name).
-:- mode check_module_name(in, in) is semidet.
-
-check_module_name(builtin, Module) :-
-	mercury_public_builtin_module(Module).
-check_module_name(private_builtin, Module) :-
-	mercury_private_builtin_module(Module).
-
-:- pred no_type_info_builtin_2(builtin_mod, string, int).
-:- mode no_type_info_builtin_2(out, in, out) is semidet.
-
-no_type_info_builtin_2(private_builtin, "unsafe_type_cast", 2).
-no_type_info_builtin_2(builtin, "unsafe_promise_unique", 2).
-no_type_info_builtin_2(private_builtin, "superclass_from_typeclass_info", 3).
-no_type_info_builtin_2(private_builtin,
-				"instance_constraint_from_typeclass_info", 3).
-no_type_info_builtin_2(private_builtin, "type_info_from_typeclass_info", 3).
-no_type_info_builtin_2(private_builtin, "table_restore_any_ans", 3).
-no_type_info_builtin_2(private_builtin, "table_lookup_insert_enum", 4).
-
-%---------------------------------------------------------------------------%
-
 :- pred polymorphism__fixup_preds(list(pred_id), module_info, module_info).
 :- mode polymorphism__fixup_preds(in, in, out) is det.
 
@@ -937,10 +897,7 @@
 	{ pred_info_arity(PredInfo, PredArity) },
 
 
-	(
-		{ polymorphism__no_type_info_builtin(PredModule,
-			PredName, PredArity)  }
-	->
+	( { no_type_info_builtin(PredModule, PredName, PredArity) } ->
 		{ Goal = Goal0 - GoalInfo }
 	;
 		{ list__length(ExtraVars, NumExtraVars) },
@@ -1662,8 +1619,7 @@
 			PredTypeVars0 = []
 		;
 			% some builtins don't need the type_info
-			polymorphism__no_type_info_builtin(PredModule,
-				PredName, PredArity)
+			no_type_info_builtin(PredModule, PredName, PredArity)
 		;
 			% Leave Aditi relations alone, since they must
 			% be monomorphic. This is checked by magic.m.
@@ -1826,9 +1782,11 @@
 		poly_info_get_var_types(Info0, VarTypes0),
 		set__list_to_set(HeadVars, OutsideVars),
 		poly_info_get_type_info_map(Info0, TVarMap),
+		poly_info_get_pred_info(Info0, PredInfo),
 		poly_info_get_module_info(Info0, ModuleInfo),
 		module_info_globals(ModuleInfo, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_goal(Goal0, VarSet0, VarTypes0,
 			TVarMap, TypeInfoLiveness, OutsideVars,
 			Goal, VarSet, VarTypes, _Warnings),
@@ -1875,9 +1833,11 @@
 			NonLocalsPlusArgs, NewOutsideVars),
 		set__union(NonLocals, NewOutsideVars, OutsideVars),
 		poly_info_get_type_info_map(Info0, TVarMap),
+		poly_info_get_pred_info(Info0, PredInfo),
 		poly_info_get_module_info(Info0, ModuleInfo),
 		module_info_globals(ModuleInfo, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_goal(Goal0, VarSet0, VarTypes0,
 			TVarMap, TypeInfoLiveness, OutsideVars,
 			Goal, VarSet, VarTypes, _Warnings),
Index: compiler/saved_vars.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/saved_vars.m,v
retrieving revision 1.24
diff -u -b -r1.24 saved_vars.m
--- compiler/saved_vars.m	2000/08/03 08:46:39	1.24
+++ compiler/saved_vars.m	2000/08/07 01:12:17
@@ -53,7 +53,7 @@
 	{ saved_vars_proc_no_io(PredId, ProcId, ProcInfo0, ProcInfo,
 		ModuleInfo0, ModuleInfo) }.
 
-saved_vars_proc_no_io(_PredId, _ProcId, ProcInfo0, ProcInfo,
+saved_vars_proc_no_io(PredId, _ProcId, ProcInfo0, ProcInfo,
 		ModuleInfo0, ModuleInfo) :-
 	proc_info_goal(ProcInfo0, Goal0),
 	proc_info_varset(ProcInfo0, Varset0),
@@ -69,14 +69,15 @@
 	% hlds_out__write_goal(Goal1, ModuleInfo, Varset1, 0, "\n"),
 
 	% recompute the nonlocals for each goal
+	module_info_pred_info(ModuleInfo0, PredId, PredInfo),
 	module_info_globals(ModuleInfo0, Globals),
-	body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+	body_should_use_typeinfo_liveness(PredInfo, Globals, TypeInfoLiveness),
 	implicitly_quantify_clause_body(HeadVars, Goal1, Varset1,
 		VarTypes1, TVarMap, TypeInfoLiveness,
 		Goal2, Varset, VarTypes, _Warnings),
 	proc_info_get_initial_instmap(ProcInfo0, ModuleInfo0, InstMap0),
-	recompute_instmap_delta(no, Goal2, Goal, VarTypes, TVarMap, InstMap0, 
-		ModuleInfo0, ModuleInfo),
+	recompute_instmap_delta(no, PredInfo, Goal2, Goal, VarTypes, TVarMap,
+		InstMap0, ModuleInfo0, ModuleInfo),
 
 	% hlds_out__write_goal(Goal, ModuleInfo, Varset, 0, "\n"),
 
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.78
diff -u -b -r1.78 simplify.m
--- compiler/simplify.m	2000/08/03 08:46:40	1.78
+++ compiler/simplify.m	2000/08/07 01:30:26
@@ -209,9 +209,11 @@
 		Goal1 = _ - GoalInfo1,
 		goal_info_get_nonlocals(GoalInfo1, NonLocals),
 		simplify_info_get_type_info_varmap(Info1, TVarMap),
+		simplify_info_get_pred_info(Info1, PredInfo0),
 		simplify_info_get_module_info(Info1, ModuleInfo1),
 		module_info_globals(ModuleInfo1, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo0, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_goal(Goal1, VarSet0, VarTypes0,
 			TVarMap, TypeInfoLiveness, NonLocals,
 			Goal2, VarSet, VarTypes, _),
@@ -226,8 +228,9 @@
 		RecomputeAtomic = yes,
 
 		simplify_info_get_module_info(Info3, ModuleInfo3),
-		recompute_instmap_delta(RecomputeAtomic, Goal2, Goal3,
-			VarTypes, TVarMap, InstMap0, ModuleInfo3, ModuleInfo4),
+		recompute_instmap_delta(RecomputeAtomic, PredInfo0,
+			Goal2, Goal3, VarTypes, TVarMap, InstMap0,
+			ModuleInfo3, ModuleInfo4),
 		simplify_info_set_module_info(Info3, ModuleInfo4, Info4)
 	;
 		Goal3 = Goal1,
@@ -1960,6 +1963,8 @@
 
 :- pred simplify_info_get_module_info(simplify_info::in,
 		module_info::out) is det.
+:- pred simplify_info_get_pred_info(simplify_info::in,
+		pred_info::out) is det.
 
 :- implementation.
 
@@ -1982,6 +1987,12 @@
 simplify_info_get_module_info(Info, ModuleInfo) :-
 	simplify_info_get_det_info(Info, DetInfo),
 	det_info_get_module_info(DetInfo, ModuleInfo).
+
+simplify_info_get_pred_info(Info, PredInfo) :-
+	simplify_info_get_det_info(Info, DetInfo),
+	det_info_get_module_info(DetInfo, ModuleInfo),
+	det_info_get_pred_id(DetInfo, PredId),
+	module_info_pred_info(ModuleInfo, PredId, PredInfo).
 
 :- interface.
 
Index: compiler/table_gen.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/table_gen.m,v
retrieving revision 1.19
diff -u -b -r1.19 table_gen.m
--- compiler/table_gen.m	2000/04/03 16:22:10	1.19
+++ compiler/table_gen.m	2000/08/07 01:13:04
@@ -281,7 +281,7 @@
 	% are pretty dodgy (especially those for if-then-elses), so 
 	% recompute them here.
 	RecomputeAtomic = no,
-	recompute_instmap_delta_proc(RecomputeAtomic,
+	recompute_instmap_delta_proc(RecomputeAtomic, PredInfo1,
 		ProcInfo4, ProcInfo, Module1, Module2),
 
 	pred_info_procedures(PredInfo1, ProcTable1),
Index: compiler/unneeded_code.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unneeded_code.m,v
retrieving revision 1.2
diff -u -b -r1.2 unneeded_code.m
--- compiler/unneeded_code.m	2000/08/03 08:46:44	1.2
+++ compiler/unneeded_code.m	2000/08/07 01:17:49
@@ -195,16 +195,18 @@
 
 unneeded_code__process_proc_msg(PredId, ProcId, ProcInfo0, ProcInfo,
 		ModuleInfo0, ModuleInfo) -->
-	globals__io_lookup_bool_option(very_verbose, VeryVerbose),
+	{ module_info_pred_info(ModuleInfo0, PredId, PredInfo) },
 	{ module_info_globals(ModuleInfo0, Globals) },
-	{ body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness) },
+	{ body_should_use_typeinfo_liveness(PredInfo, Globals,
+		TypeInfoLiveness) },
+	globals__io_lookup_bool_option(very_verbose, VeryVerbose),
 	( { VeryVerbose = yes } ->
 		io__write_string("% Removing dead code in "),
 		hlds_out__write_pred_proc_id(ModuleInfo0, PredId, ProcId),
 		io__write_string(": "),
 		{ unneeded_code__pre_process_proc(TypeInfoLiveness,
 			ProcInfo0, ProcInfo1) },
-		{ unneeded_code__process_proc(ProcInfo1, ProcInfo,
+		{ unneeded_code__process_proc(PredInfo, ProcInfo1, ProcInfo,
 			ModuleInfo0, ModuleInfo, TypeInfoLiveness,
 			Successful) },
 		(
@@ -217,7 +219,7 @@
 	;
 		{ unneeded_code__pre_process_proc(TypeInfoLiveness,
 			ProcInfo0, ProcInfo1) },
-		{ unneeded_code__process_proc(ProcInfo1, ProcInfo,
+		{ unneeded_code__process_proc(PredInfo, ProcInfo1, ProcInfo,
 			ModuleInfo0, ModuleInfo, TypeInfoLiveness, _) }
 	).
 
@@ -269,11 +271,12 @@
 			copy_limit	::	int
 		).
 
-:- pred unneeded_code__process_proc(proc_info::in, proc_info::out,
-	module_info::in, module_info::out, bool::in, bool::out) is det.
+:- pred unneeded_code__process_proc(pred_info::in,
+	proc_info::in, proc_info::out, module_info::in, module_info::out,
+	bool::in, bool::out) is det.
 
-unneeded_code__process_proc(ProcInfo0, ProcInfo, ModuleInfo0, ModuleInfo,
-		TypeInfoLiveness, Successful) :-
+unneeded_code__process_proc(PredInfo, ProcInfo0, ProcInfo,
+		ModuleInfo0, ModuleInfo, TypeInfoLiveness, Successful) :-
 	goal_path__fill_slots(ProcInfo0, ModuleInfo0, ProcInfo1),
 	proc_info_goal(ProcInfo1, Goal0),
 	proc_info_varset(ProcInfo1, Varset0),
@@ -313,12 +316,12 @@
 			Goal2, Varset0, VarTypes0,
 			TVarMap, TypeInfoLiveness,
 			Goal3, Varset, VarTypes, _Warnings),
-		recompute_instmap_delta(no, Goal3, Goal, VarTypes, TVarMap,
-			InstMap0, ModuleInfo0, ModuleInfo1),
+		recompute_instmap_delta(no, PredInfo, Goal3, Goal,
+			VarTypes, TVarMap, InstMap0, ModuleInfo0, ModuleInfo1),
 		proc_info_set_goal(ProcInfo1, Goal, ProcInfo2),
 		proc_info_set_varset(ProcInfo2, Varset, ProcInfo3),
 		proc_info_set_vartypes(ProcInfo3, VarTypes, ProcInfo4),
-		unneeded_code__process_proc(ProcInfo4, ProcInfo,
+		unneeded_code__process_proc(PredInfo, ProcInfo4, ProcInfo,
 			ModuleInfo1, ModuleInfo, TypeInfoLiveness, _),
 		Successful = yes
 	;
Index: compiler/unused_args.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/unused_args.m,v
retrieving revision 1.64
diff -u -b -r1.64 unused_args.m
--- compiler/unused_args.m	2000/08/03 08:46:44	1.64
+++ compiler/unused_args.m	2000/08/07 00:04:55
@@ -255,14 +255,7 @@
 		module_info_globals(ModuleInfo, Globals),
 		proc_interface_should_use_typeinfo_liveness(PredInfo, ProcId,
 			Globals, TypeInfoLiveness),
-		( 
-			TypeInfoLiveness = yes,
-			pred_info_module(PredInfo, PredModule),
-			pred_info_name(PredInfo, PredName),
-			pred_info_arity(PredInfo, PredArity),
-			\+ polymorphism__no_type_info_builtin(PredModule,
-				PredName, PredArity)
-		->
+		( TypeInfoLiveness = yes ->
 			proc_info_typeinfo_varmap(ProcInfo, TVarMap),
 			setup_typeinfo_deps(Vars, VarTypes, 
 				proc(PredId, ProcId), TVarMap, VarDep2,
@@ -830,7 +823,8 @@
 		    call_info(NewPredId, NewProcId, PredSymName, UnusedArgs),
 		    ProcCallInfo),
 		module_info_globals(ModuleInfo0, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(NewPredInfo, Globals,
+			TypeInfoLiveness),
 		(
 			Status0 = exported,
 			IntermodUnusedArgs = yes(UnusedArgs2)
@@ -1158,7 +1152,8 @@
 		set__list_to_set(HeadVars, NonLocals),
 		proc_info_typeinfo_varmap(ProcInfo0, TVarMap),
 		module_info_globals(Mod0, Globals),
-		body_should_use_typeinfo_liveness(Globals, TypeInfoLiveness),
+		body_should_use_typeinfo_liveness(PredInfo0, Globals,
+			TypeInfoLiveness),
 		implicitly_quantify_goal(Goal1, Varset0, VarTypes0,
 			TVarMap, TypeInfoLiveness, NonLocals,
 			Goal, Varset, VarTypes, _),
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing doc
cvs diff: Diffing extras
cvs diff: Diffing extras/aditi
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/clpr
cvs diff: Diffing extras/clpr/clpr
cvs diff: Diffing extras/clpr/samples
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing library
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
Index: tests/debugger/mdb_command_test.inp
===================================================================
RCS file: /home/mercury1/repository/tests/debugger/mdb_command_test.inp,v
retrieving revision 1.9
diff -u -b -r1.9 mdb_command_test.inp
--- tests/debugger/mdb_command_test.inp	2000/07/20 03:43:58	1.9
+++ tests/debugger/mdb_command_test.inp	2000/08/06 12:30:41
@@ -4,7 +4,6 @@
 step                 xyzzy xyzzy xyzzy xyzzy xyzzy
 goto                 xyzzy xyzzy xyzzy xyzzy xyzzy
 finish               xyzzy xyzzy xyzzy xyzzy xyzzy
-exception            xyzzy xyzzy xyzzy xyzzy xyzzy
 return               xyzzy xyzzy xyzzy xyzzy xyzzy
 forward              xyzzy xyzzy xyzzy xyzzy xyzzy
 mindepth             xyzzy xyzzy xyzzy xyzzy xyzzy
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
cvs diff: Diffing trial
cvs diff: Diffing util
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list