[m-dev.] [reuse] diff: more informative alias-tops

Nancy Mazur Nancy.Mazur at cs.kuleuven.ac.be
Wed Oct 18 05:49:10 AEDT 2000


Hi,


===================================================================


Estimated hours taken: 1

Collect more information about when aliases turn to top. 

pa_alias_as.m:
pa_run.m:
sr_dead.m:
sr_indirect.m:
	Change the handling of top so that more information of what
	is causing the top is collected. This is useful to spot the
	places where problems occur and to try to find solutions
	to those problems. 


Index: pa_alias_as.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_alias_as.m,v
retrieving revision 1.1.2.5
diff -u -r1.1.2.5 pa_alias_as.m
--- pa_alias_as.m	2000/10/16 17:47:36	1.1.2.5
+++ pa_alias_as.m	2000/10/17 18:43:33
@@ -38,6 +38,7 @@
 :- pred is_bottom( alias_as::in ) is semidet.
 
 :- pred top( string::in, alias_as::out ) is det.
+:- pred top( alias_as::in, string::in, alias_as::out) is det.
 :- pred is_top( alias_as::in ) is semidet.
 
 	% project alias abstract substitution on a list of variables.
@@ -98,10 +99,10 @@
 			hlds_goal__hlds_goal_info, alias_as, alias_as).
 :- mode extend_unification( in, in, in, in, in, out) is det.
 
-:- pred extend_foreign_code( proc_info, module_info, 
+:- pred extend_foreign_code( proc_info, module_info, hlds_goal_info, 
 			list(prog_var), list(maybe(pair(string, mode))),
                         list(type), alias_as, alias_as).
-:- mode extend_foreign_code( in, in, in, in, in, in, out) is det.
+:- mode extend_foreign_code( in, in, in, in, in, in, in, out) is det.
 
 	% Add two abstract substitutions to each other. These
 	% abstract substitutions come from different contexts, and have
@@ -156,7 +157,7 @@
 :- implementation.
 
 % library modules
-:- import_module require.
+:- import_module require, term.
 
 % compiler modules
 :- import_module pa_alias, pa_util.
@@ -187,6 +188,29 @@
 	% string__append_list(["- ",Msg," -"],NewMsg).
 	NewMsg = Msg.
 
+top( Alias, Msg, top(Msgs)):-
+	(
+		Alias = top(FirstMsgs)
+	->
+		Msgs = FirstMsgs
+	;
+		Msgs = [Msg]
+	).
+
+:- pred top_merge(alias_as::in, alias_as::in, alias_as::out) is det.
+top_merge( A0, A1, A ) :- 
+	(
+		A0 = top(Msgs0),
+		A1 = top(Msgs1)
+	->
+		list__append(Msgs0, Msgs1, MsgsDups),
+		list__remove_dups(MsgsDups, Msgs),
+		A = top(Msgs)
+	;
+		require__error("(pa_alias_as) top_merge: aliases ought to be
+both top.")
+	).
+
 	% is_top
 is_top( top(_) ).
 
@@ -281,7 +305,9 @@
 		AfterList = []
 	;
 		% AS1 is bottom or top(_)
-		AS2 = AS1
+		( AS1 = bottom, AS2 = bottom)
+		;
+		( is_top(AS1), is_top(AS2) )
 	).
 
 leq( ProcInfo, HLDS, AS1, AS2 ):-
@@ -321,7 +347,13 @@
 	;
 		AS1 = top(_)
 	->
-		RESULT = AS1
+		(
+			AS2 = top(_)
+		->
+			top_merge( AS1, AS2, RESULT)
+		;
+			RESULT = AS1
+		)
 	;
 		% AS1 = bottom
 		RESULT = AS2
@@ -366,7 +398,14 @@
 	;
 		A1 = top(_)
 	->
-		RESULT = A1
+		(
+			A2 = top(_)
+		->
+			RESULT = A2 	% if the old alias was already
+					% top, keep the old one.
+		; 		
+			RESULT = A1 	
+		)
 	; 
 		% A1 = bottom
 		RESULT = A2	
@@ -448,7 +487,8 @@
 	not contains_one_of_vars_in_list( Vars, Alias).
 
 %-----------------------------------------------------------------------------%
-extend_foreign_code( _ProcInfo, HLDS, Vars, MaybeModes, Types, Alias0, Alias):-
+extend_foreign_code( _ProcInfo, HLDS, GoalInfo, 
+			Vars, MaybeModes, Types, Alias0, Alias):-
 	to_trios(Vars, MaybeModes, Types, Trios), 
 	% remove all unique objects
 	remove_all_unique_vars( HLDS, Trios, NonUniqueVars), 
@@ -477,7 +517,17 @@
 		-> 
 			Alias = Alias0
 		; 
-			pa_alias_as__top("pragma_c_code not handled", Alias)
+
+			goal_info_get_context(GoalInfo, Context), 
+			term__context_line(Context, ContextLine), 
+			term__context_file(Context, ContextFile), 
+			string__int_to_string(ContextLine, ContextLineS), 
+
+			string__append_list(["pragma_foreign_code:",
+						" (",ContextFile, ":", 
+						ContextLineS, ")"], Msg), 
+			
+			pa_alias_as__top(Alias0, Msg, Alias)
 		)
 	).
 	
@@ -619,9 +669,13 @@
 	;
 		{ AS = top(Msgs) }
 	->
-		{ string__append_list(["% aliases = top("|Msgs],Msg) },
-		{ string__append(Msg,")",Msg2) },
-		io__write_string(Msg2)
+		{ list__map( 
+			pred( S0::in, S::out ) is det :- 
+				(string__append_list(["%\t",S0,"\n"], S)),
+			Msgs, 
+			MsgsF ) }, 
+		{ string__append_list(["% aliases are top:\n" |MsgsF],Msg) },
+		io__write_string(Msg)
 	;
 		io__write_string("% aliases = bottom")
 	).
@@ -676,7 +730,7 @@
 
 parse_read_aliases_from_single_term( OneITEM, AS ) :- 
 	(
-		OneITEM = term__functor( term__atom(CONS), _TERMS, _ )
+		OneITEM = term__functor( term__atom(CONS), _TERMS, Context )
 	->
 		(
 			CONS = "."
@@ -692,7 +746,13 @@
 		; 
 			CONS = "top"
 		->
-			AS = top(["imported top"])
+			term__context_line(Context, ContextLine), 
+			term__context_file(Context, ContextFile), 
+			string__int_to_string(ContextLine, ContextLineS), 
+			string__append_list(["imported top (", 
+				ContextFile, ":", ContextLineS, ")"], 
+					Msg),
+			top(Msg, AS)
 		;
 			string__append(
 		"(pa_alias_as) parse_read_aliases_from_single_term: could not parse aliases, top cons: ", CONS, Msg),
Index: pa_run.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_run.m,v
retrieving revision 1.1.2.8
diff -u -r1.1.2.8 pa_run.m
--- pa_run.m	2000/10/17 12:53:25	1.1.2.8
+++ pa_run.m	2000/10/17 18:43:34
@@ -61,6 +61,7 @@
 :- import_module require.
 :- import_module list, map, int, set.
 :- import_module std_util, string.
+:- import_module term.
 
 :- import_module dependency_graph.
 :- import_module instmap.
@@ -71,6 +72,7 @@
 
 
 
+
 %-------------------------------------------------------------------%
 
 pa_run__aliases_pass( HLDSin, HLDSout ) -->
@@ -298,10 +300,28 @@
 	lookup_call_alias( PRED_PROC_ID, HLDS, T0, T, CallAlias), 
 	rename_call_alias( PRED_PROC_ID, HLDS, ARGS, CallAlias, RenamedCallAlias),
 	pa_alias_as__extend( ProcInfo, HLDS, RenamedCallAlias, A0, A ).
+
+analyse_goal_expr( generic_call( GenCall,_,_,_), Info, 
+				_ProcInfo, _HLDS , T, T, A0, A):- 
+	(
+		GenCall = higher_order(_, _, _),
+		Text = "higher_order"
+	; 
+		GenCall = class_method(_, _, _, _),
+		Text = "class_method"
+	; 
+		GenCall = aditi_builtin(_,_),
+		Text = "aditi_builtin"
+	), 
+	goal_info_get_context(Info, Context), 
+	term__context_line(Context, ContextLine), 
+	term__context_file(Context, ContextFile), 
+	string__int_to_string(ContextLine, ContextLineS), 
 
-analyse_goal_expr( generic_call(_,_,_,_), _Info, 
-				_ProcInfo, _HLDS , T, T, _A, A):- 
-	pa_alias_as__top("generic_call not handled",A).
+	string__append_list(["generic_call:",Text," (",ContextFile, ":", 
+				ContextLineS, ")"], Msg), 
+	
+	pa_alias_as__top(A0, Msg, A). 
 	% error("(pa) generic_call not handled") .
 
 analyse_goal_expr( switch(_Var,_CF,Cases,_SM), _Info, 
@@ -359,18 +379,34 @@
 	pa_alias_as__least_upper_bound( ProcInfo, HLDS, A2, A3, A).
 
 analyse_goal_expr( pragma_foreign_code( _,_,_,_, Vars, MaybeModes,Types,_  ), 
-			_Info, ProcInfo, HLDS , 
+			Info, ProcInfo, HLDS , 
 			T, T, Ain, A) :- 
-	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Vars, 
+	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Info, Vars, 
 		MaybeModes, Types, Ain, A). 
 
 	% error( "(pa) pragma_c_code not handled") .
-analyse_goal_expr( par_conj( _Goals, _SM), _Info, _, _ , T, T, _A, A) :-  
-	pa_alias_as__top("par_conj not handled", A).
+analyse_goal_expr( par_conj( _Goals, _SM), Info, _, _ , T, T, A0, A) :-  
+	goal_info_get_context(Info, Context), 
+	term__context_line(Context, ContextLine), 
+	term__context_file(Context, ContextFile), 
+	string__int_to_string(ContextLine, ContextLineS), 
+
+	string__append_list(["par_conj:",
+				" (",ContextFile, ":", 
+				ContextLineS, ")"], Msg), 
+	pa_alias_as__top(A0, Msg, A).
+
 	% error( "(pa) par_conj not handled") .
-analyse_goal_expr( bi_implication( _G1, _G2),_Info, _,  _ , T, T, _A, A) :- 
-	pa_alias_as__top("bi_implication not handled", A).
-	% error( "(pa) bi_implication not handled") .
+analyse_goal_expr( bi_implication( _G1, _G2),Info, _,  _ , T, T, A0, A) :- 
+	goal_info_get_context(Info, Context), 
+	term__context_line(Context, ContextLine), 
+	term__context_file(Context, ContextFile), 
+	string__int_to_string(ContextLine, ContextLineS), 
+
+	string__append_list(["bi_implication:",
+				" (",ContextFile, ":", 
+				ContextLineS, ")"], Msg), 
+	pa_alias_as__top(A0, Msg, A).
 
 %-----------------------------------------------------------------------------%
 
@@ -683,99 +719,5 @@
 	;
 		End = List
 	).
-
-%-------------------------------------------------------------------%
-%-------------------------------------------------------------------%
-% ensure loaded interfaces.
-
-/*********************************************************************
-:- import_module term, set, prog_io, globals, prog_out, prog_io_util.
-:- import_module hlds_out, assoc_list, mode_util.
-
-	% load interfaces of the imported modules. 
-	% If some interface file appears to be unavailable, a warning
-	% is generated, and probably the code will fail at some later
-	% point. 
-:- pred pa_run__ensure_loaded_interfaces( module_info, module_info, 
-						io__state, io__state).
-:- mode pa_run__ensure_loaded_interfaces( in, out, di, uo) is det.
-
-pa_run__ensure_loaded_interfaces( HLDS0, HLDS) -->
-	{ module_info_get_imported_module_specifiers( HLDS0, ModSpecs ) },
-	{ set__to_sorted_list( ModSpecs, LModSpecs ) },
-	list__foldl2( load_interface, LModSpecs, HLDS0, HLDS).
-
-:- pred load_interface( module_specifier, module_info, module_info,
-			io__state, io__state).
-:- mode load_interface( in, in, out, di, uo) is det.
-
-load_interface( ModuleSpec, HLDS0, HLDS ) -->
-	globals__io_lookup_bool_option(very_verbose, VeryVerbose),
-	module_name_to_file_name( ModuleSpec, ".opt.pa", no, FileName ),
-	maybe_write_string(VeryVerbose, "% Reading `"),
-	maybe_write_string(VeryVerbose, FileName ),
-	maybe_write_string(VeryVerbose, "'... "),
-	maybe_flush_output(VeryVerbose),
-	prog_io__read_module( FileName, ModuleSpec, yes, Err, _ModuleName, 
-				Msgs, Items),
-	(
-		{ Err = fatal }
-	->
-		maybe_write_string(VeryVerbose, "fatal error(s).\n")
-	;
-		{ Err = yes }
-	->
-		maybe_write_string(VeryVerbose, "parse_error(s).\n")
-	;
-		maybe_write_string(VeryVerbose, "successfull parse.\n")
-	),
-	prog_out__write_messages(Msgs),
-	(
-		{ Err = fatal }
-	-> 
-		maybe_write_string(VeryVerbose, "% Continuing... errors might occur later.\n")
-	;
-		{ Err = yes }
-	->
-		maybe_write_string(VeryVerbose, "% Continuing... errors might occur later.\n")
-	;
-		maybe_write_string(VeryVerbose, "% Cool!\n")
-	),
-
-	list__foldl2( add_item_from_opt_pa, Items, HLDS0, HLDS ).
-
-:- pred add_item_from_opt_pa( item_and_context, module_info, module_info, 
-					io__state, io__state ).
-:- mode add_item_from_opt_pa( in, in, out, di, uo) is det.
-
-add_item_from_opt_pa( Item - _Context, HLDS0, HLDS ) -->
-	(
-		{ Item = pragma(Pragma) }
-	->
-		add_pragma_item_from_opt_pa( Pragma , HLDS0, HLDS)
-	;
-	 	prog_io_util__report_warning(
-				"Only pragma pa_alias_info allowed in `.opt.pa' file.")	,
-		{ HLDS = HLDS0 }
-	).
-
-:- pred add_pragma_item_from_opt_pa( pragma_type, module_info, module_info,
-					io__state, io__state).
-:- mode add_pragma_item_from_opt_pa( in, in, out, di, uo) is det.
-
-add_pragma_item_from_opt_pa( Pragma, HLDS0, HLDS) -->
-	(
-		{ Pragma = pa_alias_info( PredOrFunc, SymName, Modes,
-					HeadVars, MaybeAlias) }
-	->
-		add_pragma_possible_aliases_info( PredOrFunc, SymName, Modes,
-					HeadVars, MaybeAlias, HLDS0, HLDS)
-	;
-		prog_io_util__report_warning(
-				"Only pragma pa_alias_info allowed in `.opt.pa' file.")	,
-		{ HLDS = HLDS0 }
-	).
-
-*************************************************************************/
 
 
Index: sr_dead.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/sr_dead.m,v
retrieving revision 1.1.2.6
diff -u -r1.1.2.6 sr_dead.m
--- sr_dead.m	2000/10/16 18:06:38	1.1.2.6
+++ sr_dead.m	2000/10/17 18:43:36
@@ -181,7 +181,7 @@
 annotate_goal( ProcInfo, HLDS, Expr0 - Info0, Goal, 
 			Pool0, Pool, Alias0, Alias) :- 
 	Expr0 = pragma_foreign_code(_, _, _, _, Vars, MaybeModes, Types, _), 
-	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Vars, 
+	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Info0, Vars, 
 			MaybeModes, Types, Alias0, Alias), 
 	Pool = Pool0, 
 	Goal = Expr0 - Info0. 
Index: sr_indirect.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/sr_indirect.m,v
retrieving revision 1.1.2.10
diff -u -r1.1.2.10 sr_indirect.m
--- sr_indirect.m	2000/10/17 12:33:33	1.1.2.10
+++ sr_indirect.m	2000/10/17 18:43:37
@@ -438,7 +438,7 @@
 
 analyse_goal(ProcInfo, HLDS, Expr0 - Info0, Goal, AI0, AI) :-
 	Expr0 = pragma_foreign_code( _, _, _, _, Vars, MaybeModes, Types, _ ), 
-	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Vars, 
+	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Info0, Vars, 
 			MaybeModes, Types, AI0 ^ alias, Alias), 
 	AI = AI0 ^ alias := Alias,
 	Goal = Expr0 - Info0. 
@@ -641,7 +641,7 @@
 			Alias0, Alias, 
 			FP0, FP) :- 
 	Expr0 = pragma_foreign_code( _, _, _, _, Vars, MaybeModes, Types, _ ), 
-	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Vars, 
+	pa_alias_as__extend_foreign_code( ProcInfo, HLDS, Info0, Vars, 
 			MaybeModes, Types, Alias0, Alias), 
 	Pool = Pool0, 
 	FP = FP0,

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