[m-rev.] for review: module to read trace counts

Peter Wang wangp at students.cs.mu.OZ.AU
Tue Jan 11 14:25:55 AEDT 2005


For review by anyone.

Estimated hours taken: 10

This adds a module libs__trace_counts that reads in the .mercury_trace_counts
files produced by the compiler's trace mechanism.  The format of said files
was slightly changed.

compiler/trace_counts.m:
	New module.

compiler/libs.m:
	Add trace_counts to the libs module.

runtime/mercury_trace_base.c:
	In the format of .mercury_trace_counts, write module and predicate
	names using quoted atom syntax so that names with spaces and
	non-printable characters can be machine-parsed.


Index: compiler/libs.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/libs.m,v
retrieving revision 1.3
diff -u -r1.3 libs.m
--- compiler/libs.m	16 Mar 2003 08:01:27 -0000	1.3
+++ compiler/libs.m	10 Jan 2005 05:41:19 -0000
@@ -26,6 +26,9 @@
 :- include_module process_util.
 :- include_module timestamp.
 
+% parsing trace files
+:- include_module trace_counts.
+
 :- end_module libs.
 
 
%-----------------------------------------------------------------------------%
Index: compiler/trace_counts.m
===================================================================
RCS file: compiler/trace_counts.m
diff -N compiler/trace_counts.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ compiler/trace_counts.m	11 Jan 2005 00:19:05 -0000
@@ -0,0 +1,228 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2005 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% File: trace_counts.m.
+%
+% Author: wangp.
+%
+% This module defines a predicate to read in the execution traces generated
+% by programs compiled using the compiler's tracing options.
+
+%-----------------------------------------------------------------------------%
+
+:- module libs__trace_counts.
+
+:- interface.
+
+:- import_module backend_libs.
+:- import_module backend_libs__proc_label.
+:- import_module libs__trace_params.
+:- import_module mdbcomp.
+:- import_module mdbcomp__program_representation.
+
+:- import_module io, map, std_util.
+
+:- type trace_counts		== map(proc_label, proc_trace_counts).
+
+:- type proc_trace_counts	== map(path_port, int).
+
+:- type path_port
+        --->    port_only(trace_port)
+        ;       path_only(mdbcomp__program_representation__goal_path)
+        ;       port_and_path(
+			trace_port,
+			mdbcomp__program_representation__goal_path
+		)
+	.
+
+:- pred read_trace_counts(string::in, maybe(trace_counts)::out, io::di, 
io::uo)
+	is det.
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module hlds.
+:- import_module hlds__hlds_pred.
+:- import_module parse_tree.
+:- import_module parse_tree__prog_data.
+:- import_module parse_tree__prog_out.
+:- import_module parse_tree__prog_util.
+
+:- import_module char, exception, int, io, lexer, list, require, string, 
svmap.
+
+read_trace_counts(FileName, MaybeTraceCounts, !IO) :-
+        io__open_input(FileName, Result, !IO),
+        (
+		Result = ok(FileStream),
+                io__set_input_stream(FileStream, OldInputStream, !IO),
+		promise_only_solution_io(read_trace_counts_2, MaybeTraceCounts,
+			!IO),
+                io__set_input_stream(OldInputStream, _, !IO),
+                io__close_input(FileStream, !IO)
+        ;
+		Result = error(_),
+		MaybeTraceCounts = no
+	).
+
+:- pred read_trace_counts_2(maybe(trace_counts)::out, io::di, io::uo)
+	is cc_multi.
+
+read_trace_counts_2(MaybeTraceCounts, !IO) :-
+	try_io(read_trace_counts_3(map__init), Result, !IO),
+	(
+		Result = succeeded(TraceCounts),
+		MaybeTraceCounts = yes(TraceCounts)
+	;
+		Result = exception(Exception),
+		MaybeTraceCounts = no,
+		( Exception = univ(IOError) ->
+			io__error_message(IOError, Message)
+		; Exception = univ(Message0) ->
+			Message = Message0
+		;
+			error("read_trace_counts_2: unexpected exception type")
+		),
+		report_error(Message, !IO)
+	;
+		Result = failed,
+		error("read_trace_counts_2: IO failure")
+	).
+
+:- pred read_trace_counts_3(trace_counts::in, trace_counts::out,
+	io::di, io::uo) is det.
+
+read_trace_counts_3(!TraceCounts, !IO) :-
+	io__get_line_number(LineNum, !IO),
+	io__read_line_as_string(Result, !IO),
+	(
+		Result = ok(Line),
+		read_proc_trace_counts(LineNum, Line, !TraceCounts, !IO)
+	;
+		Result = eof
+	;
+		Result = error(Error),
+		throw(Error)
+	).
+
+:- pred read_proc_trace_counts(int::in, string::in, trace_counts::in,
+	trace_counts::out, io::di, io::uo) is det.
+
+read_proc_trace_counts(HeaderLineNum, HeaderLine, !TraceCounts, !IO) :-
+	lexer__string_get_token_list(HeaderLine, string__length(HeaderLine), 
+		TokenList, posn(HeaderLineNum, 1, 0), _),
+	(if
+		TokenList =
+			token_cons(name("proc"), _,
+			token_cons(name(PredOrFuncStr), _,
+			token_cons(name(ModuleStr), _,
+			token_cons(name(Name), _,
+			token_cons(integer(Arity), _,
+			token_cons(integer(ModeInt), _,
+			token_nil)))))),
+		string_to_pred_or_func(PredOrFuncStr, PredOrFunc)
+	then
+		string_to_sym_name(ModuleStr, ".", ModuleName),
+		proc_id_to_int(Mode, ModeInt),
+		ProcLabel = proc(ModuleName, PredOrFunc, ModuleName, Name,
+				Arity, Mode),
+		% For whatever reason some of the trace counts for a single
+		% procedure or function can be split over multiple spans.
+		% We collate them as if they appeared in a single span.
+		(if svmap__remove(ProcLabel, Probe, !TraceCounts) then
+			ProcData = Probe
+		else
+			ProcData = map__init
+		),
+		read_proc_trace_counts_2(ProcLabel, ProcData, !TraceCounts, 
+			!IO)
+	else
+		string__format("parse error on line %d of execution trace",
+			[i(HeaderLineNum)], Message),
+		throw(Message)
+	).
+
+:- pred read_proc_trace_counts_2(proc_label::in, proc_trace_counts::in,
+	trace_counts::in, trace_counts::out, io::di, io::uo) is det.
+
+read_proc_trace_counts_2(ProcLabel, ProcCounts0, !TraceCounts, !IO) :-
+	io__get_line_number(LineNum, !IO),
+	io__read_line_as_string(Result, !IO),
+	(
+		Result = ok(Line),
+		(if parse_path_port_line(Line, PathPort, Count) then
+			map__det_insert(ProcCounts0, PathPort, Count,
+				ProcCounts),
+			read_proc_trace_counts_2(ProcLabel, ProcCounts,
+				!TraceCounts, !IO)
+		else
+			svmap__det_insert(ProcLabel, ProcCounts0,
+				!TraceCounts),
+			read_proc_trace_counts(LineNum, Line,
+				!TraceCounts, !IO)
+		)
+	;
+		Result = eof,
+		svmap__det_insert(ProcLabel, ProcCounts0, !TraceCounts)
+	;
+		Result = error(Error),
+		throw(Error)
+	).
+
+:- pred parse_path_port_line(string::in, path_port::out, int::out) is 
semidet.
+
+parse_path_port_line(Line, PathPort, Count) :-
+	Words = string__words(Line),
+	(
+		Words = [Word1, CountStr],
+		( Port = string_to_trace_port(Word1) ->
+			PathPort = port_only(Port)
+		; Path = string_to_goal_path(Word1) ->
+			PathPort = path_only(Path)
+		;
+			fail
+		),
+		string__to_int(CountStr, Count)
+	;
+		Words = [PortStr, PathStr, CountStr],
+		Port = string_to_trace_port(PortStr),
+		Path = string_to_goal_path(PathStr),
+		PathPort = port_and_path(Port, Path),
+		string__to_int(CountStr, Count)
+	).
+
+:- pred string_to_pred_or_func(string::in, pred_or_func::out) is semidet.
+
+string_to_pred_or_func("p", predicate).
+string_to_pred_or_func("f", function).
+
+:- func string_to_trace_port(string) = trace_port is semidet.
+
+string_to_trace_port("CALL") = call.
+string_to_trace_port("EXIT") = exit.
+string_to_trace_port("REDO") = redo.
+string_to_trace_port("FAIL") = fail.
+string_to_trace_port("EXCP") = exception.
+string_to_trace_port("COND") = ite_cond.
+string_to_trace_port("THEN") = ite_then.
+string_to_trace_port("ELSE") = ite_else.
+string_to_trace_port("NEGE") = neg_enter.
+string_to_trace_port("NEGS") = neg_success.
+string_to_trace_port("NEGF") = neg_failure.
+string_to_trace_port("DISJ") = disj.
+string_to_trace_port("SWTC") = switch.
+string_to_trace_port("FRST") = nondet_pragma_first.
+string_to_trace_port("LATR") = nondet_pragma_later.
+
+:- func string_to_goal_path(string) =
+	mdbcomp__program_representation__goal_path is semidet.
+
+string_to_goal_path(String) = Path :-
+	string__prefix(String, "<"),
+	string__suffix(String, ">"),
+	string__length(String, Length),
+	string__substring(String, 1, Length-2, SubString),
+	mdbcomp__program_representation__path_from_string(SubString, Path).
Index: runtime/mercury_trace_base.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_trace_base.c,v
retrieving revision 1.59
diff -u -r1.59 mercury_trace_base.c
--- runtime/mercury_trace_base.c	10 Jan 2005 05:23:50 -0000	1.59
+++ runtime/mercury_trace_base.c	11 Jan 2005 03:03:35 -0000
@@ -200,6 +200,9 @@
 
 static MR_PathPort MR_named_count_port[MR_PORT_NONE + 1];
 
+static void
+MR_trace_write_quoted_atom(FILE *fp, const char *atom);
+
 void
 MR_trace_write_label_exec_counts(FILE *fp)
 {
@@ -252,11 +255,15 @@
                 {
                     id = &proc->MR_sle_user;
                     if (proc != prev_proc) {
-                        fprintf(fp, "proc %c %s %s %d %d\n",
+                        fprintf(fp, "proc %c ",
                             ( id->MR_user_pred_or_func == MR_PREDICATE
-                                ? 'p' : 'f'),
-                            id->MR_user_decl_module,
-                            id->MR_user_name,
+                                ? 'p' : 'f'));
+                        MR_trace_write_quoted_atom(fp,
+                            id->MR_user_decl_module);
+                        fputc(' ', fp);
+                        MR_trace_write_quoted_atom(fp,
+                            id->MR_user_name);
+                        fprintf(fp, " %d %d\n",
                             id->MR_user_arity,
                             id->MR_user_mode);
                     }
@@ -293,6 +300,51 @@
             }
         }
     }
+}
+
+/*
+** The output of this is supposed to be equivalent to term_io__quote_atom
+** except that it always uses quotes, even if not strictly necessary.
+*/
+static void
+MR_trace_write_quoted_atom(FILE *fp, const char *atom)
+{
+    const char *c;
+
+    fputc('\'', fp);
+    for (c = atom; *c != '\0'; c++) {
+        switch (*c) {
+            case '\'':
+                fputs("\\'", fp);
+                break;
+            case '"':
+                fputs("\\\"", fp);
+                break;
+            case '\\':
+                fputs("\\\\", fp);
+                break;
+            case '\n':
+                fputs("\\n", fp);
+                break;
+            case '\t':
+                fputs("\\t", fp);
+                break;
+            case '\b':
+                fputs("\\b", fp);
+                break;
+            default:
+                /* This assumes isalnum is the same as char__isalnum. */
+                if (isalnum(*c) ||
+                    strchr(" !@#$%^&*()-_+=`~{}[];:'\"<>.,/?\\|", *c))
+                {
+                    fputc(*c, fp);
+                } else {
+                    fprintf(fp, "\\%03o\\", *c);
+                }
+                break;
+        }
+    }
+    fputc('\'', fp);
 }
 
 #ifdef  MR_TABLE_DEBUG


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