[m-rev.] for post-commit review: Coverage Informatin Propagation in the Deep Profiler Tools.

Paul Bone pbone at csse.unimelb.edu.au
Wed Sep 17 13:25:37 AEST 2008


For post-commit review by Zoltan.

Estimated hours taken: 35
Branches: main

Introduce a new report type in the deep profiler tools.  The procedure
representation coverage report displays a representation of the procedure,
annotated with determinism and coverage information.  This allows a programmer
to view the most frequently taken execution paths through a procedure, 

This report is available when the program has been compiled for coverage
profiling, and when a Deep.procrep file is available.

deep_profiler/report.m:
	The coverage profiling dump report is now a coverage_information annotated
	procedure representation structure.
    Add a goal_path field to the call_site_perf type.

deep_profiler/program_representation_utils.m:
    Create procrep_annotate_with_coverage/5 predicate to annotate a procedure
    representation structure with coverage information.
    Use type classes to convert goal annotations to strings used with the
    procedure representation structures.

deep_profiler/create_report.m:
    Call procrep_annotate_with_coverage to build the coverage-annotated
    procedure representation report.

deep_profiler/display_report.m:
    Conform to changes in deep_profiler/report.m
    Implement a goal_annotation typeclass for coverage_info for displaying the
    coverage information.
	Display a link to the procrep_coverage report from the Procedure report.

deep_profiler/mdprof_cgi.m:
	Add the ability to generate a procrep_coverage report to the command line
	interface for debugging.

deep_profiler/mdprof_test.m:
	Add the ability to generate all the procrep coverage reports possible from
	a Deep.data file.
	Make compressing the result (using a separate gzip process) optional,
	since it can slow down the test for a negligible gain.


Index: deep_profiler/create_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/create_report.m,v
retrieving revision 1.8
diff -u -p -b -r1.8 create_report.m
--- deep_profiler/create_report.m	28 Aug 2008 10:26:14 -0000	1.8
+++ deep_profiler/create_report.m	17 Sep 2008 02:03:39 -0000
@@ -49,6 +49,7 @@
 :- import_module pair.
 :- import_module require.
 :- import_module string.
+:- import_module svmap.
 :- import_module univ.
 
 %-----------------------------------------------------------------------------%
@@ -299,6 +300,13 @@ create_call_site_summary(Deep, CSSPtr) =
     deep_lookup_call_site_statics(Deep, CSSPtr, CSS),
     KindAndCallee = CSS ^ css_kind,
     CallerPSPtr = CSS ^ css_container,
+    GoalPathString = CSS ^ css_goal_path,
+    ( goal_path_from_string(GoalPathString, GoalPathPrime) ->
+        GoalPath = GoalPathPrime
+    ;
+        error("create_call_site_summary: " ++ 
+            "Couldn't convert string to goal path: " ++ GoalPathString)
+    ),
 
     deep_lookup_call_site_calls(Deep, CSSPtr, CallSiteCallMap),
     map.to_assoc_list(CallSiteCallMap, CallSiteCalls),
@@ -350,7 +358,8 @@ create_call_site_summary(Deep, CSSPtr) =
         own_and_inherit_to_perf_row_data(Deep, CallSiteDesc, SumOwn, SumDesc,
             SummaryRowData)
     ),
-    CallSitePerf = call_site_perf(KindAndInfo, SummaryRowData, SubRowDatas).
+    CallSitePerf = call_site_perf(KindAndInfo, SummaryRowData, SubRowDatas, 
+        GoalPath).
 
 :- type call_site_callee_perf
     --->    call_site_callee_perf(
@@ -540,8 +549,25 @@ generate_procrep_coverage_dump_report(De
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         deep_lookup_proc_statics(Deep, PSPtr, PS),
         ProcLabel = PS ^ ps_id,
-        ( progrep_search_proc(ProgRep, ProcLabel, ProcRep) ->
-            MaybeReport = ok(ProcRep)
+        ( progrep_search_proc(ProgRep, ProcLabel, ProcRep0) ->
+            % Information about the procedure.
+            deep_lookup_ps_own(Deep, PSPtr, Own),
+
+            % Gather call site information.
+            CallSitesArray = PS ^ ps_sites,
+            array.foldl(create_cs_summary_add_to_map(Deep), CallSitesArray, 
+                map.init) = CallSitesMap,
+
+            % Gather information about coverage points.
+            CoveragePointsArray = PS ^ ps_coverage_points,
+            array.foldl2(add_coverage_point_to_map, CoveragePointsArray, 
+                map.init, SolnsCoveragePointMap,
+                map.init, BranchCoveragePointMap),
+
+            procrep_annotate_with_coverage(Own, CallSitesMap,
+                SolnsCoveragePointMap, BranchCoveragePointMap, 
+                ProcRep0, ProcRep),
+            MaybeReport = ok(procrep_coverage_info(PSPtr, ProcRep))
         ;
             MaybeReport = 
                 error("Program Representation doesn't contain procedure")
@@ -550,6 +576,32 @@ generate_procrep_coverage_dump_report(De
         MaybeReport = error("Invalid proc_static index")
     ).
 
+:- func create_cs_summary_add_to_map(deep, call_site_static_ptr, 
+    map(goal_path, call_site_perf)) =  map(goal_path, call_site_perf).
+
+create_cs_summary_add_to_map(Deep, CSStatic, Map0) = Map :-
+    create_call_site_summary(Deep, CSStatic) = CSSummary,
+    GoalPath = CSSummary ^ csf_goal_path,
+    map.det_insert(Map0, GoalPath, CSSummary, Map).
+
+:- pred add_coverage_point_to_map(coverage_point::in, 
+    map(goal_path, coverage_point)::in, map(goal_path, coverage_point)::out, 
+    map(goal_path, coverage_point)::in, map(goal_path, coverage_point)::out)
+    is det.
+
+add_coverage_point_to_map(CoveragePoint, !SolnsMap, !BranchMap) :-
+    CoveragePoint = coverage_point(_, GoalPath, CPType),
+    (
+        ( CPType = cp_type_solns_may_fail
+        ; CPType = cp_type_solns_multi
+        ; CPType = cp_type_solns_any
+        ),
+        svmap.det_insert(GoalPath, CoveragePoint, !SolnsMap)
+    ;
+        CPType = cp_type_branch_arm,
+        svmap.det_insert(GoalPath, CoveragePoint, !BranchMap)
+    ).
+
 %-----------------------------------------------------------------------------%
 %
 % Code to build the other dump reports.
Index: deep_profiler/display_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/display_report.m,v
retrieving revision 1.11
diff -u -p -b -r1.11 display_report.m
--- deep_profiler/display_report.m	28 Aug 2008 10:26:14 -0000	1.11
+++ deep_profiler/display_report.m	17 Sep 2008 02:10:40 -0000
@@ -118,7 +118,7 @@ report_to_display(Deep, Prefs, Report) =
         Report = report_procrep_coverage_dump(MaybeProcrepCoverageInfo),
         (
             MaybeProcrepCoverageInfo = ok(ProcrepCoverageInfo),
-            display_report_procrep_coverage_info(ProcrepCoverageInfo,
+            display_report_procrep_coverage_info(Prefs, ProcrepCoverageInfo,
                 Display)
         ;
             MaybeProcrepCoverageInfo = error(Msg),
@@ -574,6 +574,7 @@ display_report_proc(Prefs, ProcReport, D
     SortControls = sort_controls(Prefs, Cmd),
     FieldControls = field_controls(Prefs, Cmd),
     FormatControls = format_controls(Prefs, Cmd),
+    ProcReportControls = proc_reports_controls(Prefs, PSPtr, Cmd),
     MenuRestartQuitControls = cmds_menu_restart_quit(yes(Prefs)),
 
     Display = display(yes(Title),
@@ -583,13 +584,14 @@ display_report_proc(Prefs, ProcReport, D
         display_paragraph_break, SortControls,
         display_paragraph_break, FieldControls,
         display_paragraph_break, FormatControls,
+        display_paragraph_break, ProcReportControls,
         display_paragraph_break, MenuRestartQuitControls]).
 
 :- func report_proc_call_site(preferences, call_site_perf) = list(table_row).
 
 report_proc_call_site(Prefs, CallSitePerf) = Rows :-
     CallSitePerf =
-        call_site_perf(KindAndCallee, SummaryPerfRowData, SubPerfs0),
+        call_site_perf(KindAndCallee, SummaryPerfRowData, SubPerfs0, _),
 
     CallSiteDesc = SummaryPerfRowData ^ perf_row_subject,
     FileName = CallSiteDesc ^ csdesc_file_name,
@@ -993,14 +995,50 @@ make_proc_callers_link(Prefs, Label, PSP
 % Code to display procrep_coverage dumps 
 %
 
-:- pred display_report_procrep_coverage_info(procrep_coverage_info::in,
-    display::out) is det.
+:- pred display_report_procrep_coverage_info(preferences::in,
+    procrep_coverage_info::in, display::out) is det.
 
-display_report_procrep_coverage_info(ProcrepCoverageInfo, Display) :-
-    Title = "Procrep coverage dump",
-    print_proc_to_strings(ProcrepCoverageInfo, ProcRepStrings),
+display_report_procrep_coverage_info(Prefs, ProcrepCoverageReport, Display) :-
+    ProcrepCoverageReport = procrep_coverage_info(PSPtr, ProcrepCoverage),
+    print_proc_to_strings(ProcrepCoverage, ProcRepStrings),
     string.append_list(list(ProcRepStrings), ProcRepString),
-    Display = display(yes(Title), [display_verbatim(ProcRepString)]).
+    CoverageInfoItem = display_verbatim(ProcRepString),
+
+    Cmd = deep_cmd_procrep_coverage(PSPtr),
+    ProcReportControls = proc_reports_controls(Prefs, PSPtr, Cmd),
+    MenuResetQuitControls = cmds_menu_restart_quit(yes(Prefs)),
+    Controls = [display_paragraph_break, ProcReportControls, 
+                display_paragraph_break, MenuResetQuitControls], 
+
+    Title = "Procrep coverage dump",
+    Display = display(yes(Title), [CoverageInfoItem] ++ Controls).
+
+:- instance goal_annotation(coverage_info) where [
+        pred(print_goal_annotation_to_strings/2) is coverage_to_cord_string
+    ].
+
+    % Print the coverage information for a goal, this is used by
+    % print_proc_to_strings.
+    %
+:- pred coverage_to_cord_string(coverage_info::in, cord(string)::out) is det.
+
+coverage_to_cord_string(Coverage, cord.singleton(String)) :-
+    (
+        Coverage = coverage_unknown,
+        String = " _ - _"
+    ;
+        Coverage = coverage_known(Before, After),
+        String = string.format(" %d - %d", [i(Before), i(After)])
+    ;
+        Coverage = coverage_known_det(Count),
+        String = string.format(" %d - %d", [i(Count), i(Count)])
+    ;
+        Coverage = coverage_known_before(Before),
+        String = string.format(" %d - _", [i(Before)])
+    ;
+        Coverage = coverage_known_after(After),
+        String = string.format(" _ - %d", [i(After)])
+    ).
     
 
 %-----------------------------------------------------------------------------%
@@ -2530,6 +2568,38 @@ set_colour_column_groups(Colour, !Prefs)
 set_box_tables(Box, !Prefs) :-
     !Prefs ^ pref_box := Box.
 
+%----------------------------------------------------------------------------%
+%
+% Controls for related procedure reports.
+%
+
+:- func proc_reports_controls(preferences, proc_static_ptr, cmd) = display_item.
+
+proc_reports_controls(Prefs, Proc, NotCmd) = ControlsItem :-
+    make_cmd_controls_item(Prefs, proc_reports(Proc, NotCmd),
+        ProcReportControls),
+    ControlsItem = display_list(list_class_vertical_no_bullets,
+        yes("Related procedure reports:"), [ProcReportControls]).
+
+:- func proc_reports(proc_static_ptr, cmd) = assoc_list(cmd, string).
+
+proc_reports(Proc, NotCmd) = Reports :-
+    Reports0 = [
+        deep_cmd_proc(Proc) - "Procedure",
+        deep_cmd_procrep_coverage(Proc) -
+            "Coverage annotated Procedure Representation"
+        ],
+    list.filter((pred((Cmd - _)::in) is semidet :-
+            Cmd \= NotCmd
+        ), Reports0, Reports).
+
+:- pred make_cmd_controls_item(preferences::in, assoc_list(cmd, string)::in, 
+    display_item::out) is det.
+
+make_cmd_controls_item(Prefs, LabeledCmds, Item) :-
+    list.map(make_control(yes(Prefs)), LabeledCmds, CmdItems),
+    Item = display_list(list_class_horizontal, no, CmdItems).
+
 %-----------------------------------------------------------------------------%
 %
 % Control whether we display inactive modules.
@@ -2796,13 +2866,22 @@ call_site_desc_to_cell(Prefs, CallSiteDe
 make_labelled_table_row(Label - Value) =
     table_row([table_cell(td_s(Label)), table_cell(Value)]).
 
-    % Make a link for use in the menu report.
+    % Make a link from a command and label.
     %
 :- pred make_link(pair(cmd, string)::in, display_item::out) is det.
 
 make_link(Cmd - Label, Item) :-
     Item = display_link(deep_link(Cmd, no, Label, link_class_link)).
 
+    % Make a control from a command and label and optional preferences
+    % structure.
+    %
+:- pred make_control(maybe(preferences)::in, pair(cmd, string)::in,
+    display_item::out) is det.
+
+make_control(MaybePrefs, Cmd - Label, Item) :-
+    Item = display_link(deep_link(Cmd, MaybePrefs, Label, link_class_control)).
+
 %-----------------------------------------------------------------------------%
 %
 % Sort call_site_perfs by the preferred criteria of performance.
Index: deep_profiler/mdprof_cgi.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/mdprof_cgi.m,v
retrieving revision 1.26
diff -u -p -b -r1.26 mdprof_cgi.m
--- deep_profiler/mdprof_cgi.m	28 Aug 2008 10:26:14 -0000	1.26
+++ deep_profiler/mdprof_cgi.m	10 Sep 2008 13:12:49 -0000
@@ -811,6 +811,7 @@ detach_process(Result, !IO) :-
     ;       localhost
     ;       modules
     ;       proc
+    ;       procrep_coverage
     ;       quit
     ;       root
     ;       record_startup
@@ -848,6 +849,7 @@ long("help",                help).
 long("localhost",           localhost).
 long("modules",             modules).
 long("proc",                proc).
+long("procrep-coverage",    procrep_coverage).
 long("quit",                quit).
 long("root",                root).
 long("record-startup",      record_startup).
@@ -870,6 +872,7 @@ defaults(help,                  bool(no)
 defaults(localhost,             bool(no)).
 defaults(modules,               bool(no)).
 defaults(proc,                  int(0)).
+defaults(procrep_coverage,      int(0)).
 defaults(quit,                  bool(no)).
 defaults(root,                  bool(no)).
 defaults(record_loop,           bool(yes)).
@@ -886,15 +889,18 @@ default_cmd(Options) = Cmd :-
     lookup_bool_option(Options, root, Root),
     lookup_bool_option(Options, modules, Modules),
     lookup_int_option(Options, clique, CliqueNum),
-    lookup_int_option(Options, proc, ProcNum),
+    lookup_int_option(Options, proc, ProcProcNum),
+    lookup_int_option(Options, procrep_coverage, ProcrepCoverageProcNum),
     ( Root = yes ->
         Cmd = deep_cmd_root(no)
     ; Modules = yes ->
         Cmd = deep_cmd_program_modules
     ; CliqueNum > 0 ->
         Cmd = deep_cmd_clique(clique_ptr(CliqueNum))
-    ; ProcNum > 0 ->
-        Cmd = deep_cmd_proc(proc_static_ptr(ProcNum))
+    ; ProcProcNum > 0 ->
+        Cmd = deep_cmd_proc(proc_static_ptr(ProcProcNum))
+    ; ProcrepCoverageProcNum > 0 ->
+        Cmd = deep_cmd_procrep_coverage(proc_static_ptr(ProcrepCoverageProcNum))
     ; Quit = yes ->
         Cmd = deep_cmd_quit
     ;
Index: deep_profiler/mdprof_test.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/mdprof_test.m,v
retrieving revision 1.19
diff -u -p -b -r1.19 mdprof_test.m
--- deep_profiler/mdprof_test.m	28 Aug 2008 10:26:14 -0000	1.19
+++ deep_profiler/mdprof_test.m	17 Sep 2008 02:19:16 -0000
@@ -120,16 +120,20 @@ main2(ProgName, Args, Options, !IO) :-
         read_and_startup(Machine, ScriptName, FileName, Canonical,
             MaybeOutput, DumpStages, DumpOptions, Res, !IO),
         (
-            ( Res = deep_and_error(Deep, _)
-            ; Res = deep_and_progrep(Deep, _)
+            (
+                Res = deep_and_error(Deep, _),
+                MaybeProgrep = error("Couldn't read Deep.procrep file")
+            ; 
+                Res = deep_and_progrep(Deep, ProgRep),
+                MaybeProgrep = ok(ProgRep)
             ),
             lookup_bool_option(Options, test, Test),
             (
                 Test = no
             ;
                 Test = yes,
-                lookup_string_option(Options, test_dir, TestDir),
-                test_server(TestDir, default_preferences(Deep), Deep, !IO)
+                test_server(default_preferences(Deep), Deep, MaybeProgrep,
+                    Options, !IO)
             )
         ;
             Res = error(Error),
@@ -202,59 +206,81 @@ write_version_message(ProgName, !IO) :-
 
 write_help_message(ProgName) -->
     io.format("Usage: %s [<options>] <filename>\n", [s(ProgName)]),
-    io.format("<filename> must name a deep profiling data file.\n", []),
-    io.format("You should specify one of the following options:\n", []),
-    io.format("--help      Generate this help message.\n", []),
-    io.format("--version   Report the program's version number.\n", []),
-    io.format("--verbose   Generate progress messages during startup.\n", []),
-    io.format("--test      Test the deep profiler, generating all\n", []),
-    io.format("            possible web pages of the popular types.\n", []),
-    io.format("--verify-profile\n", []),
-    io.format("            Verify that <filename> is a well-formed\n",
-        []),
-    io.format("            deep profiling data file.\n", []),
-    io.nl,
-    io.format("You may also specify the following options:.\n", []),
-    io.format("--test-dir <dirname>\n", []),
-    io.format("            Put the generated web pages into <dirname>.\n",
-        []).
+    io.write_string(
+        "<filename> must name a deep profiling data file.\n" ++
+        "You should specify one of the following options:\n" ++
+        "--help      Generate this help message.\n" ++
+        "--version   Report the program's version number.\n" ++
+        "--verbose   Generate progress messages during startup.\n" ++
+        "--test      Test the deep profiler, generating all\n" ++
+        "\t\t\tpossible web pages of the popular types.\n" ++
+        "--verify-profile\n" ++
+        "\t\t\tVerify that <filename> is a well-formed deep profiling\n" ++ 
+        "\t\t\tdata file.\n" ++
+        "\n" ++
+        "You may also specify the following options:.\n" ++
+        "--test-dir <dirname>\n" ++
+        "\t\t\tPut the generated web pages into <dirname>.\n" ++
+        "--no-compress\n" ++
+        "\t\t\tDon't compress the resulting files, this speeds the test.").
     % --canonical-clique is not documented because it is not yet supported
 
 %-----------------------------------------------------------------------------%
 
-:- pred test_server(string::in, preferences::in, deep::in,
-    io::di, io::uo) is cc_multi.
+:- pred test_server(preferences::in, deep::in, maybe_error(prog_rep)::in,
+    option_table::in, io::di, io::uo) is cc_multi.
 
-test_server(DirName, Pref, Deep, !IO) :-
+test_server(Pref, Deep, MaybeProgrep, Options, !IO) :-
+    lookup_string_option(Options, test_dir, DirName),
     string.format("test -d %s || mkdir -p %s", [s(DirName), s(DirName)], Cmd),
     io.call_system(Cmd, _, !IO),
-    array.max(Deep ^ clique_members, NumCliques),
-    test_cliques(1, NumCliques, DirName, Pref, Deep, !IO),
+    
+    %XXX: These features have been disabled.  Configuration options should be
+    % introduced to enable them as the user desires.
+    % array.max(Deep ^ clique_members, NumCliques),
+    % test_cliques(1, NumCliques, DirName, Pref, Deep, !IO),
+    % test_procs(1, NumProcStatics, DirName, Pref, Deep, !IO).
+    
     array.max(Deep ^ proc_statics, NumProcStatics),
-    test_procs(1, NumProcStatics, DirName, Pref, Deep, !IO).
+    test_procrep_coverages(1, NumProcStatics, Pref, Deep, MaybeProgrep,
+        Options, !IO).
 
-:- pred test_cliques(int::in, int::in, string::in, preferences::in, deep::in,
-    io::di, io::uo) is cc_multi.
+:- pred test_cliques(int::in, int::in, option_table::in, preferences::in,
+    deep::in, io::di, io::uo) is cc_multi.
 
-test_cliques(Cur, Max, DirName, Pref, Deep, !IO) :-
+test_cliques(Cur, Max, Options, Pref, Deep, !IO) :-
     ( Cur =< Max ->
         try_exec(deep_cmd_clique(clique_ptr(Cur)), Pref, Deep, progrep_error,
             HTML, !IO),
-        write_test_html(DirName, "clique", Cur, HTML, !IO),
-        test_cliques(Cur + 1, Max, DirName, Pref, Deep, !IO)
+        write_test_html(Options, "clique", Cur, HTML, !IO),
+        test_cliques(Cur + 1, Max, Options, Pref, Deep, !IO)
     ;
         true
     ).
 
-:- pred test_procs(int::in, int::in, string::in, preferences::in, deep::in,
-    io::di, io::uo) is cc_multi.
+:- pred test_procs(int::in, int::in, option_table::in, preferences::in,
+    deep::in, io::di, io::uo) is cc_multi.
 
-test_procs(Cur, Max, DirName, Pref, Deep, !IO) :-
+test_procs(Cur, Max, Options, Pref, Deep, !IO) :-
     ( Cur =< Max ->
         try_exec(deep_cmd_proc(proc_static_ptr(Cur)), Pref, Deep,
             progrep_error, HTML, !IO),
-        write_test_html(DirName, "proc", Cur, HTML, !IO),
-        test_procs(Cur + 1, Max, DirName, Pref, Deep, !IO)
+        write_test_html(Options, "proc", Cur, HTML, !IO),
+        test_procs(Cur + 1, Max, Options, Pref, Deep, !IO)
+    ;
+        true
+    ).
+
+:- pred test_procrep_coverages(int::in, int::in, preferences::in, deep::in,
+    maybe_error(prog_rep)::in, option_table::in, io::di, io::uo) is cc_multi.
+
+test_procrep_coverages(Cur, Max, Pref, Deep, MaybeProgrep, Options, !IO) :-
+    ( Cur =< Max ->
+        try_exec(deep_cmd_procrep_coverage(proc_static_ptr(Cur)), Pref, Deep,
+            MaybeProgrep, HTML, !IO),
+        write_test_html(Options, "procrep_coverage", Cur, HTML, !IO),
+        test_procrep_coverages(Cur + 1, Max, Pref, Deep, MaybeProgrep,
+            Options, !IO)
     ;
         true
     ).
@@ -264,10 +290,10 @@ test_procs(Cur, Max, DirName, Pref, Deep
 progrep_error = 
     error("No Program Representation available when using mdprof_test").
 
-:- pred write_test_html(string::in, string::in, int::in, string::in,
+:- pred write_test_html(option_table::in, string::in, int::in, string::in,
     io::di, io::uo) is det.
 
-write_test_html(DirName, BaseName, Num, HTML, !IO) :-
+write_test_html(Options, BaseName, Num, HTML, !IO) :-
     % For large programs such as the Mercury compiler, the profiler data
     % file may contain hundreds of thousands of cliques. We therefore put
     % each batch of pages in a different subdirectory, thus limiting the
@@ -275,6 +301,7 @@ write_test_html(DirName, BaseName, Num, 
     %
     % XXX consider splitting up this predicate
     Bunch = (Num - 1) // 1000,
+    lookup_string_option(Options, test_dir, DirName),
     string.format("%s/%s_%04d",
         [s(DirName), s(BaseName), i(Bunch)], BunchName),
     ( (Num - 1) rem 1000 = 0 ->
@@ -291,9 +318,15 @@ write_test_html(DirName, BaseName, Num, 
         Res = ok(Stream),
         io.write_string(Stream, HTML, !IO),
         io.close_output(Stream, !IO),
+        lookup_bool_option(Options, compress, Compress),
+        (
+            Compress = yes,
         string.format("gzip %s", [s(FileName)], GzipCmd),
         io.call_system(GzipCmd, _, !IO)
     ;
+            Compress = no
+        )
+    ;
         Res = error(Err),
         io.error_message(Err, ErrMsg),
         error(ErrMsg)
@@ -305,7 +338,7 @@ write_test_html(DirName, BaseName, Num, 
     --->    canonical_clique
     ;       dump
     ;       dump_options
-    ;       flat
+    ;       compress
     ;       help
     ;       test
     ;       test_dir
@@ -327,6 +360,7 @@ short('v',  verbose).
 :- pred long(string::in, option::out) is semidet.
 
 long("canonical-clique",    canonical_clique).
+long("compress",            compress).
 long("dump",                dump).
 long("dump-options",        dump_options).
 long("help",                help).
@@ -339,6 +373,7 @@ long("verify-profile",      verify_profi
 :- pred defaults(option::out, option_data::out) is multi.
 
 defaults(canonical_clique,  bool(no)).
+defaults(compress,          bool(yes)).
 defaults(dump,              accumulating([])).
 defaults(dump_options,      accumulating([])).
 defaults(help,              bool(no)).
Index: deep_profiler/program_representation_utils.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/program_representation_utils.m,v
retrieving revision 1.2
diff -u -p -b -r1.2 program_representation_utils.m
--- deep_profiler/program_representation_utils.m	4 Sep 2008 11:41:02 -0000	1.2
+++ deep_profiler/program_representation_utils.m	17 Sep 2008 03:17:01 -0000
@@ -22,9 +22,14 @@
 
 :- import_module mdbcomp.
 :- import_module mdbcomp.program_representation.
+:- import_module measurements.
+:- import_module profile.
+:- import_module report.
 
 :- import_module cord.
+:- import_module map.
 :- import_module string.
+:- import_module unit.
 
 %----------------------------------------------------------------------------%
 
@@ -34,9 +39,25 @@
     %
 :- pred print_module_to_strings(module_rep::in, cord(string)::out) is det.
 
-    % Ugly-print a procedure to a string representation.
+    % Print a procedure to a string representation.
     %
-:- pred print_proc_to_strings(proc_rep::in, cord(string)::out) is det.
+:- pred print_proc_to_strings(proc_rep(GoalAnn), cord(string)) <=
+    (goal_annotation(GoalAnn)).
+:- mode print_proc_to_strings(in, out) is det.
+
+%----------------------------------------------------------------------------%
+
+:- typeclass goal_annotation(T) where [
+            % Print the goal annotation for inclusion by print_proc_to_strings
+            % above.
+            %
+        pred print_goal_annotation_to_strings(T::in, cord(string)::out) is det
+    ].
+
+    % A goal with no particular annotation has empty strings printed for goal
+    % annotations.
+    %
+:- instance goal_annotation(unit).
 
 %----------------------------------------------------------------------------%
 
@@ -48,23 +69,36 @@
 
 %----------------------------------------------------------------------------%
 
+    % Annotate the program representation structure with coverage information.
+    %
+:- pred procrep_annotate_with_coverage(own_prof_info::in,
+    map(goal_path, call_site_perf)::in, map(goal_path, coverage_point)::in,
+    map(goal_path, coverage_point)::in, proc_rep::in, 
+    proc_rep(coverage_info)::out) is det.
+
+%----------------------------------------------------------------------------%
+
 :- implementation.
 
 :- import_module mdbcomp.prim_data.
 
+:- import_module array.
 :- import_module bool.
 :- import_module int.
+:- import_module io.
 :- import_module list.
 :- import_module map.
 :- import_module maybe.
+:- import_module require.
 
 %----------------------------------------------------------------------------%
 
 print_module_to_strings(ModuleRep, Strings) :-
     ModuleRep = module_rep(ModuleName, _StringTable, ProcReps),
-    map.foldl((pred(_::in, ProcRep::in, Str0::in, Str::out) is det :-
-            print_proc_to_strings(ProcRep, Str1),
-            Str = Str0 ++ Str1), ProcReps, cord.empty, ProcStrings),
+    map.foldl((pred(_::in, Proc::in, Str0::in, Str::out) is det :-
+            print_proc_to_strings(Proc, Str1),
+            Str = Str0 ++ Str1
+        ), ProcReps, cord.empty, ProcStrings),
     Strings = cord.cons(string.format("Module %s\n", [s(ModuleName)]), 
         ProcStrings).
 
@@ -104,38 +138,40 @@ print_proc_label_to_strings(Detism, Proc
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_goal_to_strings(var_table::in, int::in, goal_rep::in,
-    cord(string)::out) is det.
+:- pred print_goal_to_strings(var_table, int, goal_rep(GoalAnn), cord(string))
+    <= goal_annotation(GoalAnn).
+:- mode print_goal_to_strings(in, in, in, out) is det.
 
 print_goal_to_strings(VarTable, Indent, GoalRep, Strings) :-
-    GoalRep = goal_rep(GoalExprRep, DetismRep, _),
+    GoalRep = goal_rep(GoalExprRep, DetismRep, GoalAnnotation),
+    detism_to_string(DetismRep, DetismString),
+    print_goal_annotation_to_strings(GoalAnnotation, GoalAnnotationString),
     (
         GoalExprRep = conj_rep(ConjGoalReps),
-        print_conj_to_strings(VarTable, Indent, ConjGoalReps, Strings)
+        print_conj_to_strings(VarTable, Indent, ConjGoalReps,
+            Strings)
     ;
         GoalExprRep = disj_rep(DisjGoalReps),
-        detism_to_string(DetismRep, DetismString),
         print_disj_to_strings(VarTable, Indent, DisjGoalReps, no, DisjString),
-        Strings = indent(Indent) ++ DetismString ++ cord.singleton(" (\n") ++
-            DisjString ++ indent(Indent) ++ cord.singleton(")\n") 
+        Strings = indent(Indent) ++ DetismString ++ GoalAnnotationString ++
+            cord.singleton(" (\n") ++ DisjString ++ indent(Indent) ++
+            cord.singleton(")\n") 
     ;
         GoalExprRep = switch_rep(SwitchVarRep, CasesRep),
-        detism_to_string(DetismRep, DetismString),
         lookup_var_name(VarTable, SwitchVarRep, SwitchVarName),
         string.format(" ( switch on %s\n", [s(SwitchVarName)],
             SwitchOpenString),
         print_switch_to_strings(VarTable, Indent, CasesRep, no, SwitchString),
-        Strings = indent(Indent) ++ DetismString ++
+        Strings = indent(Indent) ++ DetismString ++ GoalAnnotationString ++
             cord.singleton(SwitchOpenString) ++ SwitchString ++ 
             indent(Indent) ++ cord.singleton(")\n")
     ;
         GoalExprRep = ite_rep(CondRep, ThenRep, ElseRep),
-        detism_to_string(DetismRep, DetismString),
         print_goal_to_strings(VarTable, Indent + 1, CondRep, CondString),
         print_goal_to_strings(VarTable, Indent + 1, ThenRep, ThenString),
         print_goal_to_strings(VarTable, Indent + 1, ElseRep, ElseString),
         IndentString = indent(Indent),
-        Strings = IndentString ++ DetismString ++
+        Strings = IndentString ++ DetismString ++ GoalAnnotationString ++
             cord.singleton(" (\n") ++ CondString ++ IndentString ++
             cord.singleton("->\n") ++ ThenString ++ IndentString ++
             cord.singleton(";\n") ++ ElseString ++ IndentString ++
@@ -147,7 +183,6 @@ print_goal_to_strings(VarTable, Indent, 
             ++ indent(Indent) ++ cord.singleton(")\n")
     ;
         GoalExprRep = scope_rep(SubGoalRep, MaybeCut),
-        detism_to_string(DetismRep, DetismString),
         (
             MaybeCut = scope_is_cut,
             CutString = cord.empty 
@@ -156,18 +191,19 @@ print_goal_to_strings(VarTable, Indent, 
             CutString = cord.singleton(" cut")
         ),
         print_goal_to_strings(VarTable, Indent + 1, SubGoalRep, SubGoalString),
-        Strings = indent(Indent) ++ DetismString ++ cord.singleton(" scope") ++
-            CutString ++ cord.singleton(" (\n") ++ SubGoalString ++
-            indent(Indent) ++ cord.singleton(")\n") 
+        Strings = indent(Indent) ++ DetismString ++ GoalAnnotationString ++ 
+            cord.singleton(" scope") ++ CutString ++ cord.singleton(" (\n") ++
+            SubGoalString ++ indent(Indent) ++ cord.singleton(")\n") 
     ;
         GoalExprRep = atomic_goal_rep(_FileName, _LineNumber,
             _BoundVars, AtomicGoalRep),
-        print_atomic_goal_to_strings(VarTable, Indent, DetismRep,
-            AtomicGoalRep, Strings)
+        print_atomic_goal_to_strings(GoalAnnotationString, VarTable, Indent,
+            DetismRep, AtomicGoalRep, Strings)
     ).
 
-:- pred print_conj_to_strings(var_table::in, int::in, list(goal_rep)::in,
-    cord(string)::out) is det.
+:- pred print_conj_to_strings(var_table, int, list(goal_rep(GoalAnn)),
+    cord(string)) <= goal_annotation(GoalAnn).
+:- mode print_conj_to_strings(in, in, in, out) is det.
 
 print_conj_to_strings(VarTable, Indent, GoalReps, Strings) :-
     (
@@ -178,8 +214,9 @@ print_conj_to_strings(VarTable, Indent, 
         print_conj_2_to_strings(VarTable, Indent, GoalReps, Strings)
     ).
 
-:- pred print_conj_2_to_strings(var_table::in, int::in, list(goal_rep)::in, 
-    cord(string)::out) is det.
+:- pred print_conj_2_to_strings(var_table, int, list(goal_rep(GoalAnn)), 
+    cord(string)) <= goal_annotation(GoalAnn).
+:- mode print_conj_2_to_strings(in, in, in, out) is det.
 
 print_conj_2_to_strings(_, _Indent, [], cord.empty).
 print_conj_2_to_strings(VarTable, Indent, [GoalRep | GoalReps], Strings) :-
@@ -192,8 +229,9 @@ print_conj_2_to_strings(VarTable, Indent
     print_conj_2_to_strings(VarTable, Indent, GoalReps, ConjString),
     Strings = GoalString ++ ConjString.
 
-:- pred print_disj_to_strings(var_table::in, int::in, list(goal_rep)::in,
-    bool::in, cord(string)::out) is det.
+:- pred print_disj_to_strings(var_table, int, list(goal_rep(GoalAnn)), bool,
+    cord(string)) <= goal_annotation(GoalAnn).
+:- mode print_disj_to_strings(in, in, in, in, out) is det.
 
 print_disj_to_strings(_, _Indent, [], _PrintSemi, cord.empty).
 print_disj_to_strings(VarTable, Indent, [GoalRep | GoalReps], PrintSemi, Strings) :-
@@ -208,8 +246,9 @@ print_disj_to_strings(VarTable, Indent, 
     print_disj_to_strings(VarTable, Indent, GoalReps, yes, DisjString),
     Strings = DelimString ++ GoalString ++ DisjString.
 
-:- pred print_switch_to_strings(var_table::in, int::in, list(case_rep)::in,
-    bool::in, cord(string)::out) is det.
+:- pred print_switch_to_strings(var_table, int, list(case_rep(GoalAnn)), bool,
+    cord(string)) <= goal_annotation(GoalAnn).
+:- mode print_switch_to_strings(in, in, in, in, out) is det.
 
 print_switch_to_strings(_, _Indent, [], _PrintSemi, cord.empty).
 print_switch_to_strings(VarTable, Indent, [CaseRep | CaseReps], PrintSemi, Strings) :-
@@ -241,11 +280,11 @@ print_cons_id_and_arity_to_strings(Inden
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_atomic_goal_to_strings(var_table::in, int::in, detism_rep::in, 
-    atomic_goal_rep::in, cord(string)::out) is det.
+:- pred print_atomic_goal_to_strings(cord(string)::in, var_table::in, int::in,
+    detism_rep::in, atomic_goal_rep::in, cord(string)::out) is det.
 
-print_atomic_goal_to_strings(VarTable, Indent, DetismRep, AtomicGoalRep,
-        Strings) :-
+print_atomic_goal_to_strings(GoalAnnotationString, VarTable, Indent, DetismRep,
+        AtomicGoalRep, Strings) :-
     (
         (
             AtomicGoalRep = unify_construct_rep(VarRep, ConsIdRep, ArgReps),
@@ -329,7 +368,8 @@ print_atomic_goal_to_strings(VarTable, I
         Strings0 = cord.cons(HeadString, ArgsString)
     ),
     detism_to_string(DetismRep, DetismString),
-    Strings = indent(Indent) ++ DetismString ++ Strings0 ++ nl.
+    Strings = indent(Indent) ++ DetismString ++ GoalAnnotationString ++
+        Strings0 ++ nl.
 
 %-----------------------------------------------------------------------------%
 
@@ -431,11 +471,19 @@ nl = cord.singleton("\n").
 
 %----------------------------------------------------------------------------%
 
+:- instance goal_annotation(unit) where [
+        pred(print_goal_annotation_to_strings/2) is print_unit_to_strings
+    ].
+
+:- pred print_unit_to_strings(unit::in, cord(string)::out) is det.
+
+print_unit_to_strings(_, cord.empty).
+
+%----------------------------------------------------------------------------%
+
 progrep_search_proc(ProgRep, ProcLabel, ProcRep) :-
-    % XXX: what's the difference between these two module fields? which should
-    % I be using.
-    ( ProcLabel = str_ordinary_proc_label(_, Module, _Module2, _, _, _)
-    ; ProcLabel = str_special_proc_label(_, Module, _Module2, _, _, _)
+    ( ProcLabel = str_ordinary_proc_label(_, Module, _DefModule, _, _, _)
+    ; ProcLabel = str_special_proc_label(_, Module, _DefModule, _, _, _)
     ),
     progrep_search_module(ProgRep, Module, ModuleRep),
     modulerep_search_proc(ModuleRep, ProcLabel, ProcRep).
@@ -459,3 +507,1000 @@ modulerep_search_proc(ModuleRep, ProcLab
 
 %----------------------------------------------------------------------------%
 
+procrep_annotate_with_coverage(OwnProf, CallSites, SolnsCoveragePoints,
+        BranchCoveragePoints, !ProcRep) :-
+    some [!ProcDefn, !GoalRep] (
+        !:ProcDefn = !.ProcRep ^ pr_defn,
+        !:GoalRep = !.ProcDefn ^ pdr_goal,
+        Calls = calls(OwnProf),
+        Exits = exits(OwnProf),
+        ( Calls = Exits ->
+            Coverage = coverage_known_det(Calls)
+        ;
+            Coverage = coverage_known(Calls, Exits)
+        ),
+        CoverageReference =
+            coverage_reference_info(CallSites, SolnsCoveragePoints, 
+                BranchCoveragePoints),
+        goal_annotate_coverage(CoverageReference, empty_goal_path, Coverage, _,
+            !GoalRep),
+        !:ProcDefn = !.ProcDefn ^ pdr_goal := !.GoalRep,
+        !:ProcRep = !.ProcRep ^ pr_defn := !.ProcDefn
+    ).
+
+    % These maps are keyed by goal_path, which is a structure with arbitrary,
+    % comparing these structures is less efficient than comparing simple
+    % structures like the alternative goal_path_string, however, that involves
+    % frequently constructing strings from goal paths.  Using goal_path_string
+    % may be faster but I'd rather not make this optimisation without first
+    % testing it.
+    %
+:- type coverage_reference_info
+    --->    coverage_reference_info(
+                cri_call_sites              :: map(goal_path, call_site_perf),
+                cri_solns_coverage_points   :: map(goal_path, coverage_point),
+                cri_branch_coverage_points  :: map(goal_path, coverage_point)
+            ).
+
+    % Annotate a goal and it's children with coverage information.
+    %
+:- pred goal_annotate_coverage(coverage_reference_info::in, goal_path::in,
+    coverage_info::in, coverage_info::out,
+    goal_rep(unit)::in, goal_rep(coverage_info)::out) is det.
+
+goal_annotate_coverage(Info, GoalPath, !Coverage, Goal0, Goal) :-
+    Goal0 = goal_rep(GoalExpr0, Detism, _),
+
+    % Gather any coverage information about this goal and apply it.
+    (
+        get_coverage_after(!.Coverage) = coverage_unknown,
+        map.search(Info ^ cri_solns_coverage_points, GoalPath, CoveragePoint)
+    ->
+        CoveragePoint = coverage_point(Coverage, _, _),
+        !:Coverage = merge_coverage(get_coverage_before(!.Coverage),
+            coverage_known_after(Coverage))
+    ;
+        true
+    ),
+    % TODO: Infer that if a goal has a coverage of exactly 0 before it, then it
+    % must have a coverage of exactly 0 after it.  And that a goal that cannot
+    % fail that has a coverage of 0 after it, must have a coverage of 0 before
+    % it.
+    maybe_propagate_det_coverage(Detism, GoalPath, !Coverage),
+
+    % Calculate coverage of any inner goals.
+    (
+        GoalExpr0 = conj_rep(Conjuncts0),
+        conj_annotate_coverage(Info, GoalPath, 1, !Coverage,
+            Conjuncts0, Conjuncts),
+        GoalExpr = conj_rep(Conjuncts)
+    ;
+        GoalExpr0 = disj_rep(Disjuncts0),
+        disj_annotate_coverage(Info, Detism, GoalPath, !Coverage,
+            Disjuncts0, Disjuncts),
+        GoalExpr = disj_rep(Disjuncts)
+    ;
+        GoalExpr0 = switch_rep(Var, Cases0),
+        switch_annotate_coverage(Info, Detism, GoalPath, !Coverage,
+            Cases0, Cases),
+        GoalExpr = switch_rep(Var, Cases)
+    ;
+        GoalExpr0 = ite_rep(Cond0, Then0, Else0),
+        ite_annotate_coverage(Info, GoalPath, !Coverage, Cond0, Cond,
+            Then0, Then, Else0, Else),
+        GoalExpr = ite_rep(Cond, Then, Else)
+    ;
+        GoalExpr0 = negation_rep(NegGoal0),
+        negation_annotate_coverage(Info, GoalPath, !Coverage, 
+            NegGoal0, NegGoal), 
+        GoalExpr = negation_rep(NegGoal)
+    ;
+        GoalExpr0 = scope_rep(ScopedGoal0, MaybeCut),
+        scope_annotate_coverage(Info, GoalPath, MaybeCut, !Coverage, 
+            ScopedGoal0, ScopedGoal),
+        GoalExpr = scope_rep(ScopedGoal, MaybeCut)
+    ;
+        GoalExpr0 = atomic_goal_rep(Filename, Line, Vars, AtomicGoal),
+        ( 
+            ( AtomicGoal = unify_construct_rep(_, _, _)
+            ; AtomicGoal = unify_deconstruct_rep(_, _, _)
+            ; AtomicGoal = partial_deconstruct_rep(_, _, _)
+            ; AtomicGoal = partial_construct_rep(_, _, _)
+            ; AtomicGoal = unify_assign_rep(_, _)
+            ; AtomicGoal = cast_rep(_, _)
+            ; AtomicGoal = unify_simple_test_rep(_, _)
+            ; AtomicGoal = event_call_rep(_, _)
+            )
+        ;
+            ( AtomicGoal = higher_order_call_rep(_, _)
+            ; AtomicGoal = method_call_rep(_, _, _)
+            ; AtomicGoal = plain_call_rep(_, _, _)
+            ; AtomicGoal = builtin_call_rep(_, _, _)
+            ; AtomicGoal = pragma_foreign_code_rep(_)
+            ),
+            ( map.search(Info ^ cri_call_sites, GoalPath, CallSite) ->
+                Summary = CallSite ^ csf_summary_perf,
+                % Entry due to redo is not counted at the point before the
+                % goal, it's represented when the number of exists is greater
+                % than the number of calls,  This won't work with nondet code
+                % which should be fixed in the future.
+                Calls = Summary ^ perf_row_calls,
+                Exits = Summary ^ perf_row_exits, 
+                !:Coverage = coverage_known(Calls, Exits)
+            ;
+                (
+                    % These goal call types must have call sites, whereas some
+                    % builtins and foreign code pragmas may not.
+                    ( AtomicGoal = higher_order_call_rep(_, _)
+                    ; AtomicGoal = method_call_rep(_, _, _)
+                    ; AtomicGoal = plain_call_rep(_, _, _)
+                    )
+                ->
+                    error("Couldn't look up call site for port counts GP: " ++
+                        goal_path_to_string(GoalPath))
+                ;
+                    true
+                )
+            )
+        ),
+        GoalExpr = atomic_goal_rep(Filename, Line, Vars, AtomicGoal)
+    ),
+    maybe_propagate_det_coverage(Detism, GoalPath, !Coverage),
+    Goal = goal_rep(GoalExpr, Detism, !.Coverage),
+    trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+        io.write_string("goal_annotate_coverage: done\n", !IO),
+        io.format("\tGoalPath: %s\n\tDetism %s\n\tCoverage; %s\n", 
+            [s(goal_path_to_string(GoalPath)), 
+             s(string(Detism)), 
+             s(string(!.Coverage))], !IO)
+    ),
+    require(check_coverage_regarding_detism(!.Coverage, Detism), 
+        string.format("check_coverage_regarding_detism failed: %s %s", 
+            [s(string(!.Coverage)), s(string(Detism))])).
+
+    % Annotate a conjunction with coverage information.  This folds from the
+    % right over the list of conjuncts (backwards).
+    %
+    % The list of goals is the tail of a conjunction, the coverage argument
+    % describes the coverage of this list of goals if it where the entire
+    % conjunction.  However each goal has it's own coverage.
+    %
+:- pred conj_annotate_coverage(coverage_reference_info::in, goal_path::in,
+    int::in, coverage_info::in, coverage_info::out,
+    list(goal_rep(unit))::in, list(goal_rep(coverage_info))::out) is det.
+
+conj_annotate_coverage(_, GoalPath, ConjunctNum, !Coverage, [], []) :-
+    % The empty conjunction is equivalent to 'true' which is deterministic,
+    ConjGoalPath = goal_path_add_at_end(GoalPath, step_conj(ConjunctNum)),
+    propagate_det_coverage(ConjGoalPath, !Coverage).
+
+conj_annotate_coverage(Info, GoalPath, ConjunctNum, !Coverage, 
+        [Conj0 | Conjs0], [Conj | Conjs]) :-
+    split_coverage(!.Coverage, CoverageBefore0, CoverageAfter0),
+    conj_annotate_coverage(Info, GoalPath, ConjunctNum+1,
+        CoverageAfter0, TailCoverage1, Conjs0, Conjs1),
+    split_coverage(TailCoverage1, CoverageBeforeTail1, CoverageAfter1),
+
+    goal_transition_coverage(CoverageAfterHead0, CoverageBeforeTail1),
+    HeadCoverage0 = merge_coverage(CoverageBefore0, CoverageAfterHead0),
+    goal_annotate_coverage(Info,
+        goal_path_add_at_end(GoalPath, step_conj(ConjunctNum)),
+        HeadCoverage0, HeadCoverage, Conj0, Conj),
+    
+    % If computing the coverage for the head gave us information that can be
+    % used to re-compute the coverage for the tail, and we don't already know
+    % the coverage at the beginning of the tail.  Then re-compute the coverage
+    % for the tail.
+    split_coverage(HeadCoverage, CoverageBefore, CoverageAfterHead),
+    (
+        CoverageBeforeTail1 = coverage_unknown,
+        CoverageAfterHead = coverage_known_after(Count)
+    -> 
+        CoverageBeforeTail = coverage_known_before(Count),
+        TailCoverage2 = merge_coverage(CoverageBeforeTail, CoverageAfter1),
+        conj_annotate_coverage(Info, GoalPath, ConjunctNum+1,
+            TailCoverage2, TailCoverage, Conjs0, Conjs),
+        CoverageAfter = get_coverage_after(TailCoverage)
+    ;
+        Conjs = Conjs1,
+        CoverageAfter = CoverageAfter1
+    ),
+    !:Coverage = merge_coverage(CoverageBefore, CoverageAfter).
+
+    % Compute the coverage information for a disjunction.
+    %
+    % Rules:
+    %   - The coverage before a disjunction is equal to the coverage before the
+    %     first disjunct.
+    %   - The coverage after a disjunction is equal to the sum of coverages
+    %     after each disjunct.
+    %   - If the disjunction has at most one solution, then the coverage
+    %     entering a disjunct is the failure count of the previous disjunct.
+    %
+    % Examples:
+    %   A semidet disjunction.
+    %     5 ( 5 D1 2; 3 D2 2; 1 D3 0 ) 4
+    %
+    %   A nondet disjunction.
+    %     5 ( 5 D1 2; 5 D2 3; 5 D3 1 ) 6 (2 exit, 4 redo)
+    %
+    % For simplicity start with a backwards-only traversal, Not all the rules
+    % described in this comment are applied.
+    %
+:- pred disj_annotate_coverage(coverage_reference_info::in, detism_rep::in,
+    goal_path::in, coverage_info::in, coverage_info::out,
+    list(goal_rep(unit))::in, list(goal_rep(coverage_info))::out) is det.
+
+disj_annotate_coverage(Info, _Detism, GoalPath, !Coverage, 
+        Disjs0, Disjs) :-
+    CoverageBefore0 = get_coverage_before(!.Coverage),
+    disj_annotate_coverage_2(Info, GoalPath, 1,
+        Disjs0, Disjs, CoverageBefore),
+
+    % If coverage before the disjunction was unknown before and is now
+    % discovered, update it.
+    (
+        CoverageBefore0 = coverage_unknown,
+        CoverageBefore = coverage_known_before(_)
+    ->
+        CoverageAfter = get_coverage_after(!.Coverage),
+        !:Coverage = merge_coverage(CoverageBefore, CoverageAfter)
+    ;
+        true
+    ).
+
+:- pred disj_annotate_coverage_2(coverage_reference_info::in,
+    goal_path::in, int::in,
+    list(goal_rep)::in, list(goal_rep(coverage_info))::out,
+    coverage_info::out(coverage_before)) is det.
+
+disj_annotate_coverage_2(_, _, _, [], [], coverage_known_before(0)).
+
+disj_annotate_coverage_2(Info, GoalPath, DisjNum, 
+        [Disj0 | Disjs0], [Disj | Disjs], CoverageBefore) :-
+    disj_annotate_coverage_2(Info, GoalPath, DisjNum + 1,
+        Disjs0, Disjs, _),
+
+    ThisGoalPath = goal_path_add_at_end(GoalPath, step_disj(DisjNum)),
+    get_branch_coverage(Info, ThisGoalPath, CoverageBeforeDisj),
+    % This can be set from the coverage entering the next disjunct, however the
+    % transformation in the compiler doesn't do this, so for simplicity, this
+    % is pessimistic.  Otherwise set is using CoverageBeforeTail.
+    CoverageAfterDisj = coverage_unknown,
+    CoverageDisj0 = merge_coverage(CoverageBeforeDisj, CoverageAfterDisj),
+
+    goal_annotate_coverage(Info, ThisGoalPath, CoverageDisj0, CoverageDisj,
+        Disj0, Disj),
+    CoverageBefore = get_coverage_before(CoverageDisj).
+
+:- pred switch_annotate_coverage(coverage_reference_info::in, detism_rep::in,
+    goal_path::in, coverage_info::in, coverage_info::out, 
+    list(case_rep(unit))::in, list(case_rep(coverage_info))::out) is det.
+
+switch_annotate_coverage(Info, Detism, GoalPath, !Coverage, Cases0, Cases) :-
+    switch_annotate_coverage_2(Info, Detism, GoalPath, 1,
+        coverage_known_det(0), SwitchCoverage, !.Coverage, Cases0, Cases),
+    % Use the newly computed coverage if it's more informed than the current
+    % coverage.
+    (
+        !.Coverage = coverage_known_det(_)
+    ;
+        !.Coverage = coverage_known(_, _)
+    ;
+        !.Coverage = coverage_known_before(Before),
+        (
+            coverage_count_after(SwitchCoverage, After)
+        ->
+            !:Coverage = coverage_known(Before, After)
+        ;
+            true
+        )
+    ;
+        !.Coverage = coverage_known_after(After),
+        (
+            coverage_count_before(SwitchCoverage, Before)
+        ->
+            !:Coverage = coverage_known(Before, After)
+        ;
+            true
+        )
+    ;
+        !.Coverage = coverage_unknown,
+        !:Coverage = SwitchCoverage
+    ),
+
+    require(check_switch_coverage(Detism, Cases, !.Coverage),
+        string.format("check_switch_coverage failed\n\t" ++ 
+            "Detism: %s\n\tCases: %s\n\tCoverage: %s\n",
+        [s(string(Detism)), s(string(Cases)), s(string(!.Coverage))])).
+
+    % switch_annotate_coverage_2(Info, Detism, GoalPath, CaseNum, 
+    %   !CoverageSum, SwitchCoverage, !Cases),
+    %
+    % Perform coverage annotation on cases from the left to the right, The head
+    % of the !.Cases list is case number CaseNum, SwitchCoverage is the
+    % coverage for the entire switch as known by the caller, !CoverageSum is
+    % the sum of the coverage so far.
+    %
+    % For this goal we use a forwards traversal, since the last goal may not
+    % have a coverage point after it, in the expectation that the coverage at
+    % the end of the last goal may need to be computed from the coverage of
+    % each of the other goals.
+    %
+:- pred switch_annotate_coverage_2(coverage_reference_info::in, detism_rep::in, 
+    goal_path::in, int::in, coverage_info::in, coverage_info::out,
+    coverage_info::in, 
+    list(case_rep(unit))::in, list(case_rep(coverage_info))::out) is det.
+
+switch_annotate_coverage_2(_, _, _, _, !CoverageSum, _, [], []).
+
+switch_annotate_coverage_2(Info, Detism, GoalPath, CaseNum, 
+        !CoverageSum, SwitchCoverage, [ Case0 | Cases0 ], [ Case | Cases ]) :-
+    CaseGoalPath = goal_path_add_at_end(GoalPath, 
+        step_switch(CaseNum, no)),
+    
+    % If this is the last case in the switch, then it's coverage information
+    % may be computed from the coverage of other cases and the coverage of the
+    % whole switch.  This is only done for the last goal, since only this
+    % optimisation is made by the coverage profiling code in the compiler.
+    %
+    % If we can't calculate it's coverage information then try to retrieve the
+    % information from a coverage point associated with the switch branch.
+    %
+    (
+        Cases0 = [],
+        detism_get_can_fail(Detism) = cannot_fail
+    ->
+        (
+            coverage_count_before(SwitchCoverage, SwitchCountBefore),
+            coverage_count_before(!.CoverageSum, SumCountBefore)
+        ->
+            CoverageBefore0 = 
+                coverage_known_before(SwitchCountBefore - SumCountBefore)
+        ;
+            % Search for a coverage point for this case.
+            get_branch_coverage(Info, CaseGoalPath, CoverageBefore0)
+        ),
+        (
+            coverage_count_after(SwitchCoverage, SwitchCountAfter),
+            coverage_count_after(!.CoverageSum, SumCountAfter)
+        ->
+            CoverageAfter0 = 
+                coverage_known_after(SwitchCountAfter - SumCountAfter)
+        ;
+            CoverageAfter0 = coverage_unknown
+        ),
+        Coverage0 = merge_coverage(CoverageBefore0, CoverageAfter0)
+    ;
+        % Search for a coverage point for this case.
+        get_branch_coverage(Info, CaseGoalPath, Coverage0)
+    ),
+
+    % Look for a coverage point for this switch case.
+    Case0 = case_rep(ConsID, OtherConsIDs, Goal0),
+    goal_annotate_coverage(Info, CaseGoalPath, Coverage0, Coverage,
+        Goal0, Goal),
+    Case = case_rep(ConsID, OtherConsIDs, Goal),
+  
+    % Keep a sum of the coverage seen in cases so far.
+    (
+        coverage_count_before(!.CoverageSum, SumCountBefore1),
+        coverage_count_before(Coverage, CountBefore)
+    ->
+        CoverageSumBefore = coverage_known_before(SumCountBefore1 + CountBefore)
+    ;
+        CoverageSumBefore = coverage_unknown
+    ),
+    (
+        coverage_count_after(!.CoverageSum, SumCountAfter1),
+        coverage_count_after(Coverage, CountAfter)
+    ->
+        CoverageSumAfter = coverage_known_after(SumCountAfter1 + CountAfter)
+    ;
+        CoverageSumAfter = coverage_unknown
+    ),
+    !:CoverageSum = merge_coverage(CoverageSumBefore, CoverageSumAfter),
+
+    switch_annotate_coverage_2(Info, Detism, GoalPath, CaseNum + 1,
+        !CoverageSum, SwitchCoverage, Cases0, Cases).
+
+    % Propagate coverage information for if-then-else goals.
+    %
+    % Step 1:
+    %   Compute the coverage of the Then and Else goals,
+    %
+    % Step 2:
+    %   Infer and compute coverage information for the cond goal.
+    %   
+    % Step 3:
+    %   Infer coverage information for goals using the determinisms of the then
+    %   and else branches and the switch as a whole, and any coverage
+    %   information as computed above.
+    %
+    % Step 4:
+    %   Re-compute coverages for any sub goals within the Then and Else goals
+    %   whose coverage is more known than after step 1.
+    %
+:- pred ite_annotate_coverage(coverage_reference_info::in, goal_path::in,
+    coverage_info::in, coverage_info::out, 
+    goal_rep::in, goal_rep(coverage_info)::out, 
+    goal_rep::in, goal_rep(coverage_info)::out,
+    goal_rep::in, goal_rep(coverage_info)::out) is det.
+
+ite_annotate_coverage(Info, GoalPath, !Coverage,
+        Cond0, Cond, Then0, Then, Else0, Else) :-
+    CondGoalPath = goal_path_add_at_end(GoalPath, step_ite_cond),
+    ThenGoalPath = goal_path_add_at_end(GoalPath, step_ite_then),
+    ElseGoalPath = goal_path_add_at_end(GoalPath, step_ite_else),
+    CondDetism = Cond0 ^ goal_detism_rep,
+
+    % Step 1, compute coverage of each goal without inference.
+    get_branch_coverage(Info, ThenGoalPath, ThenCoverage0),
+    goal_annotate_coverage(Info, ThenGoalPath, ThenCoverage0, ThenCoverage1,
+        Then0, Then1),
+    get_branch_coverage(Info, ElseGoalPath, ElseCoverage0),
+    goal_annotate_coverage(Info, ElseGoalPath, ElseCoverage0, ElseCoverage1,
+        Else0, Else1),
+    
+    % Step 2: Infer coverage for the Cond goal..
+    ( 
+        get_coverage_before(ThenCoverage1) =
+            coverage_known_before(ThenEntryCount)
+    ->
+        CondCoverageAfter0 = coverage_known_after(ThenEntryCount)
+    ;
+        CondCoverageAfter0 = coverage_unknown
+    ),
+    CondCoverage0 = merge_coverage(get_coverage_before(!.Coverage),
+        CondCoverageAfter0),
+    goal_annotate_coverage(Info, CondGoalPath, CondCoverage0, CondCoverage, 
+        Cond0, Cond),
+    split_coverage(CondCoverage, CondCoverageBefore, CondCoverageAfter),
+
+    % Step 3: Infer coverages for the Then and Else goals if unknown.
+    CoverageAfter0 = get_coverage_after(!.Coverage),
+    split_coverage(ThenCoverage1, ThenCoverageBefore1, ThenCoverageAfter1),
+    (
+        ThenCoverageBefore1 = coverage_unknown,
+        CondCoverageAfter = coverage_known_after(CondCountAfterPrime)
+    ->
+        ThenCoverageBefore2 = coverage_known_before(CondCountAfterPrime),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+            io.format("ITE Set coverage before Then: %d\n", 
+                [i(CondCountAfterPrime)], !IO)
+        )
+    ;
+        ThenCoverageBefore2 = ThenCoverageBefore1
+    ),
+    (
+        ThenCoverageAfter1 = coverage_unknown,
+        CoverageAfter0 = coverage_known_after(CountAfterPrime),
+        ElseCoverageAfter1 = coverage_known_after(ElseCountAfterPrime)
+    ->
+        ThenCoverageAfter2 = 
+            coverage_known_after(CountAfterPrime - ElseCountAfterPrime),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+            io.format("ITE Set coverage after Then: %d - %d\n", 
+                [i(CountAfterPrime), i(ElseCountAfterPrime)], !IO)
+        )
+    ;
+        ThenCoverageAfter2 = ThenCoverageAfter1
+    ),
+    ThenCoverage2 = merge_coverage(ThenCoverageBefore2, ThenCoverageAfter2),
+    split_coverage(ElseCoverage1, ElseCoverageBefore1, ElseCoverageAfter1),
+    (
+        ElseCoverageBefore1 = coverage_unknown,
+        CondCoverageAfter = coverage_known_after(CondCountAfter),
+        CondCoverageBefore = coverage_known_before(CondCountBefore),
+        detism_get_solutions(CondDetism) = NumSolutions,
+        ( NumSolutions = at_most_zero
+        ; NumSolutions = at_most_one
+        )
+    ->
+        CondFailures = CondCountBefore - CondCountAfter,
+        ElseCoverageBefore2 = coverage_known_before(CondFailures),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+            io.format("ITE Set coverage before Else: %d\n", 
+                [i(CondFailures)], !IO)
+        )
+    ;
+        ElseCoverageBefore2 = ElseCoverageBefore1
+    ),
+    (
+        ElseCoverageAfter1 = coverage_unknown,
+        CoverageAfter0 = coverage_known_after(CountAfter),
+        ThenCoverageAfter1 = coverage_known_after(ThenCountAfterPrime)
+    ->
+        ElseCoverageAfter2 = 
+            coverage_known_after(CountAfter - ThenCountAfterPrime),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+            io.format("ITE Set coverage after Else: %d - %d\n", 
+                [i(CountAfter), i(ThenCountAfterPrime)], !IO)
+        )
+    ;
+        ElseCoverageAfter2 = ElseCoverageAfter1
+    ),
+    ElseCoverage2 = merge_coverage(ElseCoverageBefore2, ElseCoverageAfter2),
+   
+    % Step 4: If more coverage information was inferred then complete the
+    % coverage calculations for any inner goals in Then and Else.
+    ( ThenCoverage1 \= ThenCoverage2 ->
+        goal_annotate_coverage(Info, ThenGoalPath, ThenCoverage2, ThenCoverage,
+            Then0, Then)
+    ;
+        ThenCoverage = ThenCoverage2,
+        % Then1 is the result of the previous call to gaol_annotate_coverage
+        % for the then goal.
+        Then = Then1
+    ),
+    ( ElseCoverage1 \= ElseCoverage2 ->
+        goal_annotate_coverage(Info, ElseGoalPath, ElseCoverage2, ElseCoverage,
+            Else0, Else)
+    ;
+        ElseCoverage = ElseCoverage2,
+        % Else1 is the result of the previous call to gaol_annotate_coverage
+        % for the else goal.
+        Else = Else1
+    ),
+   
+    % Finally update the coverage state for the whole switch.
+    (
+        get_coverage_after(ThenCoverage) =
+            coverage_known_after(ThenCountAfter),
+        get_coverage_after(ElseCoverage) = 
+            coverage_known_after(ElseCountAfter)
+    ->
+        CoverageAfter = coverage_known_after(ThenCountAfter + ElseCountAfter),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] (
+            io.format("ITE Set coverage after ITE: %d + %d\n", 
+                [i(ThenCountAfter), i(ElseCountAfter)], !IO)
+        )
+    ;
+        CoverageAfter = get_coverage_after(!.Coverage)
+    ),
+    ( get_coverage_before(CondCoverage) = coverage_known_before(CountBefore) ->
+        CoverageBefore = coverage_known_before(CountBefore),
+        trace [ compile_time(flag("debug_coverage_propagation")), io(!IO) ] ( 
+            io.format("ITE Set coverage before ITE: %d\n", [i(CountBefore)],
+                !IO)
+        )
+    ;
+        CoverageBefore = get_coverage_before(!.Coverage)
+    ),
+    !:Coverage = merge_coverage(CoverageBefore, CoverageAfter),
+    require(check_ite_coverage(!.Coverage, CondCoverage, ThenCoverage,
+            ElseCoverage, CondDetism), 
+        string.format("check_ite_coverage/4 failed\n" ++ 
+            "\tWhole: %s\n\tCond: %s\n\tThen: %s\n\tElse: %s\n",
+            [s(string(!.Coverage)), s(string(CondCoverage)),
+            s(string(ThenCoverage)), s(string(ElseCoverage))])).
+
+    % Get the coverage information from a coverage point about the branch
+    % referenced by the given goal path.
+    %
+:- pred get_branch_coverage(coverage_reference_info::in, goal_path::in,
+    coverage_info::out(coverage_before)) is det.
+
+get_branch_coverage(Info, GoalPath, Coverage) :-
+    ( 
+        map.search(Info ^ cri_branch_coverage_points, GoalPath, CP)
+    ->
+        CP = coverage_point(Count, _, _),
+        Coverage = coverage_known_before(Count)
+    ;
+        Coverage = coverage_unknown
+    ).
+
+:- pred negation_annotate_coverage(coverage_reference_info::in, goal_path::in,
+    coverage_info::in, coverage_info::out, 
+    goal_rep::in, goal_rep(coverage_info)::out) is det.
+
+negation_annotate_coverage(Info, GoalPath, Coverage0, Coverage,
+        NegGoal0, NegGoal) :-
+    split_coverage(Coverage0, CoverageBefore, CoverageAfter0),
+    (
+        CoverageAfter0 = coverage_known_after(CountAfter0),
+        CoverageBefore = coverage_known_before(CountBefore)
+    ->
+        CoverageAfter1 = coverage_known_after(CountBefore - CountAfter0)
+    ;
+        CoverageAfter1 = coverage_unknown
+    ),
+    Coverage1 = merge_coverage(CoverageBefore, CoverageAfter1),
+    NegGoalPath = goal_path_add_at_end(GoalPath, step_neg),
+    goal_annotate_coverage(Info, NegGoalPath, Coverage1, Coverage2,
+        NegGoal0, NegGoal),
+    CoverageAfter2 = get_coverage_after(Coverage2),
+    (
+        CoverageAfter2 = coverage_known_after(CountAfter2),
+        CoverageBefore = coverage_known_before(CountBeforePrime)
+    ->
+        CoverageAfter = coverage_known_after(CountBeforePrime - CountAfter2)
+    ;
+        CoverageAfter = coverage_unknown 
+    ),
+    Coverage = merge_coverage(CoverageBefore, CoverageAfter).
+        
+:- pred scope_annotate_coverage(coverage_reference_info::in, goal_path::in,
+    maybe_cut::in, coverage_info::in, coverage_info::out,
+    goal_rep::in, goal_rep(coverage_info)::out) is det.
+
+scope_annotate_coverage(Info, GoalPath, MaybeCut, !Coverage, 
+        ScopedGoal0, ScopedGoal) :-
+    maybe_cut_discard_solutions(MaybeCut, !Coverage),
+    ScopeGoalPath = goal_path_add_at_end(GoalPath, step_scope(MaybeCut)),
+    goal_annotate_coverage(Info, ScopeGoalPath, !Coverage, ScopedGoal0,
+        ScopedGoal),
+    maybe_cut_discard_solutions(MaybeCut, !Coverage).
+
+:- pred maybe_cut_discard_solutions(maybe_cut::in,
+    coverage_info::in, coverage_info::out) is det.
+
+maybe_cut_discard_solutions(MaybeCut, !Coverage) :-
+    (
+        MaybeCut = scope_is_cut,
+        (
+            ( !.Coverage = coverage_unknown
+            ; !.Coverage = coverage_known_after(_)
+            ),
+            !:Coverage = coverage_unknown
+        ;
+            ( !.Coverage = coverage_known(Before, _)
+            ; !.Coverage = coverage_known_det(Before)
+            ; !.Coverage = coverage_known_before(Before)
+            ),
+            !:Coverage = coverage_known_before(Before)
+        )
+    ;
+        MaybeCut = scope_is_no_cut
+    ).
+    
+%----------------------------------------------------------------------------%
+%
+% These predicates are used to check that computed coverage counts make sense.
+%
+    
+    % Check that the coverage of a goal makes sense given the determinism of
+    % that goal.
+    %
+:- pred check_coverage_regarding_detism(coverage_info::in, detism_rep::in) 
+    is semidet.
+
+check_coverage_regarding_detism(Coverage, Detism) :-
+    ( Detism = det_rep
+    ; Detism = cc_multidet_rep
+    ),
+    ( Coverage = coverage_known(Count, Count)
+    ; Coverage = coverage_known_det(_)
+    ; Coverage = coverage_unknown
+    ).
+check_coverage_regarding_detism(Coverage, Detism) :-
+    ( Detism = semidet_rep
+    ; Detism = cc_nondet_rep
+    ),
+    (
+        Coverage = coverage_known(Entry, Exit),
+        Entry >= Exit
+    ; Coverage = coverage_known_before(_)
+    ; Coverage = coverage_known_after(_)
+    ; Coverage = coverage_known_det(_)
+    ; Coverage = coverage_unknown
+    ).
+check_coverage_regarding_detism(Coverage, multidet_rep) :-
+    (
+        Coverage = coverage_known(Entry, Exit),
+        Entry =< Exit
+    ; Coverage = coverage_known_before(_)
+    ; Coverage = coverage_known_after(_)
+    ; Coverage = coverage_known_det(_)
+    ; Coverage = coverage_unknown
+    ).
+check_coverage_regarding_detism(Coverage, Detism) :-
+    ( Detism = erroneous_rep
+    ; Detism = failure_rep
+    ),
+    ( Coverage = coverage_known(_, 0)
+    % This probably wont occur, but might
+    ; Coverage = coverage_known_det(0)
+    ; Coverage = coverage_known_before(_)
+    ; Coverage = coverage_known_after(0)
+    % This shouldn't occur, we should infer at least coverage_known_after(0)
+    ; Coverage = coverage_unknown
+    ).
+check_coverage_regarding_detism(_Coverage, nondet_rep).
+
+    % Check that the coverages over the switch make sense.  This works only for
+    % deterministic switches.
+    % 
+    % XXX: Re-write this to work on entry counts for switches that cannot fail
+    % only.
+    %
+:- pred check_switch_coverage(detism_rep::in,
+    list(case_rep(coverage_info))::in, coverage_info::in) is semidet.
+
+check_switch_coverage(Detism, Cases, Coverage) :-
+    (
+        ( Detism = det_rep
+        ; Detism = cc_multidet_rep
+        ),
+        list.foldl(sum_switch_case_coverage, Cases, yes(0), MaybeSum),
+        (
+            MaybeSum = yes(Sum),
+            ( 
+                ( Coverage = coverage_known_det(Sum)
+                ; Coverage = coverage_known(Sum, _)
+                ; Coverage = coverage_known_before(Sum)
+                ; Coverage = coverage_known_after(_)
+                ; Coverage = coverage_unknown
+                )
+            )
+        ;
+            MaybeSum = no
+        )
+    ;
+        ( Detism = semidet_rep
+        ; Detism = multidet_rep
+        ; Detism = nondet_rep
+        ; Detism = cc_nondet_rep
+        ; Detism = failure_rep
+        ; Detism = erroneous_rep
+        )
+    ).
+
+:- pred sum_switch_case_coverage(case_rep(coverage_info)::in,
+    maybe(int)::in, maybe(int)::out) is det.
+
+sum_switch_case_coverage(case_rep(_, _, Goal), !Acc) :-
+    (
+        !.Acc = yes(Count),
+        Coverage = Goal ^ goal_annotation,
+        (
+            ( Coverage = coverage_known_det(Addend)
+            ; Coverage = coverage_known(Addend, _)
+            ; Coverage = coverage_known_before(Addend)
+            ),
+            !:Acc = yes(Count + Addend)
+        ;
+            ( Coverage = coverage_unknown
+            ; Coverage = coverage_known_after(_)
+            ),
+            !:Acc = no
+        )
+    ;
+        !.Acc = no
+    ).
+
+:- pred check_ite_coverage(coverage_info::in, coverage_info::in,
+    coverage_info::in, coverage_info::in, detism_rep::in) is semidet.
+
+check_ite_coverage(WholeCoverage, CondCoverage, ThenCoverage, ElseCoverage,
+        CondDetism) :-
+    (
+        coverage_count_before(WholeCoverage, WholeBefore),
+        coverage_count_before(CondCoverage, CondBefore)
+    ->
+        WholeBefore = CondBefore
+    ;
+        true
+    ),
+    (
+        coverage_count_after(WholeCoverage, WholeAfter),
+        coverage_count_after(ThenCoverage, ThenAfter),
+        coverage_count_after(ElseCoverage, ElseAfter)
+    ->
+        WholeAfter = ThenAfter + ElseAfter
+    ;
+        true
+    ),
+    (
+        coverage_count_after(CondCoverage, CondAfter),
+        coverage_count_before(ThenCoverage, ThenBefore)
+    ->
+        CondAfter = ThenBefore
+    ;
+        true
+    ),
+    (
+        % This can only be checked when the condition cannot succeed more than
+        % once.
+        NumSolutions = detism_get_solutions(CondDetism),
+        ( NumSolutions = at_most_one
+        ; NumSolutions = at_most_zero
+        ),
+        coverage_count_before(CondCoverage, CondBeforePrime),
+        coverage_count_after(CondCoverage, CondAfterPrime),
+        coverage_count_before(ElseCoverage, ElseBefore)  
+    ->
+        ElseBefore = CondBeforePrime - CondAfterPrime
+    ;
+        true
+    ).
+
+%----------------------------------------------------------------------------%
+%
+% Coverage information helper predicates.
+%
+
+    % Retrive the 'before' coverage count, if there is one, otherwise fail.
+    %
+:- pred coverage_count_before(coverage_info::in, int::out) is semidet.
+
+coverage_count_before(coverage_known(Count, _), Count).
+coverage_count_before(coverage_known_before(Count), Count).
+coverage_count_before(coverage_known_det(Count), Count).
+    
+    % Retreive the 'after' coverage count, or fail.
+    %
+:- pred coverage_count_after(coverage_info::in, int::out) is semidet.
+
+coverage_count_after(coverage_known(_, Count), Count).
+coverage_count_after(coverage_known_after(Count), Count).
+coverage_count_after(coverage_known_det(Count), Count).
+
+    % The coverage before a det goal should always equal the coverage after.
+:- pred propagate_det_coverage(goal_path::in, 
+    coverage_info::in, coverage_info::out) is det.
+
+propagate_det_coverage(GoalPath, !Coverage) :-
+    (
+        !.Coverage = coverage_unknown
+    ;
+        !.Coverage = coverage_known_det(_)
+    ;
+        !.Coverage = coverage_known(Before, After),
+        ( Before = After ->
+            !:Coverage = coverage_known_det(Before)
+        ;
+            error(format("Coverage before /= after for a det goal: %s, GP: %s",
+                [s(string(!.Coverage)), s(goal_path_to_string(GoalPath))]))
+        )
+    ;
+        ( !.Coverage = coverage_known_before(Coverage)
+        ; !.Coverage = coverage_known_after(Coverage)
+        ),
+        !:Coverage = coverage_known_det(Coverage)
+    ).
+
+    % If the determinism is deterministic or cc_multi use
+    % propagate_det_coverage.
+    %
+:- pred maybe_propagate_det_coverage(detism_rep::in, goal_path::in, 
+    coverage_info::in, coverage_info::out) is det.
+
+maybe_propagate_det_coverage(Detism, GoalPath, !Coverage) :-
+    (
+        ( Detism = det_rep
+        ; Detism = cc_multidet_rep ),
+        propagate_det_coverage(GoalPath, !Coverage)
+    ;
+        Detism = semidet_rep
+    ;
+        Detism = nondet_rep
+    ;
+        Detism = multidet_rep
+    ;
+        Detism = cc_nondet_rep
+    ;
+        Detism = erroneous_rep
+    ;
+        Detism = failure_rep
+    ).
+
+    % Information about the coverage before a goal only.
+    %
+:- inst coverage_before
+    --->    coverage_unknown
+    ;       coverage_known_before(ground).
+
+    % Information about the coverage after a goal only.
+    %
+:- inst coverage_after
+    --->    coverage_unknown
+    ;       coverage_known_after(ground).
+
+    % Split a coverage information structure into the coverage before and after
+    % a goal.
+    %
+:- pred split_coverage(coverage_info, coverage_info, coverage_info).
+:- mode split_coverage(in, out(coverage_before), out(coverage_after)) is det.
+:- mode split_coverage(out, in(coverage_before), in(coverage_after))
+    is cc_multi.
+
+split_coverage(Coverage, Before, After) :-
+    (
+        Coverage = coverage_unknown,
+        Before = coverage_unknown,
+        After = coverage_unknown
+    ;
+        Coverage = coverage_known_before(CB),
+        Before = coverage_known_before(CB),
+        After = coverage_unknown
+    ;
+        Coverage = coverage_known_after(CA),
+        Before = coverage_unknown,
+        After = coverage_known_after(CA)
+    ;
+        Coverage = coverage_known_det(C),
+        Before = coverage_known_before(C),
+        After = coverage_known_after(C)
+    ;
+        Coverage = coverage_known(CB, CA),
+        Before = coverage_known_before(CB),
+        After = coverage_known_after(CA)
+    ).
+
+:- func get_coverage_before(coverage_info) = coverage_info.
+:- mode get_coverage_before(in) = out(coverage_before) is det.
+
+get_coverage_before(Coverage0) = Coverage :-
+    split_coverage(Coverage0, Coverage, _).
+
+:- func get_coverage_after(coverage_info) = coverage_info.
+:- mode get_coverage_after(in) = out(coverage_after) is det.
+
+get_coverage_after(Coverage0) = Coverage :-
+    split_coverage(Coverage0, _, Coverage).
+
+    % Merge coverage information before and after a goal into coverage
+    % information for the whole goal.
+    %
+:- func merge_coverage(coverage_info, coverage_info) = coverage_info.
+:- mode merge_coverage(in(coverage_before), in(coverage_after)) = out is det.
+
+merge_coverage(CoverageBefore, CoverageAfter) = Coverage :-
+    promise_equivalent_solutions [Coverage]
+        (split_coverage(Coverage, CoverageBefore, CoverageAfter)).
+
+    % If a goal exists (G1 , G2), then the coverage information after G1 is
+    % equal to the coverage information before G2.
+    %
+:- pred goal_transition_coverage(coverage_info, coverage_info).
+:- mode goal_transition_coverage(in(coverage_after), out(coverage_before))
+    is det.
+:- mode goal_transition_coverage(out(coverage_after), in(coverage_before))
+    is det.
+
+goal_transition_coverage(CoverageAfterG1, CoverageBeforeG2) :-
+    (
+        CoverageAfterG1 = coverage_unknown,
+        CoverageBeforeG2 = coverage_unknown
+    ;
+        CoverageAfterG1 = coverage_known_after(C),
+        CoverageBeforeG2 = coverage_known_before(C)
+    ).
+
+%----------------------------------------------------------------------------%
+
+:- type solution_count
+    --->    at_most_zero
+    ;       at_most_one   % Including committed choice.
+    ;       at_most_many.
+
+:- func detism_get_solutions(detism_rep) = solution_count.
+
+detism_get_solutions(det_rep) =         at_most_one.
+detism_get_solutions(semidet_rep) =     at_most_one.
+detism_get_solutions(multidet_rep) =    at_most_many.
+detism_get_solutions(nondet_rep) =      at_most_many.
+detism_get_solutions(cc_multidet_rep) = at_most_one.
+detism_get_solutions(cc_nondet_rep) =   at_most_one.
+detism_get_solutions(erroneous_rep) =   at_most_zero.
+detism_get_solutions(failure_rep) =     at_most_zero.
+
+:- type can_fail
+    --->    can_fail
+    ;       cannot_fail.
+
+:- func detism_get_can_fail(detism_rep) = can_fail.
+
+detism_get_can_fail(det_rep) =          cannot_fail.
+detism_get_can_fail(semidet_rep) =      can_fail.
+detism_get_can_fail(multidet_rep) =     cannot_fail.
+detism_get_can_fail(nondet_rep) =       can_fail.
+detism_get_can_fail(cc_multidet_rep) =  cannot_fail.
+detism_get_can_fail(cc_nondet_rep) =    can_fail.
+detism_get_can_fail(erroneous_rep) =    cannot_fail.
+detism_get_can_fail(failure_rep) =      can_fail.
+
+%----------------------------------------------------------------------------%
+
Index: deep_profiler/report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/report.m,v
retrieving revision 1.8
diff -u -p -b -r1.8 report.m
--- deep_profiler/report.m	28 Aug 2008 10:26:14 -0000	1.8
+++ deep_profiler/report.m	17 Sep 2008 02:00:39 -0000
@@ -133,7 +133,8 @@
                 csf_kind                    :: call_site_kind_and_info(
                                                 normal_callee_id),
                 csf_summary_perf            :: perf_row_data(call_site_desc),
-                csf_sub_callees             :: list(perf_row_data(proc_desc))
+                csf_sub_callees             :: list(perf_row_data(proc_desc)),
+                csf_goal_path               :: goal_path
             ).
 
 :- type normal_callee_id
@@ -142,7 +143,21 @@
                 nci_type_subst              :: string
             ).
 
-:- type procrep_coverage_info == proc_rep.
+:- type procrep_coverage_info
+    --->    procrep_coverage_info(
+                prci_proc                   :: proc_static_ptr,
+                prci_proc_rep               :: proc_rep(coverage_info)
+            ).
+
+:- type coverage_info
+    --->    coverage_unknown
+    ;       coverage_known_det(int)
+                % Coverage is known both before and after the goal, and the
+                % coverage is the same before as it is after.
+
+    ;       coverage_known(int, int)
+    ;       coverage_known_before(int)
+    ;       coverage_known_after(int).
 
 :- type proc_callers_report
     --->    proc_callers_report(


-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 189 bytes
Desc: Digital signature
URL: <http://lists.mercurylang.org/archives/reviews/attachments/20080917/b155b35b/attachment.sig>


More information about the reviews mailing list