[m-dev.] [reuse] diff: reuse-profiling

Nancy Mazur Nancy.Mazur at cs.kuleuven.ac.be
Thu Oct 19 09:36:57 AEDT 2000


Hi,


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


Estimated hours taken: 3

At the end of the structure-reuse pass, we want to collect some
profiling information (how much procedures are involved with reuse, 
how often is a deconstruction concerned in direct reuse, etc.. )


sr_profile.m:
sr_profile_run.m:
structure_reuse.m:
	Compute profiling information wrt the reuse analysis 
	and output it to <module>.profile


Index: sr_profile.m
===================================================================
RCS file: sr_profile.m
diff -N sr_profile.m
--- /dev/null	Tue Jul 25 14:12:01 2000
+++ sr_profile.m	Thu Oct 19 09:33:33 2000
@@ -0,0 +1,205 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2000 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% Module:	sr_profile
+% Main authors: nancy
+
+:- module sr_profile.
+
+:- interface.
+
+:- import_module io, int, string. 
+
+:- type profiling_info ---> 
+		prof(
+			% general counting of procedures
+			procs_defined	:: int, 
+			reuse_procs	:: int,
+			uncond_reuse_procs :: int,
+			procs_counted	:: int, 
+
+			% only counting about exported procedures
+			exported_procs  :: int,
+			exported_reuse_procs :: int, 
+			exported_uncond_reuse_procs ::int, 
+	
+			% info about the aliases	
+			aliases		:: int, 
+			bottom_procs	:: int,
+			top_procs	:: int, 
+	
+			deconstructs 	:: int, 
+			direct_reuses 	:: int,
+			direct_conditions :: int, 	% not used 
+			
+
+			pred_calls 	:: int, 
+			reuse_calls	:: int, 
+			no_reuse_calls 	:: int  	
+		).
+
+:- pred init( profiling_info::out ) is det.
+
+:- pred inc_procs_defined( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_reuse_procs( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_uncond_reuse_procs( profiling_info::in, 
+			profiling_info::out ) is det.
+:- pred inc_procs_counted( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_exported_procs( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_exported_reuse_procs( profiling_info::in, 
+			profiling_info::out ) is det.
+:- pred inc_exported_uncond_reuse_procs( profiling_info::in, 
+			profiling_info::out ) is det.
+
+:- pred inc_aliases( int::in, profiling_info::in, profiling_info::out ) is det.
+:- pred inc_bottom_procs( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_top_procs( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_deconstructs( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_direct_reuses( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_direct_conditions( profiling_info::in, profiling_info::out ) is
+det.
+:- pred inc_pred_calls( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_reuse_calls( profiling_info::in, profiling_info::out ) is det.
+:- pred inc_no_reuse_calls( profiling_info::in, profiling_info::out ) is det.
+
+
+:- pred write_profiling( string::in, profiling_info::in, 
+			io__state::di, io__state::uo ) is det. 
+
+%-----------------------------------------------------------------------------%
+
+:- implementation. 
+
+:- import_module require, time, list. 
+
+init( P ) :- 
+	P = prof( 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0). 
+
+inc_procs_defined( P0, P0 ^ procs_defined := (P0 ^ procs_defined + 1)).
+inc_reuse_procs( P0, P0 ^ reuse_procs := (P0 ^ reuse_procs + 1)).
+inc_uncond_reuse_procs( P0, 
+		P0 ^ uncond_reuse_procs := (P0 ^ uncond_reuse_procs + 1)).
+inc_procs_counted( P0, P0 ^ procs_counted := (P0 ^ procs_counted + 1)).
+inc_exported_procs( P0, P0 ^ exported_procs := (P0 ^ exported_procs + 1)).
+inc_exported_reuse_procs( P0, 
+		P0 ^ exported_reuse_procs := (P0 ^ exported_reuse_procs + 1)).
+inc_exported_uncond_reuse_procs( P0, 
+	P0 ^ exported_uncond_reuse_procs 
+			:= (P0 ^ exported_uncond_reuse_procs + 1)).
+inc_aliases( N, P0, P0 ^ aliases := (P0 ^ aliases + N)).
+inc_bottom_procs( P0, P0 ^ bottom_procs := (P0 ^ bottom_procs + 1)).
+inc_top_procs( P0, P0 ^ top_procs := (P0 ^ top_procs + 1)).
+inc_deconstructs( P0, P0 ^ deconstructs := (P0 ^ deconstructs + 1)).
+inc_direct_reuses( P0, P0 ^ direct_reuses := (P0 ^ direct_reuses + 1)).
+inc_direct_conditions( P0, P0 ^ direct_conditions := (P0 ^ direct_conditions + 1)).
+inc_pred_calls( P0, P0 ^ pred_calls := (P0 ^ pred_calls + 1)).
+inc_reuse_calls( P0, P0 ^ reuse_calls := (P0 ^ reuse_calls + 1)).
+inc_no_reuse_calls( P0, P0 ^ no_reuse_calls := (P0 ^ no_reuse_calls + 1)). 
+
+:- pred procs_defined( profiling_info::in, int::out) is det.
+:- pred reuse_procs( profiling_info::in, int::out) is det.
+:- pred uncond_reuse_procs( profiling_info::in, int::out) is det.
+:- pred procs_counted( profiling_info::in, int::out) is det.
+:- pred exported_procs( profiling_info::in, int::out) is det.
+:- pred exported_reuse_procs( profiling_info::in, int::out) is det.
+:- pred exported_uncond_reuse_procs( profiling_info::in, int::out) is det.
+:- pred aliases( profiling_info::in, int::out) is det.
+:- pred bottom_procs( profiling_info::in, int::out) is det.
+:- pred top_procs( profiling_info::in, int::out) is det.
+:- pred deconstructs( profiling_info::in, int::out) is det.
+:- pred direct_reuses( profiling_info::in, int::out) is det.
+:- pred direct_conditions( profiling_info::in,int::out) is det.
+:- pred pred_calls( profiling_info::in, int::out) is det.
+:- pred reuse_calls( profiling_info::in, int::out) is det.
+:- pred no_reuse_calls( profiling_info::in, int::out) is det.
+
+
+procs_defined( P0, P0 ^ procs_defined ).
+reuse_procs( P0, P0 ^ reuse_procs ).
+uncond_reuse_procs( P0, P0 ^ uncond_reuse_procs ).
+procs_counted( P0, P0 ^ procs_counted ).
+exported_procs( P0, P0 ^ exported_procs ).
+exported_reuse_procs( P0, P0 ^ exported_reuse_procs ).
+exported_uncond_reuse_procs( P0, P0 ^ exported_uncond_reuse_procs ).
+aliases( P0, P0 ^ aliases ).
+bottom_procs( P0, P0 ^ bottom_procs ).
+top_procs( P0, P0 ^ top_procs ).
+deconstructs( P0, P0 ^ deconstructs ).
+direct_reuses( P0, P0 ^ direct_reuses ).
+direct_conditions( P0, P0 ^ direct_conditions ).
+pred_calls( P0, P0 ^ pred_calls ).
+reuse_calls( P0, P0 ^ reuse_calls ).
+no_reuse_calls( P0, P0 ^ no_reuse_calls ).
+
+write_profiling( String, Prof ) --> 
+	{ string__append(String, ".profile", String2) }, 
+	io__open_output( String2, IOResult), 
+	(
+		{ IOResult = ok(Stream) },
+		% top
+		io__write_string(Stream, "Profiling output for module: "), 
+		io__write_string(Stream, String), 
+		io__nl(Stream),
+		% date
+		time__time( TimeT ), 
+		{ TimeS = time__ctime(TimeT) }, 
+		io__write_string(Stream, "Current time: "), 
+		io__write_string(Stream, TimeS ), 
+		io__nl(Stream), 
+		io__nl(Stream), 
+		io__write_string(Stream, "General info:\n"),
+		write_prof_item( Stream, procs_defined, Prof, 
+				"# declared procedures"), 
+		write_prof_item( Stream, reuse_procs, Prof, 
+				"# reuse-procedures"), 
+		write_prof_item( Stream, uncond_reuse_procs, Prof, 
+				"# unconditional reuse-procedures"), 
+		write_prof_item( Stream, procs_counted, Prof, 
+				"# procedures (total)"),
+		io__write_string(Stream, "Exported info:\n"),
+		write_prof_item( Stream, exported_procs, Prof, 
+				"# exported procedures"),
+		write_prof_item( Stream, exported_reuse_procs, Prof, 
+				"# exported procedures with reuse"), 
+		write_prof_item( Stream, exported_uncond_reuse_procs, Prof, 
+			"# exported unconditional procedures with reuse"), 
+		io__write_string(Stream, "Alias info:\n"),
+		write_prof_item( Stream, aliases, Prof, 
+				"# aliases over all the procedures"),
+		write_prof_item( Stream, bottom_procs, Prof, 
+				"# procedures with alias = bottom"), 
+		write_prof_item( Stream, top_procs, Prof, 
+				"# procedures with alias = top"), 
+		io__write_string( Stream, "About direct reuses:\n"), 
+		write_prof_item( Stream, deconstructs, Prof, 
+				"# deconstructs"), 
+		write_prof_item( Stream, direct_reuses, Prof, 
+				"# direct reuses"),
+		write_prof_item( Stream, direct_conditions, Prof, 
+				"# conditions implied by direct reuses"),
+		io__write_string( Stream, "About indirect reuses:\n"),
+		write_prof_item( Stream, pred_calls, Prof, 
+				"# procedure calls"),
+		write_prof_item( Stream, reuse_calls, Prof, 
+				"# calls to procedures with reuse"),
+		write_prof_item( Stream, no_reuse_calls, Prof, 
+				"# failed calls to procedures with reuse"),
+		io__close_output(Stream)
+	;
+		{ IOResult = error(IOError) },
+		{ io__error_message(IOError, IOErrorString) }, 
+		{ require__error(IOErrorString) }
+	).
+
+:- pred write_prof_item( io__output_stream, pred(profiling_info, int), 
+			profiling_info, 
+			string, io__state, io__state).
+:- mode write_prof_item( in, pred(in, out) is det, in, in, di, uo) is det.
+
+write_prof_item( Str, Getter, Prof, Text ) --> 
+	{ Getter(Prof,Count) },
+	io__format(Str, "%8d  %s\n", [i(Count),s(Text)]).
+		
Index: sr_profile_run.m
===================================================================
RCS file: sr_profile_run.m
diff -N sr_profile_run.m
--- /dev/null	Tue Jul 25 14:12:01 2000
+++ sr_profile_run.m	Thu Oct 19 09:33:33 2000
@@ -0,0 +1,254 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2000 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% Module:	sr_profile_run
+% Main authors: nancy
+
+:- module sr_profile_run.
+
+:- interface.
+
+:- import_module io, hlds_module. 
+
+:- pred structure_reuse_profiling( module_info::in, io__state::di, 
+			io__state::uo) is det.
+
+%-----------------------------------------------------------------------------%
+:- implementation. 
+
+:- import_module list, map, bool, std_util. 
+
+:- import_module hlds_pred.
+:- import_module globals, options, passes_aux, prog_out. 
+:- import_module pa_alias_as.
+:- import_module sr_profile, sr_data.
+:- import_module hlds_goal.
+
+
+structure_reuse_profiling( HLDS ) -->
+	globals__io_lookup_bool_option(very_verbose, Verbose), 
+	maybe_write_string( Verbose, 
+			"% Collecting reuse-profiling information... " ), 
+
+	{ collect_profiling_information( HLDS, Profiling) }, 
+	{ module_info_name( HLDS, ModuleName ) }, 
+	{ prog_out__sym_name_to_string( ModuleName, ModuleNameString) }, 
+	sr_profile__write_profiling( ModuleNameString, Profiling ), 
+	maybe_write_string( Verbose, "done.\n"). 
+
+:- pred collect_profiling_information( module_info::in, 
+		profiling_info::out ) is det.
+
+collect_profiling_information( HLDS, Prof ) :- 
+	sr_profile__init(Prof0), 
+	module_info_predids( HLDS, PredIds0 ), 
+	module_info_get_special_pred_map( HLDS, Map), 
+	map__values( Map, SpecialPredIds ), 
+	list__filter(
+		pred( Id::in ) is semidet :- 
+		( \+ member(Id, SpecialPredIds), 
+		  \+ hlds_module__pred_not_defined_in_this_module(HLDS, Id) 
+		), 
+		PredIds0,
+		PredIds), 
+	list__foldl(
+		collect_profiling_information_2( HLDS ), 
+		PredIds, 
+		Prof0,
+		Prof).
+
+:- pred collect_profiling_information_2( module_info::in, pred_id::in, 
+			profiling_info::in, profiling_info::out) is det.
+collect_profiling_information_2( HLDS, PredId, Prof0, Prof):- 
+	module_info_pred_info( HLDS, PredId, PredInfo), 
+	pred_info_import_status( PredInfo, ImportStatus), 
+	pred_info_procedures( PredInfo, Procedures ), 
+	map__values( Procedures, ProcInfos ), 
+	list__foldl(
+		collect_profiling_information_3( HLDS, ImportStatus),
+		ProcInfos, 
+		Prof0, 
+		Prof).
+
+:- pred collect_profiling_information_3( module_info::in,
+			import_status::in, proc_info::in,
+			profiling_info::in, profiling_info::out) is det.
+
+collect_profiling_information_3( HLDS, ImportStatus, ProcInfo)  --> 
+	% first record some info about the procedure in general... 
+	{ 
+		status_is_exported(ImportStatus, IsExported),
+
+		proc_info_reuse_information( ProcInfo, ReuseInfo),
+		(
+			ReuseInfo = yes(List)
+		->
+			Reuse = yes,
+			(
+				List = []
+			->
+				UnconditionalReuse = yes,
+				DefinedInModule =  yes
+			;
+				UnconditionalReuse = no,
+				DefinedInModule = no
+			)
+		;
+			Reuse = no, 
+			UnconditionalReuse = no,
+			DefinedInModule = yes
+		),
+		proc_info_possible_aliases( ProcInfo, PosAliases ), 
+		(
+			PosAliases = yes(As)
+		->
+			(
+				is_bottom(As)
+			->
+				AliasSize = 0, 
+				BottomAlias = yes, 
+				TopAlias = no
+			;
+				(
+					is_top(As)
+				->
+					AliasSize = 0,
+					BottomAlias = no, 
+					TopAlias = yes
+				;
+					AliasSize = size(As),
+					BottomAlias = no, 
+					TopAlias = no
+				)
+			)
+		;
+			AliasSize = 0, 
+			BottomAlias = no, 
+			TopAlias = yes
+		)
+	}, 	
+	% 1. if reuse procedure with conditions, then it was not defined in
+	% this module initially. 
+	maybe_increment([DefinedInModule], inc_procs_defined), 
+	% 2. reuse procedure?
+	maybe_increment([Reuse], inc_reuse_procs), 
+	% 3. unconditional reuse procedure?
+	maybe_increment([UnconditionalReuse], inc_uncond_reuse_procs),
+	% 4. just count the proc
+	inc_procs_counted,
+	% 5. exported proc?
+	maybe_increment([IsExported], inc_exported_procs), 
+	% 6. exported reuse proc?
+	maybe_increment([IsExported,Reuse], inc_exported_reuse_procs), 
+	maybe_increment([IsExported, UnconditionalReuse], 
+			inc_exported_uncond_reuse_procs),
+	% 8. aliases?
+	inc_aliases(AliasSize),
+	% 9. alias bottom?
+	maybe_increment([BottomAlias], inc_bottom_procs), 
+	% 10. alias top?
+	maybe_increment([TopAlias], inc_top_procs),
+
+	{ proc_info_goal( ProcInfo, Goal ) }, 
+	collect_profiling_information_4( HLDS, Goal ).
+
+:- pred collect_profiling_information_4( module_info::in, hlds_goal::in, 
+		profiling_info::in, profiling_info::out) is det.
+
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = conj(Goals),
+	list__foldl( collect_profiling_information_4(HLDS),
+			Goals, Prof0, Prof). 
+collect_profiling_information_4( HLDS, Expr - Info, Prof0, Prof ) :- 
+	Expr = call( PredId, ProcId, _, _, _, _), 
+	inc_pred_calls(Prof0, Prof1),
+	goal_info_get_reuse( Info, Reuse ),
+	(
+		Reuse = reuse(ShortReuse),
+		ShortReuse = reuse_call
+	->
+		inc_reuse_calls( Prof1, Prof )
+	;
+		module_info_structure_reuse_info(HLDS, ReuseInfo),
+		ReuseInfo = structure_reuse_info(ReuseMap),
+		(
+			map__contains(ReuseMap, proc(PredId, ProcId))
+		->
+			inc_no_reuse_calls( Prof1, Prof )
+		;
+			Prof = Prof1
+		)
+	).
+collect_profiling_information_4( _HLDS, Expr - _Info, Prof, Prof ) :- 
+	Expr = generic_call( _, _, _, _). 
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = switch(_, _, Cases, _), 
+	list__foldl( 
+		pred(C::in, P0::in, P::out) is det :-
+		(	
+			C = case(_, G),
+			collect_profiling_information_4(HLDS, G, P0, P)
+		), 
+		Cases,
+		Prof0, 
+		Prof).
+collect_profiling_information_4( _HLDS, Expr - Info, Prof0, Prof ) :- 
+	Expr = unify(_, _, _, Unification, _), 
+	(
+		Unification = deconstruct(_, _, _, _, _, _)
+	-> 
+		inc_deconstructs( Prof0, Prof1),
+		goal_info_get_reuse( Info, Reuse), 
+		(
+			Reuse = reuse(ShortReuse), 
+			ShortReuse = cell_died
+		->
+			inc_direct_reuses( Prof1, Prof)
+		;
+			Prof = Prof1
+		)
+	;
+		Prof = Prof0
+	).
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = disj(Goals, _),
+	list__foldl( collect_profiling_information_4(HLDS), 
+			Goals, Prof0, Prof). 
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = not(Goal), 
+	collect_profiling_information_4( HLDS, Goal, Prof0, Prof). 
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = some(_, _, Goal), 
+	collect_profiling_information_4( HLDS, Goal, Prof0, Prof). 
+collect_profiling_information_4( HLDS, Expr - _Info, Prof0, Prof ) :- 
+	Expr = if_then_else(_, If, Then, Else, _), 
+	collect_profiling_information_4( HLDS, If, Prof0, Prof1), 
+	collect_profiling_information_4( HLDS, Then, Prof1, Prof2), 
+	collect_profiling_information_4( HLDS, Else, Prof2, Prof). 
+collect_profiling_information_4( _HLDS, Expr - _Info, Prof, Prof ) :- 
+	Expr = pragma_foreign_code(_, _, _, _, _, _, _, _). 
+collect_profiling_information_4( _HLDS, Expr - _Info, Prof, Prof ) :- 
+	Expr = par_conj(_, _).
+collect_profiling_information_4( _HLDS, Expr - _Info, Prof, Prof ) :- 
+	Expr = bi_implication(_, _).
+
+		
+		
+:- pred maybe_increment( list(bool), pred( profiling_info, profiling_info), 
+			profiling_info, profiling_info).
+:- mode maybe_increment( in, pred(in, out) is det, in, out) is det.
+
+maybe_increment( Bools, IncOp, Prof0, Prof ) :- 
+	bool__and_list( Bools, Result ), 
+	(
+		Result = yes
+	->
+		IncOp( Prof0, Prof)
+	;
+		Prof = Prof0
+	).
+
Index: structure_reuse.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/structure_reuse.m,v
retrieving revision 1.1.2.5
diff -u -r1.1.2.5 structure_reuse.m
--- structure_reuse.m	2000/10/17 12:53:26	1.1.2.5
+++ structure_reuse.m	2000/10/18 22:33:33
@@ -54,6 +54,7 @@
 
 :- import_module passes_aux, sr_direct, sr_indirect, sr_split, sr_util.
 :- import_module list, map, varset, std_util, int, bool.
+:- import_module sr_profile_run.
 
 structure_reuse(HLDS0, HLDS) -->
 	{ module_info_get_special_pred_map(HLDS0, SpecialPredMap) },
@@ -70,7 +71,8 @@
 		% Do the fixpoint computation to determine all the indirect
 		% reuse, and the implied conditions.
 	sr_indirect__compute_fixpoint(HLDS1, HLDS2),
-	sr_split__create_multiple_versions(HLDS0, HLDS2, HLDS).
+	sr_split__create_multiple_versions(HLDS0, HLDS2, HLDS), 
+	sr_profile_run__structure_reuse_profiling(HLDS). 
 
 
 write_pragma_reuse_info( HLDS, SpecPredIds, PredId ) --> 

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