[m-rev.] for review: coverage testing

Zoltan Somogyi zs at csse.unimelb.edu.au
Wed Sep 20 14:16:54 AEST 2006


On 20-Sep-2006, Julien Fischer <juliensf at csse.unimelb.edu.au> wrote:
> I would prefer a different name for this, mcov for example, mct is
> too similar to mtc.

I followed this suggestion, as well as all of Ian's suggestions with
the exception of documentation and a test case (which will come later).
In the process, I managed to find and fix the bug, so I have actually
been able to create test coverage output for the compiler itself.

The updated Log file and the interdiff follow. I will commit this diff
tomorrow after a final bootcheck.

Zoltan.

Implement coverage testing. The output format is a bit crude, but people
have been asking for this capability.

The main problem tackled in this diff is that coverage testing requires
gathering information from a lot of program executions, and the execution count
files for all these executions require a huge amount of disk space. We now
therefore put a limit on the number of files we keep; when this limit is
exceeded, the program execution that reaches the limit will automatically
summarize all these files back into a single file before it exits.

This diff also tackles the same problem along a different axis by changing
the format of execution count files to make them smaller. One way is to factor
out and represent just once some information that is common to many procedures:
the file name and the module name. Another is to abbreviate some keywords,
e.g. "fproc" instead of "proc function". The third is not to write out the
defining module's name unless it differs from the declaring module's name,
which it almost never does. (The two differ only when the compiler is invoked
with intermodule optimization, and creates a specialized version of a predicate
in a module other than its home module.)

Since we are changing the trace count file format anyway, make another change
useful for coverage testing: record the entire provenance of the trace counts
in the file, including the name of the program and what files went into unions
and diffs of trace count files.

When doing coverage testing of the compiler, the compiler *must* be in a debug
grade. However, the tools for summarizing trace files, invoked from the
compiler executable when the compiler is being coverage tested, *cannot* be
in debug grade, because debug grade disables tail recursion, and without tail
recursion the summarization program runs out of stack space. This diff
therefore arranges for the slice directory to not be affected by the parameters
applying to the rest of the workspace (including the top level Mmake.params).

Mmakefile:
	Don't apply the top level mmake's parameters to recursive mmakes in
	the slice directory.

	Factor out some common code.

mdbcomp/trace_counts.m:
	Update the parsing code to parse the new format for trace count files,
	and update the code for writing out trace counts to generate the new
	format.

	Replace the proc_label_and_filename type with the proc_label_in_context
	type, which makes it easier to keep track of the current module as well
	as the current file (this is required by the new, more compact format
	for trace count files).

	When considering the union of multiple trace counts files, keep track
	of whether they contained all counts or just the nonzero counts. This
	requires keeping track of this info for single files as well.

	Provide ways to represent and to compute differences between trace
	count files, to support the new program in slice/mtc_diff.m.

mdbcomp/slice_and_dice.m:
	Reformat to conform to our Mercury style guide.

	Conform to the change to trace_counts.m.

compiler/tupling.m:
	Conform to the change to mdbcomp.

runtime/mercury_wrapper.c:
	Implement the new option values used to implement coverage testing.
	These allow control of the limit on the number of execution count
	files, and collecting execution counts only from a specified
	executable.

	Add MR_ prefixes.

runtime/mercury_trace_base.[ch]:
	Provide the mechanism for summarizing execution counts when we reach
	the limit on the number of execution counts files.

	Update the code that writes out trace counts files to generate
	the new format for trace counts files. Make this code take the boolean
	that says whether to include labels with zero counts in the output
	as an explicit parameter, not as a global variable.

	Break up an excessively large function.

scripts/mtc:
	Add the options needed to control the process of automatic
	summarization of trace counts files.

slice/.mgnuc_copts:
slice/.mgnuc_opts:
slice/SLICE_FLAGS.in:
	Make these files empty, since we don't want to refer to the rest of the
	workspace. (We could delete them as well, but CVS doesn't handle
	resurrection of deleted files very well, and we don't want to burn any
	bridges.)

slice/Mmakefile:
	Add the new executables, and make the code in this directory
	independent of the other directories in the workspace.

	Since we need the code of the modules in the mdbcomp directory
	but don't want to link to the object files in that directory (since
	the grades may differ), make copies of those modules in this directory.

slice/mcov.m:
	Add this module, the code for the Mercury coverage test tool.

slice/mtc_diff.m:
	Add this module, the code for computing the diff between two trace
	counts files. The intended use is to compare two trace counts files
	dumped at different stages of execution. (Since foreign_procs can be
	used to invoke the C functions in the runtime that write out the trace
	counts files in the middle of a program's execution, not just the end.)

slice/mdice.m:
slice/mslice.m:
slice/mtc_union.m:
	Convert to four space indentation.

tools/bootcheck:
	Since the slice directory's grade is independent of the grade of the
	other directories, don't copy it to the stage2 and stage3 by default.
	If it is copied, then still compile it (and otherwise handle it)
	separate from the other directories.

	Add an option for gathering coverage test data during bootchecking.

Diffing .
--- /home/zs/mer/ws5/Mmakefile	2006-03-25 01:18:52.000000000 +1100
+++ Mmakefile	2006-09-20 13:14:14.000000000 +1000
@@ -128,13 +128,13 @@
 	+cd compiler && $(SUBDIR_MMAKE) depend
 
 .PHONY: dep_slice
-dep_slice: slice/$(deps_subdir)mct.dep \
+dep_slice: slice/$(deps_subdir)mcov.dep \
 	slice/$(deps_subdir)mslice.dep \
 	slice/$(deps_subdir)mdice.dep \
 	slice/$(deps_subdir)mtc_union.dep \
 	slice/$(deps_subdir)mtc_diff.dep
 
-slice/$(deps_subdir)mct.dep \
+slice/$(deps_subdir)mcov.dep \
 slice/$(deps_subdir)mslice.dep \
 slice/$(deps_subdir)mdice.dep \
 slice/$(deps_subdir)mtc_union.dep \
Diffing analysis
Diffing bindist
Diffing boehm_gc
Diffing boehm_gc/Mac_files
Diffing boehm_gc/cord
Diffing boehm_gc/cord/private
Diffing boehm_gc/doc
Diffing boehm_gc/include
Diffing boehm_gc/include/private
Diffing boehm_gc/libatomic_ops-1.2
Diffing boehm_gc/libatomic_ops-1.2/doc
Diffing boehm_gc/libatomic_ops-1.2/src
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/gcc
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/hpc
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/ibmc
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/icc
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/msftc
Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/sunc
Diffing boehm_gc/libatomic_ops-1.2/tests
Diffing boehm_gc/tests
Diffing boehm_gc/windows-untested
Diffing boehm_gc/windows-untested/vc60
Diffing boehm_gc/windows-untested/vc70
Diffing boehm_gc/windows-untested/vc71
Diffing browser
Diffing bytecode
Diffing compiler
Diffing compiler/notes
Diffing debian
Diffing debian/patches
Diffing deep_profiler
Diffing deep_profiler/notes
Diffing doc
Diffing extras
Diffing extras/cgi
Diffing extras/complex_numbers
Diffing extras/complex_numbers/samples
Diffing extras/complex_numbers/tests
Diffing extras/concurrency
Diffing extras/curs
Diffing extras/curs/samples
Diffing extras/curses
Diffing extras/curses/sample
Diffing extras/dynamic_linking
Diffing extras/error
Diffing extras/gator
Diffing extras/gator/generations
Diffing extras/gator/generations/1
Diffing extras/graphics
Diffing extras/graphics/easyx
Diffing extras/graphics/easyx/samples
Diffing extras/graphics/mercury_glut
Diffing extras/graphics/mercury_opengl
Diffing extras/graphics/mercury_tcltk
Diffing extras/graphics/samples
Diffing extras/graphics/samples/calc
Diffing extras/graphics/samples/gears
Diffing extras/graphics/samples/maze
Diffing extras/graphics/samples/pent
Diffing extras/lazy_evaluation
Diffing extras/lex
Diffing extras/lex/samples
Diffing extras/lex/tests
Diffing extras/logged_output
Diffing extras/moose
Diffing extras/moose/samples
Diffing extras/moose/tests
Diffing extras/morphine
Diffing extras/morphine/non-regression-tests
Diffing extras/morphine/scripts
Diffing extras/morphine/source
Diffing extras/odbc
Diffing extras/posix
Diffing extras/quickcheck
Diffing extras/quickcheck/tutes
Diffing extras/references
Diffing extras/references/samples
Diffing extras/references/tests
Diffing extras/solver_types
Diffing extras/solver_types/library
Diffing extras/stream
Diffing extras/trailed_update
Diffing extras/trailed_update/samples
Diffing extras/trailed_update/tests
Diffing extras/windows_installer_generator
Diffing extras/windows_installer_generator/sample
Diffing extras/windows_installer_generator/sample/images
Diffing extras/xml
Diffing extras/xml/samples
Diffing extras/xml_stylesheets
Diffing java
Diffing java/runtime
Diffing library
Diffing mdbcomp
--- /home/zs/mer/ws5/mdbcomp/trace_counts.m	2006-09-18 13:18:18.000000000 +1000
+++ trace_counts.m	2006-09-19 18:05:56.000000000 +1000
@@ -39,22 +39,26 @@
             % The file contains counts for all labels from user-defined
             % procedures, provided the count is nonzero.
 
+:- type base_count_file_type
+    --->    base_count_file_type(all_or_nonzero, string).
+            % The first argument says whether we have all the counts;
+            % the second gives the name of the program.
+
 :- type trace_count_file_type
-    --->    single_file(all_or_nonzero)
-            % The file contains counts from a single execution, which
-            % wrote out the indicated counts.
+    --->    single_file(base_count_file_type)
+            % The file contains counts from a single execution.
 
-    ;       union_file(int, set(all_or_nonzero))
+    ;       union_file(int, list(trace_count_file_type))
             % The file is a union of some other trace count files.
             % The number of test cases in the union is recorded, and
             % so is the set of kinds of trace count files they came from.
+            % (We represent the set as a sorted list, because we write out
+            % values of trace_count_file_type to files, and we don't want to
+            % expose the implementation of sets.)
 
-    ;       diff_file.
+    ;       diff_file(trace_count_file_type, trace_count_file_type).
             % The file is a difference between two other trace count files.
 
-:- func maybe_sum_trace_count_file_type(trace_count_file_type,
-    trace_count_file_type) = maybe(trace_count_file_type).
-
 :- func sum_trace_count_file_type(trace_count_file_type, trace_count_file_type)
     = trace_count_file_type.
 
@@ -162,8 +166,8 @@
     % tests the trace counts come from.
     %
 :- pred read_and_union_trace_counts(bool::in, slice_source::in,
-    list(string)::in, int::out, set(all_or_nonzero)::out, trace_counts::out,
-    maybe(string)::out, io::di, io::uo) is det.
+    list(string)::in, int::out, set(trace_count_file_type)::out,
+    trace_counts::out, maybe(string)::out, io::di, io::uo) is det.
 
     % write_trace_counts_to_file(FileType, TraceCounts, FileName, Result, !IO):
     %
@@ -355,7 +359,7 @@
     io.open_input(FileName, OpenResult, !IO),
     (
         OpenResult = ok(FileStream),
-        read_trace_counts_list_stream(ShowProgress, union_file(0, set.init),
+        read_trace_counts_list_stream(ShowProgress, union_file(0, []),
             map.init, FileName, FileStream, Result, !IO)
     ;
         OpenResult = error(IOError),
@@ -476,12 +480,11 @@
     io::di, io::uo) is cc_multi.
 
 read_trace_counts_from_cur_stream(ReadResult, !IO) :-
-    io.read_line_as_string(IdResult, !IO),
+    io.read(FileTypeResult, !IO),
     (
-        IdResult = ok(IdStr),
-        IdStrNoNL = string.rstrip(IdStr),
-        string_to_file_type(IdStrNoNL, FileType)
-    ->
+        FileTypeResult = ok(FileType),
+        io.read_line_as_string(NewlineResult, !IO),
+        ( NewlineResult = ok("\n") ->
         try_io(read_trace_counts_setup(map.init), Result, !IO),
         (
             Result = succeeded(TraceCounts),
@@ -501,6 +504,12 @@
         )
     ;
         ReadResult = syntax_error("no info on trace count file type")
+        )
+    ;
+        ( FileTypeResult = eof
+        ; FileTypeResult = error(_, _)
+        ),
+        ReadResult = syntax_error("no info on trace count file type")
     ).
 
 :- pred read_trace_counts_setup(trace_counts::in, trace_counts::out,
@@ -770,15 +779,15 @@
 read_and_union_trace_counts(ShowProgress, SliceSource, Files,
         NumTests, TestKinds, TraceCounts, MaybeError, !IO) :-
     read_and_union_trace_counts_2(ShowProgress, SliceSource, Files,
-        union_file(0, set.init), FileType, map.init, TraceCounts, MaybeError,
-        !IO),
+        union_file(0, []), FileType, map.init, TraceCounts, MaybeError, !IO),
     (
-        FileType = union_file(NumTests, TestKinds)
+        FileType = union_file(NumTests, TestKindList),
+        set.list_to_set(TestKindList, TestKinds)
     ;
         FileType = single_file(_),
         error("read_and_union_trace_counts: single_file")
     ;
-        FileType = diff_file,
+        FileType = diff_file(_, _),
         error("read_and_union_trace_counts: diff_file")
     ).
 
@@ -824,8 +833,9 @@
     trace_counts::in, io::di, io::uo) is det.
 
 write_trace_counts(FileType, TraceCounts, !IO) :-
-    FileTypeStr = file_type_to_string(FileType),
-    io.write_string(FileTypeStr ++ "\n", !IO),
+    io.write(FileType, !IO),
+    io.write_string(".", !IO),
+    io.nl(!IO),
     map.foldl3(write_proc_label_and_file_trace_counts, TraceCounts,
         unqualified(""), _, "", _, !IO).
 
@@ -940,51 +950,58 @@
 
 %-----------------------------------------------------------------------------%
 
-:- func file_type_to_string(trace_count_file_type) = string.
-
-file_type_to_string(single_file(Kind)) =
-    "single " ++ all_or_nonzero_to_string(Kind).
-file_type_to_string(union_file(N, Kinds)) =
-    "union " ++ int_to_string(N)
-        ++ string.append_list(list.map(all_or_nonzero_to_space_string,
-            to_sorted_list(Kinds))).
-file_type_to_string(diff_file) = "diff".
-
-:- func all_or_nonzero_to_space_string(all_or_nonzero) = string.
-
-all_or_nonzero_to_space_string(Kind) = " " ++ all_or_nonzero_to_string(Kind).
-
-:- func all_or_nonzero_to_string(all_or_nonzero) = string.
-
-all_or_nonzero_to_string(user_all) = "all".
-all_or_nonzero_to_string(user_nonzero) = "nonzero".
-
-:- pred string_to_all_or_nonzero(string::in, all_or_nonzero::out) is semidet.
-
-string_to_all_or_nonzero("all", user_all).
-string_to_all_or_nonzero("nonzero", user_nonzero).
-
-:- pred string_to_file_type(string::in, trace_count_file_type::out) is semidet.
-
-string_to_file_type(Str, FileType) :-
-    Words = string.words(Str),
-    Words = [Word1 | Rest],
-    (
-        Word1 = "union",
-        Rest = [NumTestsStr | KindStrs],
-        string.to_int(NumTestsStr, NumTests),
-        list.map(string_to_all_or_nonzero, KindStrs, Kinds),
-        FileType = union_file(NumTests, list_to_set(Kinds))
-    ;
-        Word1 = "single",
-        Rest = [KindStr],
-        string_to_all_or_nonzero(KindStr, Kind),
-        FileType = single_file(Kind)
-    ;
-        Word1 = "diff",
-        Rest = [],
-        FileType = diff_file
-    ).
+% :- func file_type_to_string(trace_count_file_type) = string.
+% 
+% file_type_to_string(single_file(
+% base_count_file_type(Kind, Prog))
+% ) =
+%     "single " ++ all_or_nonzero_to_string(Kind) ++
+%         " " ++ term_io.quoted_atom(Prog).
+% file_type_to_string(union_file(N, KindsProgs)) =
+%     "union " ++ int_to_string(N) ++ " { " ++
+%         string.append_list(list.map(all_or_nonzero_prog_to_space_string,
+%             to_sorted_list(KindsProgs))) ++ " }".
+% file_type_to_string(diff_file(Type1, Type2)) =
+%     "diff [ " ++ file_type_to_string(Type1) ++
+%     " - " ++ file_type_to_string(Type2) ++ " ]".
+% 
+% :- func base_count_file_type_to_space_string(base_count_file_type) = string.
+% 
+% base_count_file_type_to_space_string(base_count_file_type(Kind, Prog)) =
+%     " " ++ all_or_nonzero_to_string(Kind) ++ 
+%     " " ++ term_io.quoted_atom(Prog).
+% 
+% :- func all_or_nonzero_to_string(all_or_nonzero) = string.
+% 
+% all_or_nonzero_to_string(user_all) = "all".
+% all_or_nonzero_to_string(user_nonzero) = "nonzero".
+% 
+% :- pred string_to_all_or_nonzero(string::in, all_or_nonzero::out) is semidet.
+% 
+% string_to_all_or_nonzero("all", user_all).
+% string_to_all_or_nonzero("nonzero", user_nonzero).
+% 
+% :- pred string_to_file_type(string::in, trace_count_file_type::out) is semidet.
+% 
+% string_to_file_type(Str, FileType) :-
+%     Words = string.words(Str),
+%     Words = [Word1 | Rest],
+%     (
+%         Word1 = "union",
+%         Rest = [NumTestsStr | KindStrs],
+%         string.to_int(NumTestsStr, NumTests),
+%         list.map(string_to_all_or_nonzero, KindStrs, Kinds),
+%         FileType = union_file(NumTests, list_to_set(Kinds))
+%     ;
+%         Word1 = "single",
+%         Rest = [KindStr],
+%         string_to_all_or_nonzero(KindStr, Kind),
+%         FileType = single_file(Kind)
+%     ;
+%         Word1 = "diff",
+%         Rest = [],
+%         FileType = diff_file
+%     ).
 
 %-----------------------------------------------------------------------------%
 
@@ -1012,53 +1029,56 @@
 
 num_tests_for_file_type(union_file(N, _)) = N.
 num_tests_for_file_type(single_file(_)) = 1.
-num_tests_for_file_type(diff_file) = -1.
-
-maybe_sum_trace_count_file_type(Type1, Type2) = MaybeType :-
+num_tests_for_file_type(diff_file(_, _)) = -1.
 
+sum_trace_count_file_type(Type1, Type2) = UnionType :-
     (
-        Type1 = single_file(Kind1),
-        Type2 = single_file(Kind2),
-        MaybeType = yes(union_file(2, list_to_set([Kind1, Kind2])))
+        Type1 = single_file(_),
+        Type2 = single_file(_),
+        UnionType = union_file(2, sort_and_remove_dups([Type1, Type2]))
     ;
-        Type1 = single_file(Kind1),
-        Type2 = union_file(N, Kinds2),
-        MaybeType = yes(union_file(N + 1, set.insert(Kinds2, Kind1)))
+        Type1 = single_file(_),
+        Type2 = union_file(N, IncludedTypes2),
+        UnionType = union_file(N + 1,
+            insert_into_list_as_set(IncludedTypes2, Type1))
     ;
         Type1 = single_file(_),
-        Type2 = diff_file,
-        MaybeType = no
+        Type2 = diff_file(_, _),
+        UnionType = union_file(2, sort_and_remove_dups([Type1, Type2]))
+    ;
+        Type1 = union_file(N, IncludedTypes1),
+        Type2 = single_file(_),
+        UnionType = union_file(N + 1,
+            insert_into_list_as_set(IncludedTypes1, Type2))
     ;
-        Type1 = union_file(N, Kinds1),
-        Type2 = single_file(Kind2),
-        MaybeType = yes(union_file(N + 1, set.insert(Kinds1, Kind2)))
-    ;
-        Type1 = union_file(N1, Kinds1),
-        Type2 = union_file(N2, Kinds2),
-        MaybeType = yes(union_file(N1 + N2, set.union(Kinds1, Kinds2)))
-    ;
-        Type1 = union_file(_, _),
-        Type2 = diff_file,
-        MaybeType = no
+        Type1 = union_file(N1, IncludedTypes1),
+        Type2 = union_file(N2, IncludedTypes2),
+        UnionType = union_file(N1 + N2,
+            sort_and_remove_dups(IncludedTypes1 ++ IncludedTypes2))
+    ;
+        Type1 = union_file(N, IncludedTypes1),
+        Type2 = diff_file(_, _),
+        UnionType = union_file(N + 1,
+            insert_into_list_as_set(IncludedTypes1, Type2))
     ;
-        Type1 = diff_file,
+        Type1 = diff_file(_, _),
         Type2 = single_file(_),
-        MaybeType = no
+        UnionType = union_file(2, sort_and_remove_dups([Type1, Type2]))
     ;
-        Type1 = diff_file,
-        Type2 = union_file(_, _),
-        MaybeType = no
+        Type1 = diff_file(_, _),
+        Type2 = union_file(N, IncludedTypes2),
+        UnionType = union_file(N + 1,
+            insert_into_list_as_set(IncludedTypes2, Type1))
     ;
-        Type1 = diff_file,
-        Type2 = diff_file,
-        MaybeType = no
+        Type1 = diff_file(_, _),
+        Type2 = diff_file(_, _),
+        UnionType = union_file(2, sort_and_remove_dups([Type1, Type2]))
     ).
 
-sum_trace_count_file_type(Type1, Type2) = Type :-
-    maybe_sum_trace_count_file_type(Type1, Type2) = MaybeType,
-    (
-        MaybeType = yes(Type)
-    ;
-        MaybeType = no,
-        error("sum_trace_count_file_type: inconsistent file types")
-    ).
+:- func insert_into_list_as_set(list(T), T) = list(T).
+
+insert_into_list_as_set(List0, Item) = List :-
+    set.list_to_set(List0, Set0),
+    set.insert(Set0, Item, Set),
+    set.to_sorted_list(Set, List).
+    
Diffing profiler
Diffing robdd
Diffing runtime
--- /home/zs/mer/ws5/runtime/mercury_trace_base.c	2006-09-19 10:00:34.000000000 +1000
+++ mercury_trace_base.c	2006-09-20 13:20:27.000000000 +1000
@@ -234,8 +234,8 @@
 #define INIT_MODULE_TABLE_SIZE  10
 
 const MR_Module_Layout  **MR_module_infos;
-int                     MR_module_info_next = 0;
-int                     MR_module_info_max  = 0;
+unsigned                MR_module_info_next = 0;
+unsigned                MR_module_info_max  = 0;
 
 void
 MR_insert_module_info_into_module_table(const MR_Module_Layout *module)
@@ -251,15 +251,16 @@
 }
 
 static  void    MR_trace_write_quoted_atom(FILE *fp, const char *atom);
-static  void    MR_trace_write_label_exec_counts_for_file(FILE *fp,
+static  void        MR_trace_write_string(FILE *fp, const char *atom);
+static  unsigned    MR_trace_write_label_exec_counts_for_file(FILE *fp,
                     const MR_Module_Layout *module,
-                    const MR_Module_File_Layout *file, const char *module_name,
+                        const MR_Module_File_Layout *file,
+                        const char *module_name,
                     MR_bool coverage_test);
 
 MR_PathPort     MR_named_count_port[MR_PORT_NONE + 1];
 
 #define MERCURY_TRACE_COUNTS_PREFIX     "mercury_trace_counts"
-#define UNION_CMD                       "mtc_union -o"
 #define TEMP_SUFFIX                     ".tmp"
 
 #define MR_FILE_EXISTS(filename)        (access(filename, F_OK) == 0)
@@ -268,28 +269,36 @@
 MR_trace_record_label_exec_counts(void *dummy)
 {
     FILE    *fp;
-    int     len;
     char    *name;
+    unsigned    name_len;
     MR_bool summarize;
+    MR_bool     keep;
+    char        *slash;
+    const char  *program_name;
+
+    program_name = MR_copy_string(MR_progname);
+    slash = strrchr(program_name, '/');
+    if (slash != NULL) {
+        program_name = slash + 1;
+    }
 
     summarize = MR_FALSE;
+    keep = MR_FALSE;
     if (MR_trace_count_summary_file != NULL) {
-        name = MR_copy_string(MR_trace_count_summary_file);
-
-        if (MR_FILE_EXISTS(name)) {
+        if (MR_FILE_EXISTS(MR_trace_count_summary_file)) {
             int     i;
 
             /* 30 bytes must be enough for the dot, the value of i, and '\0' */
-            len = strlen(MR_trace_count_summary_file) + 30;
-            name = MR_malloc(len);
+            name_len = strlen(MR_trace_count_summary_file) + 30;
+            name = MR_malloc(name_len);
 
             fp = NULL;
             /* search for a suffix that doesn't exist yet */
             for (i = 1; i <= MR_trace_count_summary_max; i++) {
-                snprintf(name, len, "%s.%d", MR_trace_count_summary_file, i);
+                snprintf(name, name_len, "%s.%d",
+                    MR_trace_count_summary_file, i);
                 if (! MR_FILE_EXISTS(name)) {
                     /* file doesn't exist, commit to this one */
-                    fp = fopen(name, "w");
                     if (i == MR_trace_count_summary_max) {
                         summarize = MR_TRUE;
                     }
@@ -298,12 +307,14 @@
                 }
             }
         } else {
-            /* the summary file doesn't yet exist, create it */
-            fp = fopen(name, "w");
+            /*
+            ** The summary file doesn't yet exist, create it.
+            */
+            name = MR_copy_string(MR_trace_count_summary_file);
         }
-    } else {
-        if (MR_trace_counts_file) {
-            name = MR_trace_counts_file;
+    } else if (MR_trace_counts_file) {
+        name = MR_copy_string(MR_trace_counts_file);
+        keep = MR_TRUE;
         } else {
             char    *s;
 
@@ -313,11 +324,11 @@
             */
 
             /* 100 bytes must be enough for the process id, dots and '\0' */
-            len = strlen(MERCURY_TRACE_COUNTS_PREFIX) + strlen(MR_progname)
+        name_len = strlen(MERCURY_TRACE_COUNTS_PREFIX) + strlen(program_name)
                 + 100;
-            name = MR_malloc(len);
-            snprintf(name, len, ".%s.%s.%d", MERCURY_TRACE_COUNTS_PREFIX,
-                MR_progname, getpid());
+        name = MR_malloc(name_len);
+        snprintf(name, name_len, ".%s.%s.%d", MERCURY_TRACE_COUNTS_PREFIX,
+            program_name, getpid());
 
             /* make sure name is an acceptable filename */
             for (s = name; *s != '\0'; s++) {
@@ -328,11 +339,22 @@
         }
 
         fp = fopen(name, "w");
-    }
-
     if (fp != NULL) {
-        MR_trace_write_label_exec_counts(fp, MR_coverage_test_enabled);
+        unsigned    num_written;
+
+        num_written = MR_trace_write_label_exec_counts(fp,
+            program_name, MR_coverage_test_enabled);
         (void) fclose(fp);
+
+        if (num_written == 0 && !keep) {
+            /*
+            ** We did not write out any trace counts, so there is nothing
+            ** to gather.
+            */
+
+            (void) unlink(name);
+            summarize = MR_FALSE;
+        }
     } else {
         fprintf(stderr, "%s: %s\n", name, strerror(errno));
         /*
@@ -346,19 +368,22 @@
 
     if (summarize) {
         char        *cmd;
-        int         cmd_len;
-        int         status;
+        unsigned    cmd_len;
+        int         summary_status;
+        int         mv_status;
+        int         unlink_status;
         int         i;
         const char  *old_options;
 
         /* 30 bytes must be enough for the dot, the value of i, and space */
-        len = strlen(MR_trace_count_summary_file) + 30;
-        name = MR_malloc(len);
+        name_len = strlen(MR_trace_count_summary_file) + 30;
+        name = MR_malloc(name_len);
 
         cmd_len = strlen(MR_trace_count_summary_cmd) + 4;
         cmd_len += strlen(MR_trace_count_summary_file)
             + strlen(TEMP_SUFFIX) + 1;
-        cmd_len += (MR_trace_count_summary_max + 1) * len;
+        cmd_len += (MR_trace_count_summary_max + 1) * name_len;
+        cmd_len += 100;
 
         cmd = MR_malloc(cmd_len);
 
@@ -368,63 +393,45 @@
         strcat(cmd, TEMP_SUFFIX);
         strcat(cmd, " ");
         strcat(cmd, MR_trace_count_summary_file);
-        strcat(cmd, " ");
 
         for (i = 1; i <= MR_trace_count_summary_max; i++) {
-            snprintf(name, len, "%s.%d", MR_trace_count_summary_file, i);
-            strcat(cmd, name);
+            snprintf(name, name_len, "%s.%d", MR_trace_count_summary_file, i);
             strcat(cmd, " ");
+            strcat(cmd, name);
         }
 
-#if 1
-        fp = fopen("/tmp/zs_summaries", "a");
-        if (fp != NULL) {
-            fprintf(fp, "alloc=%d\n", cmd_len);
-            fflush(fp);
-            fprintf(fp, "len=%d\n", strlen(cmd));
-            fflush(fp);
-            fprintf(fp, "%s\n", cmd);
-            fflush(fp);
-            fclose(fp);
-        }
-#endif
+        strcat(cmd, " > /dev/null 2>&1");
 
         old_options = getenv("MERCURY_OPTIONS");
         if (old_options != NULL) {
             (void) setenv("MERCURY_OPTIONS", "", MR_TRUE);
-            status = system(cmd);
+            summary_status = system(cmd);
             (void) setenv("MERCURY_OPTIONS", old_options, MR_TRUE);
         } else {
-            status = system(cmd);
+            summary_status = system(cmd);
         }
 
-        if (status == 0) {
+        if (summary_status == 0) {
             strcpy(cmd, "mv ");
             strcat(cmd, MR_trace_count_summary_file);
             strcat(cmd, TEMP_SUFFIX);
             strcat(cmd, " ");
             strcat(cmd, MR_trace_count_summary_file);
-            status = system(cmd);
+            mv_status = system(cmd);
 
-#if 1
-            fp = fopen("/tmp/zs_summaries", "a");
-            if (fp != NULL) {
-                fprintf(fp, "alloc=%d\n", cmd_len);
-                fflush(fp);
-                fprintf(fp, "len=%d\n", strlen(cmd));
-                fflush(fp);
-                fprintf(fp, "%s\n", cmd);
-                fflush(fp);
-                fclose(fp);
+            if (mv_status == 0) {
+                /* delete all files whose data is now in the summary file */
+                for (i = 1; i <= MR_trace_count_summary_max; i++) {
+                    snprintf(name, name_len, "%s.%d",
+                        MR_trace_count_summary_file, i);
+                    unlink_status = unlink(name);
+                    if (unlink_status != 0) {
+                        MR_fatal_error(
+                            "couldn't create summary of trace data");
             }
-#endif
         }
-
-        if (status == 0) {
-            /* delete all the files whose data is now in the summary file */
-            for (i = 1; i <= MR_trace_count_summary_max; i++) {
-                snprintf(name, len, "%s.%d", MR_trace_count_summary_file, i);
-                unlink(name);
+            } else {
+                MR_fatal_error("couldn't create summary of trace data");
             }
         } else {
             MR_fatal_error("couldn't create summary of trace data");
@@ -435,8 +442,9 @@
     }
 }
 
-void
-MR_trace_write_label_exec_counts(FILE *fp, MR_bool coverage_test)
+unsigned
+MR_trace_write_label_exec_counts(FILE *fp, const char *progname,
+    MR_bool coverage_test)
 {
     const MR_Module_Layout      *module;
     const MR_Module_File_Layout *file;
@@ -444,17 +452,23 @@
     int                         num_files;
     int                         module_num;
     int                         file_num;
+    unsigned                    num_written;
+    char                        *s;
 
     MR_trace_name_count_port_ensure_init();
 
     fprintf(fp, "%s", MR_TRACE_COUNT_FILE_ID);
     if (coverage_test) {
-        fprintf(fp, "single all\n");
+        fputs("single_file(base_count_file_type(user_all, ", fp);
     } else {
-        fprintf(fp, "single nonzero\n");
+        fputs("single_file(base_count_file_type(user_nonzero, ", fp);
     }
 
+    MR_trace_write_string(fp, progname);
+    fputs(")).\n", fp);
+
     num_modules = MR_module_info_next;
+    num_written = 0;
     for (module_num = 0; module_num < num_modules; module_num++) {
         module = MR_module_infos[module_num];
         num_files = module->MR_ml_filename_count;
@@ -465,13 +479,15 @@
 
         for (file_num = 0; file_num < num_files; file_num++) {
             file = module->MR_ml_module_file_layout[file_num];
-            MR_trace_write_label_exec_counts_for_file(fp, module, file,
-                module->MR_ml_name, coverage_test);
+            num_written += MR_trace_write_label_exec_counts_for_file(fp,
+                module, file, module->MR_ml_name, coverage_test);
         }
     }
+
+    return num_written;
 }
 
-static void
+static unsigned
 MR_trace_write_label_exec_counts_for_file(FILE *fp,
     const MR_Module_Layout *module, const MR_Module_File_Layout *file,
     const char *module_name, MR_bool coverage_test)
@@ -484,6 +500,7 @@
     int                         num_labels;
     int                         label_num;
     int                         label_index;
+    unsigned                    num_written;
     MR_Unsigned                 exec_count;
     MR_PathPort                 path_port;
 
@@ -493,6 +510,7 @@
 
     prev_proc = NULL;
     num_labels = file->MR_mfl_label_count;
+    num_written = 0;
     for (label_num = 0; label_num < num_labels; label_num++) {
         label = file->MR_mfl_label_layout[label_num];
         proc = label->MR_sll_entry;
@@ -501,6 +519,8 @@
         if (! MR_PROC_LAYOUT_IS_UCI(proc) && label_index > 0 &&
             (exec_count > 0 || coverage_test))
         {
+            num_written++;
+
             id = &proc->MR_sle_user;
             if (proc != prev_proc) {
                 if (MR_strdiff(module_name, id->MR_user_def_module)) {
@@ -569,6 +589,8 @@
             prev_proc = proc;
         }
     }
+
+    return num_written;
 }
 
 void
@@ -649,6 +671,42 @@
     fputc('\'', fp);
 }
 
+/*
+** The output of this is supposed to be equivalent to writing out a string.
+*/
+
+static void
+MR_trace_write_string(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 '\n':
+                fputs("\\n", fp);
+                break;
+            case '\t':
+                fputs("\\t", fp);
+                break;
+            case '\b':
+                fputs("\\b", fp);
+                break;
+            default:
+                fputc(*c, fp);
+                break;
+        }
+    }
+
+    fputc('\"', fp);
+}
+
 /**************************************************************************/
 /*
 ** This section of this file deals with the actions executed at the start
--- /home/zs/mer/ws5/runtime/mercury_trace_base.h	2006-09-19 09:53:29.000000000 +1000
+++ mercury_trace_base.h	2006-09-19 14:52:08.000000000 +1000
@@ -109,8 +109,8 @@
 */
 
 extern	const MR_Module_Layout	**MR_module_infos;
-extern	int			MR_module_info_next;
-extern	int			MR_module_info_max;
+extern	unsigned		MR_module_info_next;
+extern	unsigned		MR_module_info_max;
 
 extern	void	MR_insert_module_info_into_module_table(
 			const MR_Module_Layout *module_layout);
@@ -119,17 +119,21 @@
 ** For every label reachable from the module table, write the id of the label
 ** and the number of times it has been executed to the specified file. For 
 ** labels that haven't been executed, write them out only if the coverage_test
-** argument is true.
+** argument is true. The return value is the number of labels whose trace count
+** information was actually written out.
 **
 ** The file can be recognized as a Mercury trace counts file as its first
 ** line matches MR_TRACE_COUNT_FILE_ID. The value of that macro should be
 ** kept in sync with trace_count_file_id in mdbcomp/trace_counts.m.
+** One of the later lines gives the name of the program that the trace counts
+** were derived from; this should be supplied by the caller as the progname
+** argument.
 */
 
 #define	MR_TRACE_COUNT_FILE_ID	    "Mercury trace counts file\n"
 
-extern	void		MR_trace_write_label_exec_counts(FILE *fp,
-				MR_bool coverage_test);
+extern	unsigned int	MR_trace_write_label_exec_counts(FILE *fp,
+				const char *progname, MR_bool coverage_test);
 
 /*
 ** Figure out where (to which file) to write out the label execution counts,
--- /home/zs/mer/ws5/runtime/mercury_wrapper.c	2006-09-14 14:05:56.000000000 +1000
+++ mercury_wrapper.c	2006-09-19 14:48:03.000000000 +1000
@@ -1118,12 +1118,16 @@
     { "tabling-statistics",             0, 0, MR_TABLING_STATISTICS_OPT },
     { "trace-count",                    0, 0, MR_TRACE_COUNT_OPT },
     { "trace-count-if-exec",            1, 0, MR_TRACE_COUNT_IF_EXEC_OPT },
-    { "trace-count-summary-file",       1, 0, MR_TRACE_COUNT_SUMMARY_FILE_OPT },
-    { "trace-count-summary-cmd",        1, 0, MR_TRACE_COUNT_SUMMARY_CMD_OPT },
-    { "trace-count-summary-max",        1, 0, MR_TRACE_COUNT_SUMMARY_MAX_OPT },
     { "coverage-test",                  0, 0, MR_COVERAGE_TEST_OPT },
     { "coverage-test-if-exec",          1, 0, MR_COVERAGE_TEST_IF_EXEC_OPT },
     { "tc-output-file",                 1, 0, MR_TRACE_COUNT_FILE },
+    { "trace-count-output-file",        1, 0, MR_TRACE_COUNT_FILE },
+    { "tc-summary-file",                1, 0, MR_TRACE_COUNT_SUMMARY_FILE_OPT },
+    { "trace-count-summary-file",       1, 0, MR_TRACE_COUNT_SUMMARY_FILE_OPT },
+    { "tc-summary-cmd",                 1, 0, MR_TRACE_COUNT_SUMMARY_CMD_OPT },
+    { "trace-count-summary-cmd",        1, 0, MR_TRACE_COUNT_SUMMARY_CMD_OPT },
+    { "tc-summary-max",                 1, 0, MR_TRACE_COUNT_SUMMARY_MAX_OPT },
+    { "trace-count-summary-max",        1, 0, MR_TRACE_COUNT_SUMMARY_MAX_OPT },
     { "mem-usage-report",               0, 0, MR_MEM_USAGE_REPORT },
 
     /* This needs to be kept at the end. */
@@ -1515,6 +1519,28 @@
                 }
                 break;
 
+            case MR_COVERAGE_TEST_OPT:
+                MR_coverage_test_enabled = MR_TRUE;
+                MR_trace_count_enabled = MR_TRUE;
+                break;
+
+            case MR_COVERAGE_TEST_IF_EXEC_OPT:
+                if (MR_matches_exec_name(MR_optarg)) {
+                    MR_coverage_test_enabled = MR_TRUE;
+                    MR_trace_count_enabled = MR_TRUE;
+                }
+                break;
+
+            case MR_TRACE_COUNT_FILE:
+                if (MR_trace_count_summary_file != NULL) {
+                    MR_fatal_error(
+                        "--trace-count-file and --trace-count-summary-file"
+                        " are mutually exclusive\n");
+                }
+
+                MR_trace_counts_file = MR_copy_string(MR_optarg);
+                break;
+
             case MR_TRACE_COUNT_SUMMARY_FILE_OPT:
                 if (MR_trace_counts_file != NULL) {
                     MR_fatal_error(
@@ -1523,7 +1549,6 @@
                 }
 
                 MR_trace_count_summary_file = MR_copy_string(MR_optarg);
-                MR_trace_count_enabled = MR_TRUE;
                 break;
 
             case MR_TRACE_COUNT_SUMMARY_CMD_OPT:
@@ -1542,28 +1567,6 @@
                 MR_trace_count_summary_max = size;
                 break;
 
-            case MR_COVERAGE_TEST_OPT:
-                MR_coverage_test_enabled = MR_TRUE;
-                MR_trace_count_enabled = MR_TRUE;
-                break;
-
-            case MR_COVERAGE_TEST_IF_EXEC_OPT:
-                if (MR_matches_exec_name(MR_optarg)) {
-                    MR_coverage_test_enabled = MR_TRUE;
-                    MR_trace_count_enabled = MR_TRUE;
-                }
-                break;
-
-            case MR_TRACE_COUNT_FILE:
-                if (MR_trace_count_summary_file != NULL) {
-                    MR_fatal_error(
-                        "--trace-count-file and --trace-count-summary-file"
-                        " are mutually exclusive\n");
-                }
-
-                MR_trace_counts_file = MR_copy_string(MR_optarg);
-                break;
-
             case MR_MEM_USAGE_REPORT:
                 mem_usage_report = MR_TRUE;
                 break;
Diffing runtime/GETOPT
Diffing runtime/machdeps
Diffing samples
Diffing samples/c_interface
Diffing samples/c_interface/c_calls_mercury
Diffing samples/c_interface/cplusplus_calls_mercury
Diffing samples/c_interface/mercury_calls_c
Diffing samples/c_interface/mercury_calls_cplusplus
Diffing samples/c_interface/mercury_calls_fortran
Diffing samples/c_interface/simpler_c_calls_mercury
Diffing samples/c_interface/simpler_cplusplus_calls_mercury
Diffing samples/diff
Diffing samples/muz
Diffing samples/rot13
Diffing samples/solutions
Diffing samples/tests
Diffing samples/tests/c_interface
Diffing samples/tests/c_interface/c_calls_mercury
Diffing samples/tests/c_interface/cplusplus_calls_mercury
Diffing samples/tests/c_interface/mercury_calls_c
Diffing samples/tests/c_interface/mercury_calls_cplusplus
Diffing samples/tests/c_interface/mercury_calls_fortran
Diffing samples/tests/c_interface/simpler_c_calls_mercury
Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
Diffing samples/tests/diff
Diffing samples/tests/muz
Diffing samples/tests/rot13
Diffing samples/tests/solutions
Diffing samples/tests/toplevel
Diffing scripts
--- /home/zs/mer/ws5/scripts/mtc	2006-09-18 13:37:56.000000000 +1000
+++ mtc	2006-09-19 13:46:58.000000000 +1000
@@ -172,8 +172,7 @@
 if test "$output_file" != ""
 then
 	MERCURY_OPTIONS="$MERCURY_OPTIONS --tc-output-file $output_file"
-    	;;
-esac
+fi
 
 export MERCURY_OPTIONS
 exec "$@"
Diffing slice
--- /home/zs/mer/ws5/slice/Mmakefile	2006-03-25 01:18:29.000000000 +1100
+++ Mmakefile	2006-09-20 13:13:59.000000000 +1000
@@ -22,8 +22,8 @@
 MAIN_TARGET		= all
 
 # If you add more modules, you'll also have to modify ../Mmakefile.
-MERCURY_MAIN_MODULES	= mct mslice mdice mtc_union mtc_diff
-MERCURY_MAIN_MODULES_MS	= $(mct.ms) $(mslice.ms) $(mdice.ms) $(mtc_union.ms) \
+MERCURY_MAIN_MODULES	= mcov mslice mdice mtc_union mtc_diff
+MERCURY_MAIN_MODULES_MS	= $(mcov.ms) $(mslice.ms) $(mdice.ms) $(mtc_union.ms) \
 				$(mtc_diff.ms)
 
 DEPENDS	= $(patsubst %,%.depend,$(MERCURY_MAIN_MODULES))
@@ -91,26 +91,26 @@
 
 .PHONY: dates
 dates:
-	touch $(mct.dates) $(mslice.dates) $(mdice.dates) \
+	touch $(mcov.dates) $(mslice.dates) $(mdice.dates) \
 		$(mtc_union.dates) $(mtc_diff.dates)
 
 #-----------------------------------------------------------------------------#
 
 .PHONY: os cs ss ils
-os:	$(mct.os) $(mslice.os) $(mdice.os) $(mtc_union.os) $(mtc_diff.os) \
-	$(os_subdir)mct_init.o \
+os:	$(mcov.os) $(mslice.os) $(mdice.os) $(mtc_union.os) $(mtc_diff.os) \
+	$(os_subdir)mcov_init.o \
 	$(os_subdir)mslice_init.o \
 	$(os_subdir)mdice_init.o \
 	$(os_subdir)mtc_union_init.o \
 	$(os_subdir)mtc_diff_init.o
-cs:	$(mct.cs) $(mslice.cs) $(mdice.cs) $(mtc_union.cs) $(mtc_diff.cs) \
-	$(cs_subdir)mct_init.c \
+cs:	$(mcov.cs) $(mslice.cs) $(mdice.cs) $(mtc_union.cs) $(mtc_diff.cs) \
+	$(cs_subdir)mcov_init.c \
 	$(cs_subdir)mslice_init.c \
 	$(cs_subdir)mdice_init.c \
 	$(cs_subdir)mtc_union_init.c \
 	$(cs_subdir)mtc_diff_init.c
-ss:	$(mct.ss) $(mslice.ss) $(mdice.ss) $(mtc_union.ss) $(mtc_diff.ss)
-ils:	$(mct.ils) $(mslice.ils) $(mdice.ils) $(mtc_union.ils) $(mtc_diff.ils)
+ss:	$(mcov.ss) $(mslice.ss) $(mdice.ss) $(mtc_union.ss) $(mtc_diff.ss)
+ils:	$(mcov.ils) $(mslice.ils) $(mdice.ils) $(mtc_union.ils) $(mtc_diff.ils)
 
 #-----------------------------------------------------------------------------#
 
--- /dev/null	2006-05-23 00:25:23.000000000 +1000
+++ mcov.m	2006-09-20 13:49:32.000000000 +1000
@@ -0,0 +1,363 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 expandtab
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2006 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.
+%-----------------------------------------------------------------------------%
+%
+% Mercury coverage test tool.
+%
+% Author: Zoltan Somogyi.
+%
+%-----------------------------------------------------------------------------%
+
+:- module mcov.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module mdbcomp.
+:- import_module mdbcomp.prim_data.
+:- import_module mdbcomp.program_representation.
+:- import_module mdbcomp.trace_counts.
+
+:- import_module assoc_list.
+:- import_module bool.
+:- import_module getopt.
+:- import_module int.
+:- import_module list.
+:- import_module map.
+:- import_module maybe.
+:- import_module pair.
+:- import_module require.
+:- import_module set.
+:- import_module string.
+:- import_module svmap.
+:- import_module term_io.
+
+main(!IO) :-
+    io.command_line_arguments(Args0, !IO),
+    OptionOps = option_ops_multi(short_option, long_option, option_default),
+    getopt.process_options(OptionOps, Args0, Args, GetoptResult),
+    (
+        GetoptResult = ok(OptionTable),
+        (
+            Args = [_ | _],
+            lookup_bool_option(OptionTable, verbose, Verbose),
+            read_and_union_trace_counts(Verbose, try_single_first, Args,
+                _NumTests, FileTypes, TraceCounts, MaybeReadError, !IO),
+            stderr_stream(StdErr, !IO),
+            (
+                MaybeReadError = yes(ReadErrorMsg),
+                io.write_string(StdErr, ReadErrorMsg, !IO),
+                io.nl(StdErr, !IO)
+            ;
+                MaybeReadError = no,
+                set.to_sorted_list(FileTypes, FileTypeList),
+                ( FileTypeList = [single_file(BaseType)] ->
+                    BaseType = base_count_file_type(Kind, _Program),
+                    (
+                        Kind = user_nonzero,
+                        io.write_string(StdErr, kind_warning, !IO)
+                    ;
+                        Kind = user_all
+                    )
+                ;
+                    io.write_string(StdErr, consistency_warning, !IO)
+                ),
+                lookup_bool_option(OptionTable, detailed, Detailed),
+                lookup_string_option(OptionTable, output_filename, OutputFile),
+                ( OutputFile = "" ->
+                    write_coverage_test(Detailed, TraceCounts, !IO)
+                ;
+                    io.tell(OutputFile, OpenRes, !IO),
+                    (
+                        OpenRes = ok,
+                        write_coverage_test(Detailed, TraceCounts, !IO)
+                    ;
+                        OpenRes = error(OpenErrorMsg),
+                        io.write_string(StdErr, "Error opening " ++
+                            "file `" ++ OutputFile ++ "'" ++ ": " ++
+                            string(OpenErrorMsg), !IO),
+                        io.nl(StdErr, !IO)
+                    )
+                )
+            )
+        ;
+            Args = [],
+            usage(!IO)
+        )
+    ;
+        GetoptResult = error(GetoptErrorMsg),
+        io.write_string(GetoptErrorMsg, !IO),
+        io.nl(!IO)
+    ).
+
+:- func kind_warning = string.
+
+kind_warning =
+    "Warning: the original trace count files did not include all labels.\n".
+
+:- func consistency_warning = string.
+
+consistency_warning =
+    "Warning: reporting on a mixture of trace file types and/or programs.\n".
+
+%-----------------------------------------------------------------------------%
+
+:- type proc_info
+    --->    proc_info(
+                proc_source_file    :: string,
+                proc_line_number    :: int,
+                proc_proc           :: proc_label
+            ).
+
+:- type label_info
+    --->    label_info(
+                label_source_file   :: string,
+                label_line_number   :: int,
+                label_proc          :: proc_label,
+                label_path_port     :: path_port
+            ).
+
+:- pred write_coverage_test(bool::in, trace_counts::in, io::di, io::uo) is det.
+
+write_coverage_test(Detailed, TraceCountMap, !IO) :-
+    map.to_assoc_list(TraceCountMap, TraceCounts),
+    (
+        Detailed = no,
+        collect_zero_count_local_procs(TraceCounts, ZeroCountProcs),
+        sort(ZeroCountProcs, SortedZeroCountProcs),
+        io.write_string("Unexecuted procedures:\n\n", !IO),
+        list.foldl(write_proc_info, SortedZeroCountProcs, !IO)
+    ;
+        Detailed = yes,
+        collect_zero_count_local_labels(TraceCounts, [], ZeroCountLabels),
+        sort(ZeroCountLabels, SortedZeroCountLabels),
+        io.write_string("Unexecuted labels:\n\n", !IO),
+        list.foldl(write_label_info, SortedZeroCountLabels, !IO)
+    ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred collect_zero_count_local_procs(
+    assoc_list(proc_label_in_context, proc_trace_counts)::in,
+    list(proc_info)::out) is det.
+
+collect_zero_count_local_procs(TraceCounts, ZeroCountProcInfos) :-
+    collect_proc_infos_counts(TraceCounts, map.init, ProcInfoMap,
+        map.init, CountMap),
+    map.to_assoc_list(CountMap, CountList),
+    list.filter_map(is_zero_count_local_proc(ProcInfoMap), CountList,
+        ZeroCountProcInfos).
+
+:- pred collect_proc_infos_counts(
+    assoc_list(proc_label_in_context, proc_trace_counts)::in,
+    map(proc_label, proc_info)::in, map(proc_label, proc_info)::out,
+    map(proc_label, int)::in, map(proc_label, int)::out) is det.
+
+collect_proc_infos_counts([], !ProcInfoMap, !CountMap).
+collect_proc_infos_counts([Assoc | Assocs], !ProcInfoMap, !CountMap) :-
+    Assoc = LabelFilename - PathPortCountMap,
+    LabelFilename = proc_label_in_context(_ModuleNameSym, FileName, ProcLabel),
+    map.foldl2(proc_process_path_port_count, PathPortCountMap,
+        no, MaybeCallInfo, 0, CurCount),
+    ( map.search(!.CountMap, ProcLabel, OldCount) ->
+        svmap.det_update(ProcLabel, OldCount + CurCount, !CountMap)
+    ;
+        svmap.det_insert(ProcLabel, CurCount, !CountMap)
+    ),
+    (
+        MaybeCallInfo = no
+    ;
+        MaybeCallInfo = yes(LineNumber),
+        ProcInfo = proc_info(FileName, LineNumber, ProcLabel),
+        svmap.det_insert(ProcLabel, ProcInfo, !ProcInfoMap)
+    ),
+    collect_proc_infos_counts(Assocs, !ProcInfoMap, !CountMap).
+
+:- pred proc_process_path_port_count(path_port::in, line_no_and_count::in,
+    maybe(int)::in, maybe(int)::out, int::in, int::out) is det.
+
+proc_process_path_port_count(PathPort, LineNumberAndCount, !MaybeCallInfo,
+        !Count) :-
+    LineNumberAndCount = line_no_and_count(LineNumber, CurCount, _NumTests),
+    !:Count = !.Count + CurCount,
+    ( PathPort = port_only(call) ->
+        require(unify(!.MaybeCallInfo, no),
+            "proc_process_path_port_count: duplicate call port:"),
+        !:MaybeCallInfo = yes(LineNumber)
+    ;
+        true
+    ).
+
+:- pred is_zero_count_local_proc(map(proc_label, proc_info)::in,
+    pair(proc_label, int)::in, proc_info::out) is semidet.
+
+is_zero_count_local_proc(ProcInfoMap, ProcLabel - Count, ProcInfo) :-
+    Count = 0,
+    is_local_proc(ProcLabel),
+    map.lookup(ProcInfoMap, ProcLabel, ProcInfo).
+
+%-----------------------------------------------------------------------------%
+
+:- pred collect_zero_count_local_labels(
+    assoc_list(proc_label_in_context, proc_trace_counts)::in,
+    list(label_info)::in, list(label_info)::out) is det.
+
+collect_zero_count_local_labels([], !ZeroLabelInfos).
+collect_zero_count_local_labels([Assoc | Assocs], !ZeroLabelInfos) :-
+    Assoc = LabelFilename - PathPortCountMap,
+    LabelFilename = proc_label_in_context(_ModuleNameSym, FileName, ProcLabel),
+    map.foldl(label_process_path_port_count(ProcLabel, FileName),
+        PathPortCountMap, !ZeroLabelInfos),
+    collect_zero_count_local_labels(Assocs, !ZeroLabelInfos).
+
+:- pred label_process_path_port_count(proc_label::in, string::in,
+    path_port::in, line_no_and_count::in,
+    list(label_info)::in, list(label_info)::out) is det.
+
+label_process_path_port_count(ProcLabel, FileName,
+        PathPort, LineNumberAndCount, !ZeroLabelInfos) :-
+    LineNumberAndCount = line_no_and_count(LineNumber, Count, _NumTests),
+    (
+        Count = 0,
+        is_local_proc(ProcLabel)
+    ->
+        LabelInfo = label_info(FileName, LineNumber, ProcLabel, PathPort),
+        !:ZeroLabelInfos = [LabelInfo | !.ZeroLabelInfos]
+    ;
+        true
+    ).
+
+%-----------------------------------------------------------------------------%
+
+    % We don't want to warn about zero executions of a copy of a procedure
+    % inlined in a module other than the module that defines the procedure.
+    %
+:- pred is_local_proc(proc_label::in) is semidet.
+
+is_local_proc(ProcLabel) :-
+    (
+        ProcLabel = ordinary_proc_label(DefModuleSym, _, DeclModuleSym,
+            _, _, _),
+        DefModuleSym = DeclModuleSym
+    ;
+        ProcLabel = special_proc_label(DefModuleSym, _, TypeModuleSym,
+            _, _, _),
+        DefModuleSym = TypeModuleSym
+    ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred write_proc_info(proc_info::in, io::di, io::uo) is det.
+
+write_proc_info(ProcInfo, !IO) :-
+    ProcInfo = proc_info(FileName, LineNumber, ProcLabel),
+    io.write_string(FileName, !IO),
+    io.write_char(':', !IO),
+    io.write_int(LineNumber, !IO),
+    io.write_string(": ", !IO),
+    write_proc_label_for_user(ProcLabel, !IO),
+    io.nl(!IO).
+
+:- pred write_label_info(label_info::in, io::di, io::uo) is det.
+
+write_label_info(LabelInfo, !IO) :-
+    LabelInfo = label_info(FileName, LineNumber, ProcLabel, PathPort),
+    io.write_string(FileName, !IO),
+    io.write_char(':', !IO),
+    io.write_int(LineNumber, !IO),
+    io.write_string(": ", !IO),
+    write_proc_label_for_user(ProcLabel, !IO),
+    write_path_port_for_user(PathPort, !IO),
+    io.nl(!IO).
+
+:- pred write_proc_label_for_user(proc_label::in, io::di, io::uo) is det.
+
+write_proc_label_for_user(ProcLabel, !IO) :-
+    (
+        ProcLabel = ordinary_proc_label(_DefModuleSym, PredOrFunc,
+            _DeclModuleSym, Name, Arity, Mode),
+        (
+            PredOrFunc = predicate,
+            io.write_string("pred ", !IO)
+        ;
+            PredOrFunc = function,
+            io.write_string("func ", !IO)
+        ),
+        term_io.quote_atom(Name, !IO),
+        io.write_string("/", !IO),
+        io.write_int(Arity, !IO),
+        io.write_string("-", !IO),
+        io.write_int(Mode, !IO)
+    ;
+        % We don't record trace counts in special preds.
+        ProcLabel = special_proc_label(_, _, _, _, _, _),
+        error("write_proc_label_for_user: special_pred")
+    ).
+
+:- pred write_path_port_for_user(path_port::in, io::di, io::uo) is det.
+
+write_path_port_for_user(port_only(Port), !IO) :-
+    string_to_trace_port(PortStr, Port),
+    io.write_string(PortStr, !IO).
+write_path_port_for_user(path_only(Path), !IO) :-
+    string_from_path(Path, PathStr),
+    io.write_strings(["<", PathStr, ">"], !IO).
+write_path_port_for_user(port_and_path(Port, Path), !IO) :-
+    string_to_trace_port(PortStr, Port),
+    string_from_path(Path, PathStr),
+    io.write_strings([PortStr, " <", PathStr, ">"], !IO).
+
+%-----------------------------------------------------------------------------%
+
+:- pred usage(io::di, io::uo) is det.
+
+usage(!IO) :-
+    io.write_strings([
+        "Usage: mct [-d] [-v] [-o output_file] file1 file2 ...\n",
+        "The -d or --detailed option causes the printing of a report for\n",
+        "each label that has not been executed, even if some other code\n",
+        "has been executed in the same procedure.\n",
+        "The -v or --verbose option causes each trace count file name\n",
+        "to be printed as it is added to the union.\n",
+        "file1, file2, etc can be trace count files or they can be files\n",
+        "that contains lists of the names of other trace count files.\n"],
+        !IO).
+
+%-----------------------------------------------------------------------------%
+
+:- type option
+    --->    detailed
+    ;       output_filename
+    ;       verbose.
+
+:- type option_table == option_table(option).
+
+:- pred short_option(character::in, option::out) is semidet.
+:- pred long_option(string::in, option::out) is semidet.
+:- pred option_default(option::out, option_data::out) is multi.
+
+option_default(detailed,        bool(no)).
+option_default(output_filename, string("")).
+option_default(verbose,         bool(no)).
+
+short_option('d',               detailed).
+short_option('o',               output_filename).
+short_option('v',               verbose).
+
+long_option("detailed",         detailed).
+long_option("out",              output_filename).
+long_option("verbose",          verbose).
+
+%-----------------------------------------------------------------------------%
--- mct.m	2006-09-19 09:52:49.000000000 +1000
+++ /dev/null	2006-05-23 00:25:23.000000000 +1000
@@ -1,287 +0,0 @@
-%-----------------------------------------------------------------------------%
-% vim: ft=mercury ts=4 sw=4 expandtab
-%-----------------------------------------------------------------------------%
-% Copyright (C) 2006 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.
-%-----------------------------------------------------------------------------%
-%
-% Mercury coverage test tool.
-%
-% Author: Zoltan Somogyi.
-%
-%-----------------------------------------------------------------------------%
-
-:- module mct.
-
-:- interface.
-
-:- import_module io.
-
-:- pred main(io::di, io::uo) is det.
-
-%-----------------------------------------------------------------------------%
-%-----------------------------------------------------------------------------%
-
-:- implementation.
-
-:- import_module mdbcomp.
-:- import_module mdbcomp.prim_data.
-:- import_module mdbcomp.trace_counts.
-
-:- import_module assoc_list.
-:- import_module bool.
-:- import_module getopt.
-:- import_module int.
-:- import_module list.
-:- import_module map.
-:- import_module maybe.
-:- import_module pair.
-:- import_module require.
-:- import_module set.
-:- import_module string.
-:- import_module svmap.
-
-main(!IO) :-
-    io.command_line_arguments(Args0, !IO),
-    OptionOps = option_ops_multi(short_option, long_option, option_default),
-    getopt.process_options(OptionOps, Args0, Args, GetoptResult),
-    (
-        GetoptResult = ok(OptionTable),
-        (
-            Args = [_ | _],
-            lookup_bool_option(OptionTable, verbose, Verbose),
-            read_and_union_trace_counts(Verbose, try_single_first, Args,
-                _NumTests, Kinds, TraceCounts, MaybeReadError, !IO),
-            stderr_stream(StdErr, !IO),
-            (
-                MaybeReadError = yes(ReadErrorMsg),
-                io.write_string(StdErr, ReadErrorMsg, !IO),
-                io.nl(StdErr, !IO)
-            ;
-                MaybeReadError = no,
-                set.to_sorted_list(Kinds, KindList),
-                ( KindList = [user_all] ->
-                    true
-                ;
-                    io.write_string(StdErr,
-                        "warning: some of the original trace count files\n",
-                        !IO),
-                    io.write_string(StdErr, "did not include all counts.\n",
-                        !IO)
-                ),
-                lookup_bool_option(OptionTable, detailed, Detailed),
-                lookup_string_option(OptionTable, output_filename, OutputFile),
-                ( OutputFile = "" ->
-                    write_coverage_test(Detailed, TraceCounts, !IO)
-                ;
-                    io.tell(OutputFile, OpenRes, !IO),
-                    (
-                        OpenRes = ok,
-                        write_coverage_test(Detailed, TraceCounts, !IO)
-                    ;
-                        OpenRes = error(OpenErrorMsg),
-                        io.write_string(StdErr, "Error opening " ++
-                            "file `" ++ OutputFile ++ "'" ++ ": " ++
-                            string(OpenErrorMsg), !IO),
-                        io.nl(StdErr, !IO)
-                    )
-                )
-            )
-        ;
-            Args = [],
-            usage(!IO)
-        )
-    ;
-        GetoptResult = error(GetoptErrorMsg),
-        io.write_string(GetoptErrorMsg, !IO),
-        io.nl(!IO)
-    ).
-
-%-----------------------------------------------------------------------------%
-
-:- type proc_info
-    --->    proc_info(
-                proc_source_file    :: string,
-                proc_line_number    :: int,
-                proc_proc           :: proc_label
-            ).
-
-:- type label_info
-    --->    label_info(
-                label_source_file   :: string,
-                label_line_number   :: int,
-                label_proc          :: proc_label,
-                label_path_port     :: path_port
-            ).
-
-:- pred write_coverage_test(bool::in, trace_counts::in, io::di, io::uo) is det.
-
-write_coverage_test(Detailed, TraceCountMap, !IO) :-
-    map.to_assoc_list(TraceCountMap, TraceCounts),
-    (
-        Detailed = no,
-        collect_zero_count_procs(TraceCounts, ZeroCountProcs),
-        sort(ZeroCountProcs, SortedZeroCountProcs),
-        io.write_string("Unexecuted procedures:\n\n", !IO),
-        list.foldl(write_proc_info, SortedZeroCountProcs, !IO)
-    ;
-        Detailed = yes,
-        collect_zero_count_labels(TraceCounts, [], ZeroCountLabels),
-        sort(ZeroCountLabels, SortedZeroCountLabels),
-        io.write_string("Unexecuted labels:\n\n", !IO),
-        list.foldl(write_label_info, SortedZeroCountLabels, !IO)
-    ).
-
-%-----------------------------------------------------------------------------%
-
-:- pred collect_zero_count_procs(
-    assoc_list(proc_label_in_context, proc_trace_counts)::in,
-    list(proc_info)::out) is det.
-
-collect_zero_count_procs(TraceCounts, ZeroCountProcInfos) :-
-    collect_proc_infos_counts(TraceCounts, map.init, ProcInfoMap,
-        map.init, CountMap),
-    map.to_assoc_list(CountMap, CountList),
-    list.filter_map(is_zero_count_proc(ProcInfoMap), CountList,
-        ZeroCountProcInfos).
-
-:- pred collect_proc_infos_counts(
-    assoc_list(proc_label_in_context, proc_trace_counts)::in,
-    map(proc_label, proc_info)::in, map(proc_label, proc_info)::out,
-    map(proc_label, int)::in, map(proc_label, int)::out) is det.
-
-collect_proc_infos_counts([], !ProcInfoMap, !CountMap).
-collect_proc_infos_counts([Assoc | Assocs], !ProcInfoMap, !CountMap) :-
-    Assoc = LabelFilename - PathPortCountMap,
-    LabelFilename = proc_label_in_context(_ModuleNameSym, FileName, ProcLabel),
-    map.foldl2(proc_process_path_port_count, PathPortCountMap,
-        no, MaybeCallInfo, 0, CurCount),
-    ( map.search(!.CountMap, ProcLabel, OldCount) ->
-        svmap.det_update(ProcLabel, OldCount + CurCount, !CountMap)
-    ;
-        svmap.det_insert(ProcLabel, CurCount, !CountMap)
-    ),
-    (
-        MaybeCallInfo = no
-    ;
-        MaybeCallInfo = yes(LineNumber),
-        ProcInfo = proc_info(FileName, LineNumber, ProcLabel),
-        svmap.det_insert(ProcLabel, ProcInfo, !ProcInfoMap)
-    ),
-    collect_proc_infos_counts(Assocs, !ProcInfoMap, !CountMap).
-
-:- pred proc_process_path_port_count(path_port::in, line_no_and_count::in,
-    maybe(int)::in, maybe(int)::out, int::in, int::out) is det.
-
-proc_process_path_port_count(PathPort, LineNumberAndCount, !MaybeCallInfo,
-        !Count) :-
-    LineNumberAndCount = line_no_and_count(LineNumber, CurCount, _NumTests),
-    !:Count = !.Count + CurCount,
-    ( PathPort = port_only(call) ->
-        require(unify(!.MaybeCallInfo, no),
-            "proc_process_path_port_count: duplicate call port:"),
-        !:MaybeCallInfo = yes(LineNumber)
-    ;
-        true
-    ).
-
-:- pred is_zero_count_proc(map(proc_label, proc_info)::in,
-    pair(proc_label, int)::in, proc_info::out) is semidet.
-
-is_zero_count_proc(ProcInfoMap, ProcLabel - Count, ProcInfo) :-
-    Count = 0,
-    map.lookup(ProcInfoMap, ProcLabel, ProcInfo).
-
-%-----------------------------------------------------------------------------%
-
-:- pred collect_zero_count_labels(
-    assoc_list(proc_label_in_context, proc_trace_counts)::in,
-    list(label_info)::in, list(label_info)::out) is det.
-
-collect_zero_count_labels([], !ZeroLabelInfos).
-collect_zero_count_labels([Assoc | Assocs], !ZeroLabelInfos) :-
-    Assoc = LabelFilename - PathPortCountMap,
-    LabelFilename = proc_label_in_context(_ModuleNameSym, FileName, ProcLabel),
-    map.foldl(label_process_path_port_count(ProcLabel, FileName),
-        PathPortCountMap, !ZeroLabelInfos),
-    collect_zero_count_labels(Assocs, !ZeroLabelInfos).
-
-:- pred label_process_path_port_count(proc_label::in, string::in,
-    path_port::in, line_no_and_count::in,
-    list(label_info)::in, list(label_info)::out) is det.
-
-label_process_path_port_count(ProcLabel, FileName,
-        PathPort, LineNumberAndCount, !ZeroLabelInfos) :-
-    LineNumberAndCount = line_no_and_count(LineNumber, Count, _NumTests),
-    ( Count = 0 ->
-        LabelInfo = label_info(FileName, LineNumber, ProcLabel, PathPort),
-        !:ZeroLabelInfos = [LabelInfo | !.ZeroLabelInfos]
-    ;
-        true
-    ).
-
-%-----------------------------------------------------------------------------%
-
-:- pred write_proc_info(proc_info::in, io::di, io::uo) is det.
-
-write_proc_info(ProcInfo, !IO) :-
-    ProcInfo = proc_info(FileName, LineNumber, ProcLabel),
-    io.write(FileName, !IO),
-    io.write_char(':', !IO),
-    io.write_int(LineNumber, !IO),
-    io.write_string(": ", !IO),
-    write_proc_label(ProcLabel, !IO).
-
-:- pred write_label_info(label_info::in, io::di, io::uo) is det.
-
-write_label_info(LabelInfo, !IO) :-
-    LabelInfo = label_info(FileName, LineNumber, ProcLabel, _),
-    io.write(FileName, !IO),
-    io.write_char(':', !IO),
-    io.write_int(LineNumber, !IO),
-    io.write_string(": ", !IO),
-    write_proc_label(ProcLabel, !IO).
-
-%-----------------------------------------------------------------------------%
-
-:- pred usage(io::di, io::uo) is det.
-
-usage(!IO) :-
-    io.write_strings([
-        "Usage: mct [-d] [-v] [-o output_file] file1 file2 ...\n",
-        "The -d or --detailed option causes the printing of a report for\n",
-        "each label that has not been executed, even if some other code\n",
-        "has been executed in the same procedure.\n",
-        "The -v or --verbose option causes each trace count file name\n",
-        "to be printed as it is added to the union.\n",
-        "file1, file2, etc can be trace count files or they can be files\n",
-        "that contains lists of the names of other trace count files.\n"],
-        !IO).
-
-%-----------------------------------------------------------------------------%
-
-:- type option
-    --->    detailed
-    ;       output_filename
-    ;       verbose.
-
-:- type option_table == option_table(option).
-
-:- pred short_option(character::in, option::out) is semidet.
-:- pred long_option(string::in, option::out) is semidet.
-:- pred option_default(option::out, option_data::out) is multi.
-
-option_default(detailed,        bool(no)).
-option_default(output_filename, string("")).
-option_default(verbose,         bool(no)).
-
-short_option('d',               detailed).
-short_option('o',               output_filename).
-short_option('v',               verbose).
-
-long_option("detailed",         detailed).
-long_option("out",              output_filename).
-long_option("verbose",          verbose).
-
-%-----------------------------------------------------------------------------%
--- /home/zs/mer/ws5/slice/mtc_diff.m	2006-04-01 16:56:36.000000000 +1100
+++ mtc_diff.m	2006-09-19 17:08:12.000000000 +1000
@@ -69,12 +69,12 @@
                 io.nl(StdErr, !IO)
             ),
             (
-                MaybeTraceCounts1 = list_ok(_, TraceCounts1),
-                MaybeTraceCounts2 = list_ok(_, TraceCounts2)
+                MaybeTraceCounts1 = list_ok(Type1, TraceCounts1),
+                MaybeTraceCounts2 = list_ok(Type2, TraceCounts2)
             ->
                 diff_trace_counts(TraceCounts1, TraceCounts2, TraceCounts),
-                write_trace_counts_to_file(diff_file, TraceCounts, OutputFile,
-                    WriteResult, !IO),
+                write_trace_counts_to_file(diff_file(Type1, Type2),
+                    TraceCounts, OutputFile, WriteResult, !IO),
                 (
                     WriteResult = ok
                 ;
--- /home/zs/mer/ws5/slice/mtc_union.m	2006-09-14 14:16:37.000000000 +1000
+++ mtc_union.m	2006-09-19 17:09:42.000000000 +1000
@@ -36,6 +36,7 @@
 :- import_module map.
 :- import_module maybe.
 :- import_module require.
+:- import_module set.
 :- import_module string.
 
 main(!IO) :-
@@ -59,8 +60,9 @@
                 io.nl(StdErr, !IO)
             ;
                 MaybeReadError = no,
-                write_trace_counts_to_file(union_file(NumTests, Kinds),
-                    TraceCounts, OutputFile, WriteResult, !IO),
+                Type = union_file(NumTests, set.to_sorted_list(Kinds)),
+                write_trace_counts_to_file(Type, TraceCounts, OutputFile,
+                    WriteResult, !IO),
                 (
                     WriteResult = ok
                 ;
Diffing tests
Diffing tests/benchmarks
Diffing tests/debugger
Diffing tests/debugger/declarative
Diffing tests/dppd
Diffing tests/general
Diffing tests/general/accumulator
Diffing tests/general/string_format
Diffing tests/general/structure_reuse
Diffing tests/grade_subdirs
Diffing tests/hard_coded
Diffing tests/hard_coded/exceptions
Diffing tests/hard_coded/purity
Diffing tests/hard_coded/sub-modules
Diffing tests/hard_coded/typeclasses
Diffing tests/invalid
Diffing tests/invalid/purity
Diffing tests/misc_tests
Diffing tests/mmc_make
Diffing tests/mmc_make/lib
Diffing tests/par_conj
Diffing tests/recompilation
Diffing tests/tabling
Diffing tests/term
Diffing tests/trailing
Diffing tests/valid
Diffing tests/warnings
Diffing tools
Diffing trace
Diffing util
Diffing vim
Diffing vim/after
Diffing vim/ftplugin
Diffing vim/syntax
--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list