[m-rev.] for post-commit review: proc_callers, modules, module

Zoltan Somogyi zs at csse.unimelb.edu.au
Mon Aug 25 17:19:16 AEST 2008


For post-commit review by Paul.

Zoltan.

Move three deep profiler commands to the new framework: the one that reports
all of a procedure's callers, the one that lists all the modules, and the one
that lists all the procedures in a module.

deep_profiler/report.m:
	Add report structures for the three newly handled commands.

	Modify the perf_row_data type to allow the representation of rows
	in which the self measures are meaningful, but the self_and_desc
	measures aren't, since this is true for module summaries.

	Remove a redundant field from an existing report structure.

deep_profiler/query.m:
	Change the cmd type slightly to (a) make command names more distinct,
	(b) make it less error prone by replacing ints with purpose-specific
	wrapper types, and (c) to specify whether contour exclusion should be
	applied in the proc_callers command. Change (c) is needed because
	we contour exclusion alters the report we want to generate for the
	proc_callers command, but we don't want to pass the preferences to the
	code that computes reports.

deep_profiler/create_report.m:
	Add code for computing the new report structures.

	Conform to the change to perf_row_data.

deep_profiler/display_report.m:
	Add code for displaying the new report structures.

	Conform to the change to perf_row_data.

deep_profiler/display.m:
	Avoid the need for a number-of-columns field in most table cells
	by having separate function symbols for single- and multi-column cells.

	Add a mechanism that allows us to avoid artifically nested lists
	(horizontal list inside a vertical list).

	Add the column classes needed by the newly implemented commands.

deep_profiler/html_format.m:
	Conform to the changes in display.m and query.m.

deep_profiler/profile.m:
	We used to read in the contour exclusion file just before computing
	and displaying a HTML page whose contents required it. We cannot do
	this with the report framework (since the predicate that computes
	report structures does not take I/O states as arguments), and it is
	better to read the contour exclusion file just once anyway. This diff
	therefore adds a field to the deep structure for holding the result
	of reading in the contour exclusion file (if any).

deep_profiler/startup.m:
	Add code to fill in this new field.

	Switch to using state variables.

deep_profiler/apply_exclusion.m:
	New module. It contains some code that used to be in query.m, but
	is now also needed by create_report.m, slightly modified. The
	modifications are to add some code that used to be in the callers
	of the moved predicates. This code used to be needed only once,
	but is now needed twice (since each predicate now has two callers).

	The reason why I didn't put all this into the existing exclude.m
	is that that would have required profile.m and exclude.m to import
	each other.

deep_profiler/exclude.m:
	Change the return value to separate the case of a non-existent contour
	exclusion file from a file that exists but whose reading yields an
	error.

	Give variables better names.

deep_profiler/mdprof_cgi.m:
deep_profiler/mdprof_test.m:
	Conform to the changes in query.m.

deep_profiler/apply_exclusion.m:
	New module. It contains some code that used to be in query.m, but
	is now also needed by create_report.m, slightly modified. The
	modifications are to add some code that used to be in the callers
	of the moved predicates. This code used to be needed only once,
	but is now needed twice (since each predicate now has two callers).

	The reason why I didn't put all this into the existing exclude.m
	is that that would have required profile.m and exclude.m to import
	each other.

deep_profiler/exclude.m:
	Give variables better names.

deep_profiler/measurements.m:
	Turn a semidet predicate into a function.

cvs diff: Diffing .
Index: apply_exclusion.m
===================================================================
RCS file: apply_exclusion.m
diff -N apply_exclusion.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ apply_exclusion.m	19 Aug 2008 08:11:49 -0000
@@ -0,0 +1,181 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2008 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% File: apply_exclusion.m.
+%
+% This module contains the predicates required to implement contour exclusion.
+%
+%-----------------------------------------------------------------------------%
+
+:- module apply_exclusion.
+:- interface.
+
+:- import_module exclude.
+:- import_module measurements.
+:- import_module profile.
+
+:- import_module assoc_list.
+:- import_module list.
+:- import_module pair.
+
+:- func group_csds_by_call_site(deep, list(pair(call_site_dynamic_ptr))) =
+    assoc_list(call_site_static_ptr, list(call_site_dynamic_ptr)).
+
+:- func group_csds_by_procedure(deep, list(pair(call_site_dynamic_ptr))) =
+    assoc_list(proc_static_ptr, list(call_site_dynamic_ptr)).
+
+:- func group_csds_by_module(deep, list(pair(call_site_dynamic_ptr))) =
+    assoc_list(string, list(call_site_dynamic_ptr)).
+
+:- func group_csds_by_clique(deep, list(pair(call_site_dynamic_ptr))) =
+    assoc_list(clique_ptr, list(call_site_dynamic_ptr)).
+
+:- pred compute_parent_csd_prof_info(deep::in, proc_static_ptr::in,
+    list(call_site_dynamic_ptr)::in,
+    own_prof_info::out, inherit_prof_info::out) is det.
+
+:- func pair_self(call_site_dynamic_ptr) = pair(call_site_dynamic_ptr).
+
+:- func pair_contour(deep, exclude_file, call_site_dynamic_ptr)
+    = pair(call_site_dynamic_ptr).
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module map.
+
+group_csds_by_call_site(Deep, GroupCostCSDPtrs) = Groups :-
+    GroupMap = list.foldl(accumulate_csds_by_call_site(Deep),
+        GroupCostCSDPtrs, map.init),
+    map.to_assoc_list(GroupMap, Groups).
+
+group_csds_by_procedure(Deep, GroupCostCSDPtrs) = Groups :-
+    GroupMap = list.foldl(accumulate_csds_by_procedure(Deep),
+        GroupCostCSDPtrs, map.init),
+    map.to_assoc_list(GroupMap, Groups).
+
+group_csds_by_module(Deep, GroupCostCSDPtrs) = Groups :-
+    GroupMap = list.foldl(accumulate_csds_by_module(Deep),
+        GroupCostCSDPtrs, map.init),
+    map.to_assoc_list(GroupMap, Groups).
+
+group_csds_by_clique(Deep, GroupCostCSDPtrs) = Groups :-
+    GroupMap = list.foldl(accumulate_csds_by_clique(Deep),
+        GroupCostCSDPtrs, map.init),
+    map.to_assoc_list(GroupMap, Groups).
+
+%-----------------------------------------------------------------------------%
+
+:- func accumulate_csds_by_call_site(deep, pair(call_site_dynamic_ptr),
+    map(call_site_static_ptr, list(call_site_dynamic_ptr))) =
+    map(call_site_static_ptr, list(call_site_dynamic_ptr)).
+
+accumulate_csds_by_call_site(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
+    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
+    ( map.search(Map0, GroupCSSPtr, CostCSDPtrs0) ->
+        map.det_update(Map0, GroupCSSPtr, [CostCSDPtr | CostCSDPtrs0], Map)
+    ;
+        map.det_insert(Map0, GroupCSSPtr, [CostCSDPtr], Map)
+    ).
+
+:- func accumulate_csds_by_procedure(deep, pair(call_site_dynamic_ptr),
+    map(proc_static_ptr, list(call_site_dynamic_ptr))) =
+    map(proc_static_ptr, list(call_site_dynamic_ptr)).
+
+accumulate_csds_by_procedure(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
+    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
+    deep_lookup_call_site_statics(Deep, GroupCSSPtr, GroupCSS),
+    GroupPSPtr = GroupCSS ^ css_container,
+    ( map.search(Map0, GroupPSPtr, CostCSDPtrs0) ->
+        map.det_update(Map0, GroupPSPtr, [CostCSDPtr | CostCSDPtrs0], Map)
+    ;
+        map.det_insert(Map0, GroupPSPtr, [CostCSDPtr], Map)
+    ).
+
+:- func accumulate_csds_by_module(deep, pair(call_site_dynamic_ptr),
+    map(string, list(call_site_dynamic_ptr))) =
+    map(string, list(call_site_dynamic_ptr)).
+
+accumulate_csds_by_module(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
+    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
+    deep_lookup_call_site_statics(Deep, GroupCSSPtr, GroupCSS),
+    GroupPSPtr = GroupCSS ^ css_container,
+    deep_lookup_proc_statics(Deep, GroupPSPtr, GroupPS),
+    GroupModuleName = GroupPS ^ ps_decl_module,
+    ( map.search(Map0, GroupModuleName, CostCSDPtrs0) ->
+        map.det_update(Map0, GroupModuleName, [CostCSDPtr | CostCSDPtrs0], Map)
+    ;
+        map.det_insert(Map0, GroupModuleName, [CostCSDPtr], Map)
+    ).
+
+:- func accumulate_csds_by_clique(deep, pair(call_site_dynamic_ptr),
+    map(clique_ptr, list(call_site_dynamic_ptr))) =
+    map(clique_ptr, list(call_site_dynamic_ptr)).
+
+accumulate_csds_by_clique(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
+    deep_lookup_call_site_dynamics(Deep, GroupCSDPtr, GroupCSD),
+    CallerPDPtr = GroupCSD ^ csd_caller,
+    deep_lookup_clique_index(Deep, CallerPDPtr, CliquePtr),
+    ( map.search(Map0, CliquePtr, CostCSDPtrs0) ->
+        map.det_update(Map0, CliquePtr, [CostCSDPtr | CostCSDPtrs0], Map)
+    ;
+        map.det_insert(Map0, CliquePtr, [CostCSDPtr], Map)
+    ).
+
+%-----------------------------------------------------------------------------%
+
+compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc) :-
+    list.foldl2(accumulate_parent_csd_prof_info(Deep, CalleePSPtr), CSDPtrs,
+        zero_own_prof_info, Own, zero_inherit_prof_info, Desc).
+
+:- pred accumulate_parent_csd_prof_info(deep::in, proc_static_ptr::in,
+    call_site_dynamic_ptr::in,
+    own_prof_info::in, own_prof_info::out,
+    inherit_prof_info::in, inherit_prof_info::out) is det.
+
+accumulate_parent_csd_prof_info(Deep, CallerPSPtr, CSDPtr,
+        Own0, Own, Desc0, Desc) :-
+    deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
+    ( CSD ^ csd_callee = CSD ^ csd_caller ->
+        % We want to sum only cross-clique callers.
+        Own = Own0,
+        Desc = Desc0
+    ;
+        deep_lookup_csd_own(Deep, CSDPtr, CSDOwn),
+        deep_lookup_csd_desc(Deep, CSDPtr, CSDDesc),
+        add_own_to_own(Own0, CSDOwn) = Own,
+        add_inherit_to_inherit(Desc0, CSDDesc) = Desc1,
+
+        deep_lookup_clique_index(Deep, CSD ^ csd_callee, CalleeCliquePtr),
+        deep_lookup_clique_members(Deep, CalleeCliquePtr, CalleeCliquePDPtrs),
+        list.foldl(compensate_using_comp_table(Deep, CallerPSPtr),
+            CalleeCliquePDPtrs, Desc1, Desc)
+    ).
+
+:- pred compensate_using_comp_table(deep::in, proc_static_ptr::in,
+    proc_dynamic_ptr::in, inherit_prof_info::in, inherit_prof_info::out)
+    is det.
+
+compensate_using_comp_table(Deep, CallerPSPtr, PDPtr, Desc0, Desc) :-
+    deep_lookup_pd_comp_table(Deep, PDPtr, CompTableArray),
+    ( map.search(CompTableArray, CallerPSPtr, InnerTotal) ->
+        Desc = subtract_inherit_from_inherit(InnerTotal, Desc0)
+    ;
+        Desc = Desc0
+    ).
+
+%-----------------------------------------------------------------------------%
+
+pair_self(CSDPtr) = CSDPtr - CSDPtr.
+
+pair_contour(Deep, ExcludeSpec, CSDPtr) =
+    apply_contour_exclusion(Deep, ExcludeSpec, CSDPtr) - CSDPtr.
+
+%-----------------------------------------------------------------------------%
+
Index: create_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/create_report.m,v
retrieving revision 1.6
diff -u -b -r1.6 create_report.m
--- create_report.m	18 Aug 2008 02:14:51 -0000	1.6
+++ create_report.m	25 Aug 2008 06:06:01 -0000
@@ -28,6 +28,7 @@
 
 :- implementation.
 
+:- import_module apply_exclusion.
 :- import_module measurement_units.
 :- import_module measurements.
 :- import_module top_procs.
@@ -52,13 +53,13 @@
         Cmd = deep_cmd_quit,
         Msg = string.format("Shutting down deep profile server for %s.",
             [s(Deep ^ data_file_name)]),
-        MessageInfo = message_report(Msg),
-        Report = report_message(MessageInfo)
+        MessageReport = message_report(Msg),
+        Report = report_message(MessageReport)
     ;
         Cmd = deep_cmd_timeout(Timeout),
         Msg = string.format("Timeout set to %d minutes.", [i(Timeout)]),
-        MessageInfo = message_report(Msg),
-        Report = report_message(MessageInfo)
+        MessageReport = message_report(Msg),
+        Report = report_message(MessageReport)
     ;
         Cmd = deep_cmd_menu,
         Deep ^ profile_stats = profile_stats(ProgramName, 
@@ -66,54 +67,145 @@
             QuantaPerSec, InstrumentationQuanta, UserQuanta, NumCallseqs,
             _, _),
         NumCliques = array.max(Deep ^ clique_members),
-        MenuInfo = menu_report(ProgramName, QuantaPerSec,
+        MenuReport = menu_report(ProgramName, QuantaPerSec,
             UserQuanta, InstrumentationQuanta,
             NumCallseqs, NumCSD, NumCSS, NumPD, NumPS, NumCliques),
-        Report = report_menu(ok(MenuInfo))
+        Report = report_menu(ok(MenuReport))
+    ;
+        Cmd = deep_cmd_program_modules,
+        create_program_modules_report(Deep, MaybeProgramModulesReport),
+        Report = report_program_modules(MaybeProgramModulesReport)
+    ;
+        Cmd = deep_cmd_module(ModuleName),
+        create_module_report(Deep, ModuleName, MaybeModuleReport),
+        Report = report_module(MaybeModuleReport)
     ;
         Cmd = deep_cmd_top_procs(Limit, CostKind, InclDesc, Scope),
         create_top_procs_report(Deep, Limit, CostKind, InclDesc, Scope,
-            MaybeTopProcsInfo),
-        Report = report_top_procs(MaybeTopProcsInfo)
+            MaybeTopProcsReport),
+        Report = report_top_procs(MaybeTopProcsReport)
     ;
-        Cmd = deep_cmd_proc(PSI),
-        create_proc_report(Deep, PSI, MaybeProcReport),
+        Cmd = deep_cmd_proc(PSPtr),
+        create_proc_report(Deep, PSPtr, MaybeProcReport),
         Report = report_proc(MaybeProcReport)
     ;
-        Cmd = deep_cmd_proc_static(PSI),
-        create_proc_static_dump_report(Deep, PSI, MaybeProcStaticDumpInfo),
-        Report = report_proc_static_dump(MaybeProcStaticDumpInfo)
-    ;
-        Cmd = deep_cmd_proc_dynamic(PDI),
-        create_proc_dynamic_dump_report(Deep, PDI, MaybeProcDynamicDumpInfo),
-        Report = report_proc_dynamic_dump(MaybeProcDynamicDumpInfo)
-    ;
-        Cmd = deep_cmd_call_site_static(CSSI),
-        create_call_site_static_dump_report(Deep, CSSI,
-            MaybeCallSiteStaticDumpInfo),
-        Report = report_call_site_static_dump(MaybeCallSiteStaticDumpInfo)
-    ;
-        Cmd = deep_cmd_call_site_dynamic(CSDI),
-        create_call_site_dynamic_dump_report(Deep, CSDI,
-            MaybeCallSiteStaticDumpInfo),
-        Report = report_call_site_dynamic_dump(MaybeCallSiteStaticDumpInfo)
+        Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum, Contour),
+        create_proc_callers_report(Deep, PSPtr, CallerGroups, BunchNum,
+            Contour, MaybeProcCallersReport),
+        Report = report_proc_callers(MaybeProcCallersReport)
+    ;
+        Cmd = deep_cmd_dump_proc_static(PSPtr),
+        create_proc_static_dump_report(Deep, PSPtr, MaybeProcStaticDump),
+        Report = report_proc_static_dump(MaybeProcStaticDump)
+    ;
+        Cmd = deep_cmd_dump_proc_dynamic(PDPtr),
+        create_proc_dynamic_dump_report(Deep, PDPtr, MaybeProcDynamicDump),
+        Report = report_proc_dynamic_dump(MaybeProcDynamicDump)
+    ;
+        Cmd = deep_cmd_dump_call_site_static(CSSPtr),
+        create_call_site_static_dump_report(Deep, CSSPtr,
+            MaybeCallSiteStaticDump),
+        Report = report_call_site_static_dump(MaybeCallSiteStaticDump)
+    ;
+        Cmd = deep_cmd_dump_call_site_dynamic(CSDPtr),
+        create_call_site_dynamic_dump_report(Deep, CSDPtr,
+            MaybeCallSiteStaticDump),
+        Report = report_call_site_dynamic_dump(MaybeCallSiteStaticDump)
     ;
         Cmd = deep_cmd_restart,
         error("create_report/3", "unexpected restart command")
     ;
         ( Cmd = deep_cmd_root(_)
         ; Cmd = deep_cmd_clique(_)
-        ; Cmd = deep_cmd_proc_callers(_, _, _)
-        ; Cmd = deep_cmd_modules
-        ; Cmd = deep_cmd_module(_)
-        ; Cmd = deep_cmd_raw_clique(_)
+        ; Cmd = deep_cmd_dump_clique(_)
         ),
         error("create_report/3", "Command not supported: " ++ string(Cmd))
     ).
 
 %-----------------------------------------------------------------------------%
 %
-% Code to build top_procs report.
+% Code to build a program_modules report.
+%
+
+    % Create a modules report, from the given data with the specified
+    % parameters.
+    %
+:- pred create_program_modules_report(deep::in,
+    maybe_error(program_modules_report)::out) is det.
+
+create_program_modules_report(Deep, MaybeProgramModulesReport) :-
+    map.to_assoc_list(Deep ^ module_data, ModulePairs0),
+    list.filter(not_mercury_runtime, ModulePairs0, ModulePairs),
+    ModuleRowDatas = list.map(module_pair_to_row_data(Deep), ModulePairs),
+    ProgramModulesReport = program_modules_report(ModuleRowDatas),
+    MaybeProgramModulesReport = ok(ProgramModulesReport).
+
+:- pred not_mercury_runtime(pair(string, module_data)::in) is semidet.
+
+not_mercury_runtime(ModuleName - _) :-
+    ModuleName \= "Mercury runtime".
+
+:- func module_pair_to_row_data(deep, pair(string, module_data))
+    = perf_row_data(module_active).
+
+module_pair_to_row_data(Deep, ModuleName - ModuleData) = ModuleRowData :-
+    Own = ModuleData ^ module_own,
+    IsActive = compute_is_active(Own),
+    (
+        IsActive = is_active,
+        ModuleIsActive = module_is_active
+    ;
+        IsActive = is_not_active,
+        ModuleIsActive = module_is_not_active
+    ),
+    ModuleActive = module_active(ModuleName, ModuleIsActive),
+    own_and_maybe_inherit_to_perf_row_data(Deep, ModuleActive, Own, no,
+        ModuleRowData).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to build a module report.
+%
+
+    % Create a module report, from the given data with the specified
+    % parameters.
+    %
+:- pred create_module_report(deep::in, string::in,
+    maybe_error(module_report)::out) is det.
+
+create_module_report(Deep, ModuleName, MaybeModuleReport) :-
+    ( map.search(Deep ^ module_data, ModuleName, ModuleData) ->
+        PSPtrs = ModuleData ^ module_procs, 
+        ProcRowDatas = list.map(proc_to_active_row_data(Deep), PSPtrs),
+        ModuleReport = module_report(ModuleName, ProcRowDatas),
+        MaybeModuleReport = ok(ModuleReport)
+    ;
+        Msg = string.format("There is no module named `%s'.\n",
+            [s(ModuleName)]),
+        MaybeModuleReport = error(Msg)
+    ).
+
+:- func proc_to_active_row_data(deep, proc_static_ptr)
+    = perf_row_data(proc_active).
+
+proc_to_active_row_data(Deep, PSPtr) = ProcRowData :-
+    deep_lookup_ps_own(Deep, PSPtr, Own),
+    deep_lookup_ps_desc(Deep, PSPtr, Desc),
+    IsActive = compute_is_active(Own),
+    (
+        IsActive = is_active,
+        ProcIsActive = proc_is_active
+    ;
+        IsActive = is_not_active,
+        ProcIsActive = proc_is_not_active
+    ),
+    ProcDesc = describe_proc(Deep, PSPtr),
+    ProcActive = proc_active(ProcDesc, ProcIsActive),
+    own_and_inherit_to_perf_row_data(Deep, ProcActive, Own, Desc, ProcRowData).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to build a top_procs report.
 %
 
     % Create a top procs report, from the given data with the specified
@@ -148,21 +240,20 @@
     ;
         MaybeTopPSIs = ok(TopPSIs),
         Ordering = report_ordering(Limit, CostKind, InclDesc, Scope),
-        list.map(psi_to_perf_row_data(Deep), TopPSIs, RowData),
-        TopProcsReport = top_procs_report(Ordering, RowData),
+        list.map(psi_to_perf_row_data(Deep), TopPSIs, ProcRowDatas),
+        TopProcsReport = top_procs_report(Ordering, ProcRowDatas),
         MaybeTopProcsReport = ok(TopProcsReport)
     ).
 
 %-----------------------------------------------------------------------------%
 %
-% Code to build proc report.
+% Code to build a proc report.
 %
 
-:- pred create_proc_report(deep::in, int::in, maybe_error(proc_report)::out)
-    is det.
+:- pred create_proc_report(deep::in, proc_static_ptr::in,
+    maybe_error(proc_report)::out) is det.
 
-create_proc_report(Deep, PSI, MaybeProcReport) :-
-    PSPtr = proc_static_ptr(PSI),
+create_proc_report(Deep, PSPtr, MaybeProcReport) :-
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         ProcDesc = describe_proc(Deep, PSPtr),
         deep_lookup_ps_own(Deep, PSPtr, Own),
@@ -176,7 +267,7 @@
         ProcCallSiteSummaryRowDatas = list.map(create_call_site_summary(Deep),
             CallSites),
 
-        ProcReport = proc_report(PSPtr, ProcSummaryRowData,
+        ProcReport = proc_report(ProcSummaryRowData,
             ProcCallSiteSummaryRowDatas),
         MaybeProcReport = ok(ProcReport)
     ;
@@ -293,14 +384,142 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Code to build a proc_callers report.
+%
+
+:- pred create_proc_callers_report(deep::in, proc_static_ptr::in,
+    caller_groups::in, int::in, contour_exclusion::in,
+    maybe_error(proc_callers_report)::out) is det.
+
+create_proc_callers_report(Deep, PSPtr, CallerGroups, BunchNum, Contour,
+        MaybeProcCallersReport) :-
+    ( valid_proc_static_ptr(Deep, PSPtr) ->
+        ProcDesc = describe_proc(Deep, PSPtr),
+
+        deep_lookup_proc_callers(Deep, PSPtr, CallerCSDPtrs),
+        MaybeMaybeExcludeFile = Deep ^ exclude_contour_file,
+        (
+            Contour = do_not_apply_contour_exclusion,
+            CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs),
+            Messages = []
+        ;
+            Contour = apply_contour_exclusion,
+            (
+                MaybeMaybeExcludeFile = no,
+                % There is no contour exclusion file, so do the same as for
+                % do_not_apply_contour_exclusion, but add a message to the
+                % report.
+                CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs),
+                Message = "There is no readable contour exclusion file.",
+                Messages = [Message]
+            ;
+                MaybeMaybeExcludeFile = yes(MaybeExcludeFile),
+                (
+                    MaybeExcludeFile = ok(ExcludeSpec),
+                    CallerCSDPtrPairs = list.map(
+                        pair_contour(Deep, ExcludeSpec), CallerCSDPtrs),
+                    Messages = []
+                ;
+                    MaybeExcludeFile = error(ErrorMsg),
+                    CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs),
+                    MessagePrefix = "The contour exclusion file has an error:",
+                    Messages = [MessagePrefix, ErrorMsg]
+                )
+            )
+        ),
+        (
+            CallerGroups = group_by_call_site,
+            CallSiteCallerGroups = group_csds_by_call_site(Deep,
+                CallerCSDPtrPairs),
+            ProcCallerCallSites = list.map(
+                create_proc_caller_call_sites(Deep, PSPtr),
+                CallSiteCallerGroups),
+            Callers = proc_caller_call_sites(ProcCallerCallSites)
+        ;
+            CallerGroups = group_by_proc,
+            ProcCallerGroups = group_csds_by_procedure(Deep,
+                CallerCSDPtrPairs),
+            ProcCallerProcs = list.map(
+                create_proc_caller_procedures(Deep, PSPtr),
+                ProcCallerGroups),
+            Callers = proc_caller_procedures(ProcCallerProcs)
+        ;
+            CallerGroups = group_by_module,
+            ModuleCallerGroups = group_csds_by_module(Deep,
+                CallerCSDPtrPairs),
+            ProcCallerModules = list.map(
+                create_proc_caller_modules(Deep, PSPtr),
+                ModuleCallerGroups),
+            Callers = proc_caller_modules(ProcCallerModules)
+        ;
+            CallerGroups = group_by_clique,
+            CliqueCallerGroups = group_csds_by_clique(Deep,
+                CallerCSDPtrPairs),
+            ProcCallerCliques = list.map(
+                create_proc_caller_cliques(Deep, PSPtr),
+                CliqueCallerGroups),
+            Callers = proc_caller_cliques(ProcCallerCliques)
+        ),
+
+        ProcCallersReport = proc_callers_report(ProcDesc, Callers,
+            BunchNum, Contour, Messages),
+        MaybeProcCallersReport = ok(ProcCallersReport)
+    ;
+        MaybeProcCallersReport = error("invalid proc_static index")
+    ).
+
+:- func create_proc_caller_call_sites(deep, proc_static_ptr,
+    pair(call_site_static_ptr, list(call_site_dynamic_ptr)))
+    = perf_row_data(call_site_desc).
+
+create_proc_caller_call_sites(Deep, CalleePSPtr, CSSPtr - CSDPtrs) =
+        PerfRowData :-
+    CallSiteDesc = describe_call_site(Deep, CSSPtr),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
+    own_and_inherit_to_perf_row_data(Deep, CallSiteDesc, Own, Desc,
+        PerfRowData).
+
+:- func create_proc_caller_procedures(deep, proc_static_ptr,
+    pair(proc_static_ptr, list(call_site_dynamic_ptr)))
+    = perf_row_data(proc_desc).
+
+create_proc_caller_procedures(Deep, CalleePSPtr, PSSPtr - CSDPtrs) =
+        PerfRowData :-
+    ProcDesc = describe_proc(Deep, PSSPtr),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
+    own_and_inherit_to_perf_row_data(Deep, ProcDesc, Own, Desc,
+        PerfRowData).
+
+:- func create_proc_caller_modules(deep, proc_static_ptr,
+    pair(string, list(call_site_dynamic_ptr)))
+    = perf_row_data(string).
+
+create_proc_caller_modules(Deep, CalleePSPtr, ModuleName - CSDPtrs) =
+        PerfRowData :-
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
+    own_and_inherit_to_perf_row_data(Deep, ModuleName, Own, Desc,
+        PerfRowData).
+
+:- func create_proc_caller_cliques(deep, proc_static_ptr,
+    pair(clique_ptr, list(call_site_dynamic_ptr)))
+    = perf_row_data(clique_desc).
+
+create_proc_caller_cliques(Deep, CalleePSPtr, CliquePtr - CSDPtrs) =
+        PerfRowData :-
+    CliqueDesc = describe_clique(Deep, CliquePtr),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
+    own_and_inherit_to_perf_row_data(Deep, CliqueDesc, Own, Desc,
+        PerfRowData).
+
+%-----------------------------------------------------------------------------%
+%
 % Code to build the dump reports.
 %
 
-:- pred create_proc_static_dump_report(deep::in, int::in,
+:- pred create_proc_static_dump_report(deep::in, proc_static_ptr::in,
     maybe_error(proc_static_dump_info)::out) is det.
 
-create_proc_static_dump_report(Deep, PSI, MaybeProcStaticDumpInfo) :-
-    PSPtr = proc_static_ptr(PSI),
+create_proc_static_dump_report(Deep, PSPtr, MaybeProcStaticDumpInfo) :-
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         deep_lookup_proc_statics(Deep, PSPtr, PS),
         % Should we dump some other fields?
@@ -315,11 +534,10 @@
         MaybeProcStaticDumpInfo = error("invalid proc_static index")
     ).
 
-:- pred create_proc_dynamic_dump_report(deep::in, int::in,
+:- pred create_proc_dynamic_dump_report(deep::in, proc_dynamic_ptr::in,
     maybe_error(proc_dynamic_dump_info)::out) is det.
 
-create_proc_dynamic_dump_report(Deep, PDI, MaybeProcDynamicDumpInfo) :-
-    PDPtr = proc_dynamic_ptr(PDI),
+create_proc_dynamic_dump_report(Deep, PDPtr, MaybeProcDynamicDumpInfo) :-
     ( valid_proc_dynamic_ptr(Deep, PDPtr) ->
         deep_lookup_proc_dynamics(Deep, PDPtr, PD),
         PD = proc_dynamic(PSPtr, CallSiteArray),
@@ -334,12 +552,11 @@
         MaybeProcDynamicDumpInfo = error("invalid proc_dynamic index")
     ).
 
-:- pred create_call_site_static_dump_report(deep::in, int::in,
+:- pred create_call_site_static_dump_report(deep::in, call_site_static_ptr::in,
     maybe_error(call_site_static_dump_info)::out) is det.
 
-create_call_site_static_dump_report(Deep, CSSI,
+create_call_site_static_dump_report(Deep, CSSPtr,
         MaybeCallSiteStaticDumpInfo) :-
-    CSSPtr = call_site_static_ptr(CSSI),
     ( valid_call_site_static_ptr(Deep, CSSPtr) ->
         deep_lookup_call_site_statics(Deep, CSSPtr, CSS),
         CSS = call_site_static(ContainingPSPtr, SlotNumber, CallSiteKind,
@@ -351,12 +568,12 @@
         MaybeCallSiteStaticDumpInfo = error("invalid call_site_static index")
     ).
 
-:- pred create_call_site_dynamic_dump_report(deep::in, int::in,
+:- pred create_call_site_dynamic_dump_report(deep::in,
+    call_site_dynamic_ptr::in,
     maybe_error(call_site_dynamic_dump_info)::out) is det.
 
-create_call_site_dynamic_dump_report(Deep, CSDI,
+create_call_site_dynamic_dump_report(Deep, CSDPtr,
         MaybeCallSiteDynamicDumpInfo) :-
-    CSDPtr = call_site_dynamic_ptr(CSDI),
     ( valid_call_site_dynamic_ptr(Deep, CSDPtr) ->
         deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
         CSD = call_site_dynamic(CallerPSPtr, CalleePSDPtr, Own),
@@ -391,6 +608,15 @@
     own_prof_info::in, inherit_prof_info::in, perf_row_data(T)::out) is det.
 
 own_and_inherit_to_perf_row_data(Deep, Subject, Own, Desc, RowData) :-
+    own_and_maybe_inherit_to_perf_row_data(Deep, Subject, Own, yes(Desc),
+        RowData).
+
+:- pred own_and_maybe_inherit_to_perf_row_data(deep::in, T::in,
+    own_prof_info::in, maybe(inherit_prof_info)::in, perf_row_data(T)::out)
+    is det.
+
+own_and_maybe_inherit_to_perf_row_data(Deep, Subject, Own, MaybeDesc,
+        RowData) :-
     % Look up global parameters and totals.
     ProfileStats = Deep ^ profile_stats,
     TicksPerSec = ProfileStats ^ ticks_per_sec,
@@ -415,60 +641,66 @@
     SelfTimePercent = percent_from_ints(SelfTicks, RootQuanta),
     SelfTimePerCall = time_percall(SelfTime, Calls),
 
-    % Self + descendants times.
-    TotalTicks = SelfTicks + inherit_quanta(Desc),
-    TotalTime = ticks_to_time(TotalTicks, TicksPerSec),
-    TotalTimePercent = percent_from_ints(TotalTicks, RootQuanta),
-    TotalTimePerCall = time_percall(TotalTime, Calls),
-
     % Self call sequence counts.
     SelfCallseqs = callseqs(Own),
     SelfCallseqsPercent = percent_from_ints(SelfCallseqs, RootCallseqs),
     SelfCallseqsPerCall = int_per_call(SelfCallseqs, Calls),
 
-    % Self + descendants call sequence counts.
-    TotalCallseqs = callseqs(Own) + inherit_callseqs(Desc),
-    TotalCallseqsPercent = percent_from_ints(TotalCallseqs, RootCallseqs),
-    TotalCallseqsPerCall = int_per_call(TotalCallseqs, Calls),
-
     % Self memory allocations.
     SelfAllocs = allocs(Own),
     SelfAllocsPercent = percent_from_ints(SelfAllocs, RootAllocs),
     SelfAllocsPerCall = int_per_call(SelfAllocs, Calls),
 
-    % Self + descendants memory allocations.
-    TotalAllocs = SelfAllocs + inherit_allocs(Desc),
-    TotalAllocsPercent = percent_from_ints(TotalAllocs, RootAllocs),
-    TotalAllocsPerCall = int_per_call(TotalAllocs, Calls),
-
     % Self memory words.
     SelfWords = words(Own),
     SelfMemory = memory_words(SelfWords, WordSize),
     SelfMemoryPercent = percent_from_ints(SelfWords, RootWords),
     SelfMemoryPerCall = SelfMemory / Calls,
 
+    SelfPerf = inheritable_perf(
+        SelfTicks, SelfTime, SelfTimePercent, SelfTimePerCall,
+        SelfCallseqs, SelfCallseqsPercent, SelfCallseqsPerCall,
+        SelfAllocs, SelfAllocsPercent, SelfAllocsPerCall,
+        SelfMemory, SelfMemoryPercent, SelfMemoryPerCall),
+
+    (
+        MaybeDesc = no,
+        MaybeTotalPerf = no
+    ;
+        MaybeDesc = yes(Desc),
+
+        % Self + descendants times.
+        TotalTicks = SelfTicks + inherit_quanta(Desc),
+        TotalTime = ticks_to_time(TotalTicks, TicksPerSec),
+        TotalTimePercent = percent_from_ints(TotalTicks, RootQuanta),
+        TotalTimePerCall = time_percall(TotalTime, Calls),
+
+        % Self + descendants call sequence counts.
+        TotalCallseqs = callseqs(Own) + inherit_callseqs(Desc),
+        TotalCallseqsPercent = percent_from_ints(TotalCallseqs, RootCallseqs),
+        TotalCallseqsPerCall = int_per_call(TotalCallseqs, Calls),
+
+        % Self + descendants memory allocations.
+        TotalAllocs = SelfAllocs + inherit_allocs(Desc),
+        TotalAllocsPercent = percent_from_ints(TotalAllocs, RootAllocs),
+        TotalAllocsPerCall = int_per_call(TotalAllocs, Calls),
+
     % Self + descendants memory words.
     TotalWords = SelfWords + inherit_words(Desc),
     TotalMemory = memory_words(TotalWords, WordSize),
     TotalMemoryPercent = percent_from_ints(TotalWords, RootWords),
     TotalMemoryPerCall = TotalMemory / Calls,
 
-    RowData = perf_row_data(Subject,
-        Calls, Exits, Fails, Redos, Excps,
-
-        SelfTicks, SelfTime, SelfTimePercent, SelfTimePerCall,
+        TotalPerf = inheritable_perf(
         TotalTicks, TotalTime, TotalTimePercent, TotalTimePerCall,
-
-        SelfCallseqs, SelfCallseqsPercent, SelfCallseqsPerCall,
         TotalCallseqs, TotalCallseqsPercent, TotalCallseqsPerCall,
-
-        SelfAllocs, SelfAllocsPercent, SelfAllocsPerCall,
         TotalAllocs, TotalAllocsPercent, TotalAllocsPerCall,
+            TotalMemory, TotalMemoryPercent, TotalMemoryPerCall),
+        MaybeTotalPerf = yes(TotalPerf)
+    ),
 
-        WordSize,
-        SelfMemory, SelfMemoryPercent, SelfMemoryPerCall,
-        TotalMemory, TotalMemoryPercent, TotalMemoryPerCall
-    ).
+    RowData = perf_row_data(Subject, Calls, Exits, Fails, Redos, Excps,
+        WordSize, SelfPerf, MaybeTotalPerf).
 
 %-----------------------------------------------------------------------------%
 
@@ -497,7 +729,7 @@
 
 %-----------------------------------------------------------------------------%
 
-    % Create a report_proc structure for a given proc static pointer.
+    % Create a proc_desc structure for a given proc static pointer.
     %
 :- func describe_proc(deep, proc_static_ptr) = proc_desc.
 
@@ -514,7 +746,7 @@
     ),
     ProcDesc = proc_desc(PSPtr, FileName, LineNumber, RefinedName).
 
-    % Create a report_call_site structure for a given call site static pointer.
+    % Create a call_site_desc structure for a given call site static pointer.
     %
 :- func describe_call_site(deep, call_site_static_ptr) = call_site_desc.
 
@@ -537,6 +769,25 @@
     CallSiteDesc = call_site_desc(CSSPtr, ContainingPSPtr,
         FileName, LineNumber, RefinedName, SlotNumber, GoalPath).
 
+    % Create a clique_desc structure for a given clique.
+    %
+:- func describe_clique(deep, clique_ptr) = clique_desc.
+
+describe_clique(Deep, CliquePtr) = CliqueDesc :-
+    ( valid_clique_ptr(Deep, CliquePtr) ->
+        deep_lookup_clique_members(Deep, CliquePtr, MemberPDPtrs),
+        ProcDescs = list.map(describe_clique_member(Deep), MemberPDPtrs),
+        CliqueDesc = clique_desc(CliquePtr, ProcDescs)
+    ;
+        error("describe_clique", "invalid clique_ptr")
+    ).
+
+:- func describe_clique_member(deep, proc_dynamic_ptr) = proc_desc.
+
+describe_clique_member(Deep, PDPtr) = ProcDesc :-
+    deep_lookup_proc_dynamics(Deep, PDPtr, PD),
+    ProcDesc = describe_proc(Deep, PD ^ pd_proc_static).
+
 %-----------------------------------------------------------------------------%
 %
 % Code shared across entire module.
Index: display.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/display.m,v
retrieving revision 1.7
diff -u -b -r1.7 display.m
--- display.m	18 Aug 2008 02:14:51 -0000	1.7
+++ display.m	25 Aug 2008 07:16:42 -0000
@@ -34,7 +34,7 @@
 
 :- type display_item
     --->    display_heading(
-                % A string to be displayed as a HTML header.
+                % A string to be displayed as a header.
                 string
             )
     ;       display_text(
@@ -48,7 +48,7 @@
     ;       display_pseudo_link(
                 % A string to be formatted exactly as if it were a link,
                 % without it actually being a link. Used for situations
-                % when a link would lead back to this page.
+                % when a link would lead back to the same page.
                 pseudo_link
             )
     ;       display_list(
@@ -103,6 +103,9 @@
                 % about how to paint this column.
                 thg_class       :: table_column_class,
 
+                % This field controls the mechanism that use to shade every
+                % second column in the table, which should make it easier for
+                % people to associate table entries with their columns.
                 thg_colour      :: table_column_colour
             ).
 
@@ -131,8 +134,11 @@
 
 :- type table_cell
     --->    table_cell(
-                tc_text         :: table_data,
-                tc_span         :: int
+                tc_text         :: table_data
+            )
+    ;       table_multi_cell(
+                tcs_text        :: table_data,
+                tcs_span        :: int
             )
     ;       table_empty_cell.
 
@@ -149,7 +155,9 @@
 :- type table_column_class
     --->    table_column_class_allocations
     ;       table_column_class_callseqs
+    ;       table_column_class_clique
     ;       table_column_class_memory
+    ;       table_column_class_module_name
     ;       table_column_class_no_class
     ;       table_column_class_number
     ;       table_column_class_ordinal_rank
@@ -187,7 +195,8 @@
 :- type list_class
     --->    list_class_vertical_no_bullets
     ;       list_class_vertical_bullets
-    ;       list_class_horizontal.
+    ;       list_class_horizontal
+    ;       list_class_horizontal_except_title.
 
 %-----------------------------------------------------------------------------%
 %
Index: display_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/display_report.m,v
retrieving revision 1.9
diff -u -b -r1.9 display_report.m
--- display_report.m	18 Aug 2008 02:14:51 -0000	1.9
+++ display_report.m	25 Aug 2008 07:06:09 -0000
@@ -66,6 +66,25 @@
             Display = display(no, [display_heading(Msg)])
         )
     ;
+        Report = report_program_modules(MaybeProgramModulesReport),
+        (
+            MaybeProgramModulesReport = ok(ProgramModulesReport),
+            display_report_program_modules(Prefs, ProgramModulesReport,
+                Display)
+        ;
+            MaybeProgramModulesReport = error(Msg),
+            Display = display(no, [display_heading(Msg)])
+        )
+    ;
+        Report = report_module(MaybeModuleReport),
+        (
+            MaybeModuleReport = ok(ModuleReport),
+            display_report_module(Prefs, ModuleReport, Display)
+        ;
+            MaybeModuleReport = error(Msg),
+            Display = display(no, [display_heading(Msg)])
+        )
+    ;
         Report = report_top_procs(MaybeTopProcsReport),
         (
             MaybeTopProcsReport = ok(TopProcsReport),
@@ -84,6 +103,15 @@
             Display = display(no, [display_heading(Msg)])
         )
     ;
+        Report = report_proc_callers(MaybeProcCallersReport),
+        (
+            MaybeProcCallersReport = ok(ProcCallersReport),
+            display_report_proc_callers(Prefs, ProcCallersReport, Display)
+        ;
+            MaybeProcCallersReport = error(Msg),
+            Display = display(no, [display_heading(Msg)])
+        )
+    ;
         Report = report_proc_static_dump(MaybeProcStaticDumpInfo),
         (
             MaybeProcStaticDumpInfo = ok(ProcStaticDumpInfo),
@@ -144,7 +172,7 @@
             "Exploring the call graph, starting at the root."),
          (deep_cmd_root(yes(90)) -
             "Exploring the call graph, starting at the action."),
-         (deep_cmd_modules -
+         (deep_cmd_program_modules -
             "Exploring the program module by module.")],
 
     (
@@ -228,7 +256,7 @@
         ("Quanta in user code:"         - td_i(UserQuanta)),
         ("Quanta in instrumentation:"   - td_i(InstQuanta)),
         ("Call sequence numbers:"       - td_i(NumCallseqs)),
-        ("CallSiteDyanic structures:"   - td_i(NumCSD)),
+        ("CallSiteDynamic structures:"  - td_i(NumCSD)),
         ("ProcDynamic structures:"      - td_i(NumPD)),
         ("CallSiteStatic structures:"   - td_i(NumCSS)),
         ("ProcStatic structures:"       - td_i(NumPS)),
@@ -246,6 +274,157 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Code to display a program_modules report.
+%
+
+    % Create a display_report structure for a program_modules report.
+    %
+:- pred display_report_program_modules(preferences::in,
+    program_modules_report::in, display::out) is det.
+
+display_report_program_modules(Prefs, ProgramModulesReport, Display) :-
+    ProgramModulesReport = program_modules_report(ModuleRowDatas0),
+    Cmd = deep_cmd_program_modules,
+    Title = "The modules of the program:",
+
+    ShowInactiveModules = Prefs ^ pref_inactive ^ inactive_modules,
+    (
+        ShowInactiveModules = inactive_show,
+        ModuleRowDatas1 = ModuleRowDatas0
+    ;
+        ShowInactiveModules = inactive_hide,
+        list.filter(active_module, ModuleRowDatas0, ModuleRowDatas1)
+    ),
+
+    SortPrefs = avoid_sort_self_and_desc(Prefs),
+    sort_module_active_rows_by_preferences(SortPrefs,
+        ModuleRowDatas1, ModuleRowDatas),
+
+    % Build the table of all modules.
+    SortByNamePrefs = Prefs ^ pref_criteria := by_name,
+    ModuleHeaderCell = td_l(deep_link(Cmd, yes(SortByNamePrefs), "Module",
+        link_class_link)),
+    RankHeaderGroup =
+        make_single_table_header_group(td_s("Rank"),
+            table_column_class_ordinal_rank, column_do_not_colour),
+    ModuleHeaderGroup =
+        make_single_table_header_group(ModuleHeaderCell,
+            table_column_class_module_name, column_do_not_colour),
+    MakeHeaderData = override_order_criteria_header_data(Cmd),
+    perf_table_header(total_columns_not_meaningful, Prefs, MakeHeaderData,
+        PerfHeaderGroups),
+    AllHeaderGroups =
+        [RankHeaderGroup, ModuleHeaderGroup] ++ PerfHeaderGroups,
+    header_groups_to_header(AllHeaderGroups, NumColumns, Header),
+
+    list.map_foldl(
+        maybe_ranked_subject_perf_table_row(Prefs, ranked,
+            total_columns_not_meaningful, module_active_to_cell),
+        ModuleRowDatas, Rows, 1, _),
+    Table = table(table_class_box_if_pref, NumColumns, yes(Header), Rows),
+    DisplayTable = display_table(Table),
+
+    % Build controls at the bottom of the page.
+    InactiveControls = inactive_module_controls(Prefs, Cmd),
+    FieldControls = field_controls(Prefs, Cmd),
+    FormatControls = format_controls(Prefs, Cmd),
+    MenuRestartQuitControls = cmds_menu_restart_quit(yes(Prefs)),
+
+    Display = display(yes(Title),
+        [DisplayTable,
+        display_paragraph_break, InactiveControls,
+        display_paragraph_break, FieldControls,
+        display_paragraph_break, FormatControls,
+        display_paragraph_break, MenuRestartQuitControls]).
+
+:- pred active_module(perf_row_data(module_active)::in) is semidet.
+
+active_module(ModuleRowData) :-
+    ModuleActive = ModuleRowData ^ perf_row_subject,
+    ModuleActive ^ ma_is_active = module_is_active.
+
+:- func avoid_sort_self_and_desc(preferences) = preferences.
+
+avoid_sort_self_and_desc(Prefs) = SortPrefs :-
+    ( Prefs ^ pref_criteria = by_cost(CostKind, self_and_desc, Scope) ->
+        SortPrefs = Prefs ^ pref_criteria := by_cost(CostKind, self, Scope)
+    ;
+        SortPrefs = Prefs
+    ).
+
+%-----------------------------------------------------------------------------%
+%
+% Code to display a module report.
+%
+
+    % Create a display_report structure for a module report.
+    %
+:- pred display_report_module(preferences::in, module_report::in, display::out)
+    is det.
+
+display_report_module(Prefs, ModuleReport, Display) :-
+    ModuleReport = module_report(ModuleName, ProcRowDatas0),
+    Cmd = deep_cmd_module(ModuleName),
+    Title = string.format("The procedures of module %s:", [s(ModuleName)]),
+
+    ShowInactiveProcs = Prefs ^ pref_inactive ^ inactive_procs,
+    (
+        ShowInactiveProcs = inactive_show,
+        ProcRowDatas1 = ProcRowDatas0
+    ;
+        ShowInactiveProcs = inactive_hide,
+        list.filter(active_proc, ProcRowDatas0, ProcRowDatas1)
+    ),
+
+    SortPrefs = avoid_sort_self_and_desc(Prefs),
+    sort_proc_active_rows_by_preferences(SortPrefs,
+        ProcRowDatas1, ProcRowDatas),
+
+    % Build the table of all modules.
+    SortByNamePrefs = Prefs ^ pref_criteria := by_name,
+    ProcHeaderCell = td_l(deep_link(Cmd, yes(SortByNamePrefs), "Procedure",
+        link_class_link)),
+    RankHeaderGroup =
+        make_single_table_header_group(td_s("Rank"),
+            table_column_class_ordinal_rank, column_do_not_colour),
+    ProcHeaderGroup =
+        make_single_table_header_group(ProcHeaderCell,
+            table_column_class_module_name, column_do_not_colour),
+    MakeHeaderData = override_order_criteria_header_data(Cmd),
+    perf_table_header(total_columns_meaningful, Prefs, MakeHeaderData,
+        PerfHeaderGroups),
+    AllHeaderGroups =
+        [RankHeaderGroup, ProcHeaderGroup] ++ PerfHeaderGroups,
+    header_groups_to_header(AllHeaderGroups, NumColumns, Header),
+
+    list.map_foldl(
+        maybe_ranked_subject_perf_table_row(Prefs, ranked,
+            total_columns_meaningful, proc_active_to_cell),
+        ProcRowDatas, Rows, 1, _),
+    Table = table(table_class_box_if_pref, NumColumns, yes(Header), Rows),
+    DisplayTable = display_table(Table),
+
+    % Build controls at the bottom of the page.
+    InactiveControls = inactive_proc_controls(Prefs, Cmd),
+    FieldControls = field_controls(Prefs, Cmd),
+    FormatControls = format_controls(Prefs, Cmd),
+    MenuRestartQuitControls = cmds_menu_restart_quit(yes(Prefs)),
+
+    Display = display(yes(Title),
+        [DisplayTable,
+        display_paragraph_break, InactiveControls,
+        display_paragraph_break, FieldControls,
+        display_paragraph_break, FormatControls,
+        display_paragraph_break, MenuRestartQuitControls]).
+
+:- pred active_proc(perf_row_data(proc_active)::in) is semidet.
+
+active_proc(ProcRowData) :-
+    ProcActive = ProcRowData ^ perf_row_subject,
+    ProcActive ^ pa_is_active = proc_is_active.
+
+%-----------------------------------------------------------------------------%
+%
 % Code to display a top procedures report.
 %
 
@@ -266,12 +445,13 @@
     maybe_ranked_proc_table_header(Prefs, ranked, MakeHeaderData,
         NumColumns, Header),
     list.map_foldl(
-        maybe_ranked_subject_perf_table_row(Prefs, ranked, proc_desc_to_cell),
+        maybe_ranked_subject_perf_table_row(Prefs, ranked,
+            total_columns_meaningful, proc_desc_to_cell),
         TopProcs, Rows, 1, _),
     Table = table(table_class_box_if_pref, NumColumns, yes(Header), Rows),
     DisplayTable = display_table(Table),
 
-    % Build controls at the bottom of page.
+    % Build controls at the bottom of the page.
     Cmd = deep_cmd_top_procs(DisplayLimit, CostKind, InclDesc, Scope),
     TopProcsControls = top_procs_controls(Prefs,
         DisplayLimit, CostKind, InclDesc, Scope),
@@ -334,20 +514,21 @@
     display::out) is det.
 
 display_report_proc(Prefs, ProcReport, Display) :-
-    ProcReport = proc_report(PSPtr, ProcSummaryRowData, CallSitePerfs0),
+    ProcReport = proc_report(ProcSummaryRowData, CallSitePerfs0),
     ProcDesc = ProcSummaryRowData ^ perf_row_subject,
-    RefinedName = ProcDesc ^ proc_desc_refined_name,
+    RefinedName = ProcDesc ^ pdesc_refined_name,
     Title = "Summary of procedure " ++ RefinedName,
 
-    PSPtr = proc_static_ptr(PSI),
-    Cmd = deep_cmd_proc(PSI),
+    PSPtr = ProcDesc ^ pdesc_ps_ptr,
+    Cmd = deep_cmd_proc(PSPtr),
 
     SourceHeaderGroup = make_single_table_header_group(td_s("Source"),
         table_column_class_source_context, column_do_not_colour),
     ProcHeaderGroup = make_single_table_header_group(td_s("Procedure"),
         table_column_class_proc, column_do_not_colour),
     MakeHeaderData = override_order_criteria_header_data(Cmd),
-    perf_table_header(Prefs, MakeHeaderData, PerfHeaderGroups),
+    perf_table_header(total_columns_meaningful, Prefs, MakeHeaderData,
+        PerfHeaderGroups),
     AllHeaderGroups =
         [SourceHeaderGroup, ProcHeaderGroup] ++ PerfHeaderGroups,
     header_groups_to_header(AllHeaderGroups, NumColumns, Header),
@@ -359,9 +540,10 @@
     %
     % SummaryProcCell spans two columns: the ones that contain (1) the context
     % and (2) the callee of each call site in the rows below.
-    SummaryProcCell = table_cell(td_s(RefinedName), 2),
+    SummaryProcCell = table_multi_cell(td_s(RefinedName), 2),
     Fields = Prefs ^ pref_fields,
-    perf_table_row(Fields, ProcSummaryRowData, SummaryPerfCells),
+    perf_table_row(total_columns_meaningful, Fields, ProcSummaryRowData,
+        SummaryPerfCells),
     SummaryCells = [SummaryProcCell] ++ SummaryPerfCells,
     SummaryRow = table_row(SummaryCells),
 
@@ -372,8 +554,9 @@
     Table = table(table_class_box_if_pref, NumColumns, yes(Header), AllRows),
     DisplayTable = display_table(Table),
 
-    % Build the controls at the bottom of page.
-    ParentControls = proc_parent_controls(Prefs, PSI),
+    % Build the controls at the bottom of the page.
+    ProcCallersControls = proc_callers_group_controls(Prefs, Cmd,
+        PSPtr, group_by_call_site, Prefs ^ pref_contour),
     SummarizeControls = summarize_controls(Prefs, Cmd),
     SortControls = sort_controls(Prefs, Cmd),
     FieldControls = field_controls(Prefs, Cmd),
@@ -382,37 +565,13 @@
 
     Display = display(yes(Title),
         [DisplayTable,
-        display_paragraph_break, ParentControls,
+        display_paragraph_break, ProcCallersControls,
         display_paragraph_break, SummarizeControls,
         display_paragraph_break, SortControls,
         display_paragraph_break, FieldControls,
         display_paragraph_break, FormatControls,
         display_paragraph_break, MenuRestartQuitControls]).
 
-:- func proc_parent_controls(preferences, int) = display_item.
-
-proc_parent_controls(Prefs, PSI) = ControlsItem :-
-    OrderedByCallSiteCmd = deep_cmd_proc_callers(PSI, group_by_call_site, 1),
-    OrderedByCallSite = display_link(deep_link(OrderedByCallSiteCmd,
-        yes(Prefs), "Ordered by call site", link_class_control)),
-
-    OrderedByProcCmd = deep_cmd_proc_callers(PSI, group_by_proc, 1),
-    OrderedByProc = display_link(deep_link(OrderedByProcCmd,
-        yes(Prefs), "Ordered by procedure", link_class_control)),
-
-    OrderedByModuleCmd = deep_cmd_proc_callers(PSI, group_by_module, 1),
-    OrderedByModule = display_link(deep_link(OrderedByModuleCmd,
-        yes(Prefs), "Ordered by module", link_class_control)),
-
-    OrderedByCliqueCmd = deep_cmd_proc_callers(PSI, group_by_clique, 1),
-    OrderedByClique = display_link(deep_link(OrderedByCliqueCmd,
-        yes(Prefs), "Ordered by clique", link_class_control)),
-
-    List = display_list(list_class_horizontal, no,
-        [OrderedByCallSite, OrderedByProc, OrderedByModule, OrderedByClique]),
-    ControlsItem = display_list(list_class_vertical_no_bullets,
-        yes("The procedure's callers:"), [List]).
-
 :- func report_proc_call_site(preferences, call_site_perf) = list(table_row).
 
 report_proc_call_site(Prefs, CallSitePerf) = Rows :-
@@ -420,27 +579,26 @@
         call_site_perf(KindAndCallee, SummaryPerfRowData, SubPerfs0),
 
     CallSiteDesc = SummaryPerfRowData ^ perf_row_subject,
-    FileName = CallSiteDesc ^ call_site_desc_file_name,
-    LineNumber = CallSiteDesc ^ call_site_desc_line_number,
+    FileName = CallSiteDesc ^ csdesc_file_name,
+    LineNumber = CallSiteDesc ^ csdesc_line_number,
     Context = string.format("%s:%d", [s(FileName), i(LineNumber)]),
-    ContextCell = table_cell(td_s(Context), 1),
+    ContextCell = table_cell(td_s(Context)),
 
     (
         KindAndCallee = normal_call_and_info(NormalCalleeId),
         NormalCalleeId = normal_callee_id(CalleeDesc, TypeSubstStr),
-        CalleeRefinedName = CalleeDesc ^ proc_desc_refined_name,
+        CalleeRefinedName = CalleeDesc ^ pdesc_refined_name,
         ( TypeSubstStr = "" ->
             CallSiteStr = CalleeRefinedName
         ;
             CallSiteStr = string.format("%s [%s]",
                 [s(CalleeRefinedName), s(TypeSubstStr)])
         ),
-        CalleePSPtr = CalleeDesc ^ proc_desc_static_ptr,
-        CalleePSPtr = proc_static_ptr(CalleePSI),
-        CallSiteLinkCmd = deep_cmd_proc(CalleePSI),
+        CalleePSPtr = CalleeDesc ^ pdesc_ps_ptr,
+        CallSiteLinkCmd = deep_cmd_proc(CalleePSPtr),
         CallSiteLink = deep_link(CallSiteLinkCmd, yes(Prefs),
             CallSiteStr, link_class_link),
-        CallSiteCell = table_cell(td_l(CallSiteLink), 1),
+        CallSiteCell = table_cell(td_l(CallSiteLink)),
 
         require(unify(SubPerfs0, []),
             "report_proc_call_site: SubPerfs0 != [] for normal call site")
@@ -458,11 +616,12 @@
             KindAndCallee = callback_and_no_info,
             CallSiteStr = "callback"
         ),
-        CallSiteCell = table_cell(td_s(CallSiteStr), 1)
+        CallSiteCell = table_cell(td_s(CallSiteStr))
     ),
 
     Fields = Prefs ^ pref_fields,
-    perf_table_row(Fields, SummaryPerfRowData, SummaryPerfCells),
+    perf_table_row(total_columns_meaningful, Fields, SummaryPerfRowData,
+        SummaryPerfCells),
     SummaryCells = [ContextCell, CallSiteCell] ++ SummaryPerfCells,
     SummaryRow = table_row(SummaryCells),
 
@@ -487,19 +646,337 @@
 
     ProcDesc = RowData ^ perf_row_subject,
     ProcDesc = proc_desc(PSPtr, _FileName, _LineNumber, RefinedName),
-    PSPtr = proc_static_ptr(PSI),
-    ProcLinkCmd = deep_cmd_proc(PSI),
+    ProcLinkCmd = deep_cmd_proc(PSPtr),
     ProcLink = deep_link(ProcLinkCmd, yes(Prefs), RefinedName,
         link_class_link),
-    ProcCell = table_cell(td_l(ProcLink), 1),
+    ProcCell = table_cell(td_l(ProcLink)),
 
-    perf_table_row(Fields, RowData, PerfCells),
+    perf_table_row(total_columns_meaningful, Fields, RowData, PerfCells),
 
     Cells = [EmptyCell, ProcCell] ++ PerfCells,
     Row = table_row(Cells).
 
 %-----------------------------------------------------------------------------%
 %
+% Code to display a procedure callers report.
+%
+
+    % Create a display_report structure for a proc_callers report.
+    %
+:- pred display_report_proc_callers(preferences::in, proc_callers_report::in,
+    display::out) is det.
+
+display_report_proc_callers(Prefs0, ProcCallersReport, Display) :-
+    ProcCallersReport = proc_callers_report(ProcDesc, CallerRowDatas,
+        BunchNum, ContourExcl, _ContourErrorMessages),
+    RefinedName = ProcDesc ^ pdesc_refined_name,
+
+    % Remember the selected value of contour exclusion.
+    Prefs = Prefs0 ^ pref_contour := ContourExcl,
+
+    PSPtr = ProcDesc ^ pdesc_ps_ptr,
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum, ContourExcl),
+    MakeHeaderData = override_order_criteria_header_data(Cmd),
+    perf_table_header(total_columns_meaningful, Prefs, MakeHeaderData,
+        PerfHeaderGroups),
+
+    RankHeaderGroup = make_single_table_header_group(td_s("Rank"),
+        table_column_class_ordinal_rank, column_do_not_colour),
+
+    (
+        CallerRowDatas = proc_caller_call_sites(CallSiteRowDatas),
+        CallerGroups = group_by_call_site,
+        Title = "The call sites calling " ++ RefinedName,
+        sort_call_site_desc_rows_by_preferences(Prefs, CallSiteRowDatas,
+            SortedCallSiteRowDatas),
+        select_displayed_rows(SortedCallSiteRowDatas, BunchNum,
+            DisplayedCallSiteRowDatas, TotalNumRows, FirstRowNum, LastRowNum,
+            DisplayedBunchNum, MaybeFirstAndLastBunchNum),
+        list.map_foldl(display_caller_call_site(Prefs),
+            DisplayedCallSiteRowDatas, Rows, FirstRowNum, AfterLastRowNum),
+        SourceHeaderGroup = make_single_table_header_group(td_s("Source"),
+            table_column_class_source_context, column_do_not_colour),
+        ProcHeaderGroup = make_single_table_header_group(td_s("In procedure"),
+            table_column_class_proc, column_do_not_colour),
+        IdHeaderGroups = [SourceHeaderGroup, ProcHeaderGroup]
+    ;
+        CallerRowDatas = proc_caller_procedures(ProcRowDatas),
+        CallerGroups = group_by_proc,
+        Title = "The procedures calling " ++ RefinedName,
+        sort_proc_desc_rows_by_preferences(Prefs, ProcRowDatas,
+            SortedProcRowDatas),
+        select_displayed_rows(SortedProcRowDatas, BunchNum,
+            DisplayedProcRowDatas, TotalNumRows, FirstRowNum, LastRowNum,
+            DisplayedBunchNum, MaybeFirstAndLastBunchNum),
+        list.map_foldl(display_caller_proc(Prefs),
+            DisplayedProcRowDatas, Rows, FirstRowNum, AfterLastRowNum),
+        SourceHeaderGroup = make_single_table_header_group(td_s("Source"),
+            table_column_class_source_context, column_do_not_colour),
+        ProcHeaderGroup = make_single_table_header_group(td_s("Procedure"),
+            table_column_class_proc, column_do_not_colour),
+        IdHeaderGroups = [SourceHeaderGroup, ProcHeaderGroup]
+    ;
+        CallerRowDatas = proc_caller_modules(ModuleRowDatas),
+        CallerGroups = group_by_module,
+        Title = "The modules calling " ++ RefinedName,
+        sort_module_name_rows_by_preferences(Prefs, ModuleRowDatas,
+            SortedModuleRowDatas),
+        select_displayed_rows(SortedModuleRowDatas, BunchNum,
+            DisplayedModuleRowDatas, TotalNumRows, FirstRowNum, LastRowNum,
+            DisplayedBunchNum, MaybeFirstAndLastBunchNum),
+        list.map_foldl(display_caller_module(Prefs),
+            DisplayedModuleRowDatas, Rows, FirstRowNum, AfterLastRowNum),
+        ModuleHeaderGroup = make_single_table_header_group(td_s("Module"),
+            table_column_class_source_context, column_do_not_colour),
+        IdHeaderGroups = [ModuleHeaderGroup]
+    ;
+        CallerRowDatas = proc_caller_cliques(CliqueRowDatas),
+        CallerGroups = group_by_clique,
+        Title = "The cliques calling " ++ RefinedName,
+        sort_clique_rows_by_preferences(Prefs, CliqueRowDatas,
+            SortedCliqueRowDatas),
+        select_displayed_rows(SortedCliqueRowDatas, BunchNum,
+            DisplayedCliqueRowDatas, TotalNumRows, FirstRowNum, LastRowNum,
+            DisplayedBunchNum, MaybeFirstAndLastBunchNum),
+        list.map_foldl(display_caller_clique(Prefs),
+            DisplayedCliqueRowDatas, Rows, FirstRowNum, AfterLastRowNum),
+        CliqueHeaderGroup = make_single_table_header_group(td_s("Clique"),
+            table_column_class_clique, column_do_not_colour),
+        MembersHeaderGroup = make_single_table_header_group(td_s("Members"),
+            table_column_class_clique, column_do_not_colour),
+        IdHeaderGroups = [CliqueHeaderGroup, MembersHeaderGroup]
+    ),
+
+    AllHeaderGroups = [RankHeaderGroup] ++ IdHeaderGroups ++ PerfHeaderGroups,
+    header_groups_to_header(AllHeaderGroups, NumColumns, Header),
+
+    (
+        MaybeFirstAndLastBunchNum = no,
+        Message = "There are none.",
+        Display = display(yes(Title), [display_text(Message)])
+    ;
+        MaybeFirstAndLastBunchNum = yes({FirstBunchNum, LastBunchNum}),
+        require(unify(LastRowNum + 1, AfterLastRowNum),
+            "display_report_proc_callers: row number mismatch"),
+        require((FirstBunchNum =< DisplayedBunchNum),
+            "display_report_proc_callers: display bunch number mismatch"),
+        require((DisplayedBunchNum =< LastBunchNum),
+            "display_report_proc_callers: display bunch number mismatch"),
+
+        ( FirstBunchNum = LastBunchNum ->
+            Message = string.format("There are %d:",
+                [i(TotalNumRows)]),
+            BunchControls = []
+        ;
+            Message = string.format("There are %d, showing %d to %d:",
+                [i(TotalNumRows), i(FirstRowNum), i(LastRowNum)]),
+            ( BunchNum > FirstBunchNum ->
+                BunchControlsFirst = [make_proc_callers_link(Prefs,
+                    "First group", PSPtr, CallerGroups, FirstBunchNum,
+                    ContourExcl)]
+            ;
+                BunchControlsFirst = []
+            ),
+            ( BunchNum - 1 > FirstBunchNum ->
+                BunchControlsPrev = [make_proc_callers_link(Prefs,
+                    "Previous group", PSPtr, CallerGroups, BunchNum - 1,
+                    ContourExcl)]
+            ;
+                BunchControlsPrev = []
+            ),
+            ( BunchNum + 1 < LastBunchNum ->
+                BunchControlsNext = [make_proc_callers_link(Prefs,
+                    "Next group", PSPtr, CallerGroups, BunchNum + 1,
+                    ContourExcl)]
+            ;
+                BunchControlsNext = []
+            ),
+            ( BunchNum < LastBunchNum ->
+                BunchControlsLast = [make_proc_callers_link(Prefs,
+                    "Last group", PSPtr, CallerGroups, LastBunchNum,
+                    ContourExcl)]
+            ;
+                BunchControlsLast = []
+            ),
+            BunchControlList = BunchControlsFirst ++ BunchControlsPrev ++
+                BunchControlsNext ++ BunchControlsLast,
+            BunchControls = [display_paragraph_break,
+                display_list(list_class_horizontal_except_title,
+                    yes("Show other groups:"), BunchControlList)]
+        ),
+
+        Table = table(table_class_box_if_pref, NumColumns, yes(Header), Rows),
+        DisplayTable = display_table(Table),
+
+        % Build the controls at the bottom of the page.
+        FirstCmd = deep_cmd_proc_callers(PSPtr, CallerGroups, 1, ContourExcl),
+        CallerGroupControls = proc_callers_group_controls(Prefs, FirstCmd,
+            PSPtr, CallerGroups, ContourExcl),
+        FieldControls = field_controls(Prefs, Cmd),
+        FormatControls = format_controls(Prefs, Cmd),
+        MenuRestartQuitControls = cmds_menu_restart_quit(yes(Prefs)),
+
+        Display = display(yes(Title),
+            [display_text(Message),
+            display_paragraph_break, DisplayTable] ++
+            BunchControls ++
+            [display_paragraph_break, CallerGroupControls,
+            display_paragraph_break, FieldControls,
+            display_paragraph_break, FormatControls,
+            display_paragraph_break, MenuRestartQuitControls])
+    ).
+
+:- pred select_displayed_rows(list(perf_row_data(T))::in, int::in,
+    list(perf_row_data(T))::out, int::out, int::out, int::out,
+    int::out, maybe({int, int})::out) is det.
+
+select_displayed_rows(RowDatas, BunchNum, DisplayRowDatas,
+        TotalNumRows, FirstRowNum, LastRowNum,
+        DisplayedBunchNum, MaybeFirstAndLastBunchNum) :-
+    list.length(RowDatas, TotalNumRows),
+    NumRowsToDelete = (BunchNum - 1) * bunch_size,
+    (
+        list.drop(NumRowsToDelete, RowDatas, RemainingRowDatasPrime),
+        RemainingRowDatasPrime = [_ | _]
+    ->
+        DisplayedBunchNum = BunchNum,
+        % We start counting rows at 1, not 0.
+        FirstRowNum = NumRowsToDelete + 1,
+        RemainingRowDatas = RemainingRowDatasPrime,
+        NumRemainingRows = TotalNumRows - NumRowsToDelete
+    ;
+        DisplayedBunchNum = 1,
+        FirstRowNum = 1,
+        RemainingRowDatas = RowDatas,
+        NumRemainingRows = TotalNumRows
+    ),
+    ( NumRemainingRows > bunch_size ->
+        list.take_upto(bunch_size, RemainingRowDatas, DisplayRowDatas)
+    ;
+        DisplayRowDatas = RemainingRowDatas
+    ),
+    LastRowNum = FirstRowNum - 1 + list.length(DisplayRowDatas),
+    ( TotalNumRows > 0 ->
+        FirstBunchNum = 1,
+        LastBunchNum = (TotalNumRows + bunch_size - 1) / bunch_size,
+        MaybeFirstAndLastBunchNum = yes({FirstBunchNum, LastBunchNum})
+    ;
+        MaybeFirstAndLastBunchNum = no
+    ).
+
+:- func bunch_size = int.
+
+bunch_size = 5.
+
+:- pred display_caller_call_site(preferences::in,
+    perf_row_data(call_site_desc)::in, table_row::out, int::in, int::out)
+    is det.
+
+display_caller_call_site(Prefs, CallSiteRowData, Row, !RowNum) :-
+    RankCell = table_cell(td_i(!.RowNum)),
+    !:RowNum = !.RowNum + 1,
+
+    CallSiteDesc = CallSiteRowData ^ perf_row_subject,
+    PSPtr = CallSiteDesc ^ csdesc_container,
+    FileName = CallSiteDesc ^ csdesc_file_name,
+    LineNumber = CallSiteDesc ^ csdesc_line_number,
+    CallerRefinedName = CallSiteDesc ^ csdesc_caller_refined_name,
+
+    Source = string.format("%s:%d", [s(FileName), i(LineNumber)]),
+    SourceCell = table_cell(td_s(Source)),
+    ProcLinkCmd = deep_cmd_proc(PSPtr),
+    ProcLink = deep_link(ProcLinkCmd, yes(Prefs), CallerRefinedName,
+        link_class_link),
+    ProcCell = table_cell(td_l(ProcLink)),
+
+    Fields = Prefs ^ pref_fields,
+    perf_table_row(total_columns_meaningful, Fields, CallSiteRowData,
+        PerfCells),
+    Cells = [RankCell, SourceCell, ProcCell] ++ PerfCells,
+    Row = table_row(Cells).
+
+:- pred display_caller_proc(preferences::in, perf_row_data(proc_desc)::in,
+    table_row::out, int::in, int::out) is det.
+
+display_caller_proc(Prefs, ProcRowData, Row, !RowNum) :-
+    RankCell = table_cell(td_i(!.RowNum)),
+    !:RowNum = !.RowNum + 1,
+
+    ProcDesc = ProcRowData ^ perf_row_subject,
+    PSPtr = ProcDesc ^ pdesc_ps_ptr,
+    FileName = ProcDesc ^ pdesc_file_name,
+    LineNumber = ProcDesc ^ pdesc_line_number,
+    RefinedName = ProcDesc ^ pdesc_refined_name,
+
+    Source = string.format("%s:%d", [s(FileName), i(LineNumber)]),
+    SourceCell = table_cell(td_s(Source)),
+    ProcLinkCmd = deep_cmd_proc(PSPtr),
+    ProcLink = deep_link(ProcLinkCmd, yes(Prefs), RefinedName,
+        link_class_link),
+    ProcCell = table_cell(td_l(ProcLink)),
+
+    Fields = Prefs ^ pref_fields,
+    perf_table_row(total_columns_meaningful, Fields, ProcRowData, PerfCells),
+    Cells = [RankCell, SourceCell, ProcCell] ++ PerfCells,
+    Row = table_row(Cells).
+
+:- pred display_caller_module(preferences::in, perf_row_data(string)::in,
+    table_row::out, int::in, int::out) is det.
+
+display_caller_module(Prefs, ModuleRowData, Row, !RowNum) :-
+    RankCell = table_cell(td_i(!.RowNum)),
+    !:RowNum = !.RowNum + 1,
+
+    ModuleName = ModuleRowData ^ perf_row_subject,
+    ModuleCell = table_cell(td_s(ModuleName)),
+
+    Fields = Prefs ^ pref_fields,
+    perf_table_row(total_columns_meaningful, Fields, ModuleRowData, PerfCells),
+    Cells = [RankCell, ModuleCell] ++ PerfCells,
+    Row = table_row(Cells).
+
+:- pred display_caller_clique(preferences::in, perf_row_data(clique_desc)::in,
+    table_row::out, int::in, int::out) is det.
+
+display_caller_clique(Prefs, CliqueRowData, Row, !RowNum) :-
+    RankCell = table_cell(td_i(!.RowNum)),
+    !:RowNum = !.RowNum + 1,
+
+    CliqueDesc = CliqueRowData ^ perf_row_subject,
+    CliquePtr = CliqueDesc ^ cdesc_clique_ptr,
+    CliquePtr = clique_ptr(CliqueNum),
+
+    CliqueLinkCmd = deep_cmd_clique(CliquePtr),
+    CliqueText = string.format("clique %d", [i(CliqueNum)]),
+    CliqueLink = deep_link(CliqueLinkCmd, yes(Prefs), CliqueText,
+        link_class_link),
+    CliqueCell = table_cell(td_l(CliqueLink)),
+
+    MembersStrs = list.map(project_proc_desc_refined_name,
+        CliqueDesc ^ cdesc_members),
+    MembersStr = string.join_list(", ", MembersStrs),
+    MembersCell = table_cell(td_s(MembersStr)),
+
+    Fields = Prefs ^ pref_fields,
+    perf_table_row(total_columns_meaningful, Fields, CliqueRowData, PerfCells),
+    Cells = [RankCell, CliqueCell, MembersCell] ++ PerfCells,
+    Row = table_row(Cells).
+
+:- func project_proc_desc_refined_name(proc_desc) = string.
+
+project_proc_desc_refined_name(ProcDesc) = ProcDesc ^ pdesc_refined_name.
+
+:- func make_proc_callers_link(preferences, string, proc_static_ptr,
+    caller_groups, int, contour_exclusion) = display_item.
+
+make_proc_callers_link(Prefs, Label, PSPtr, CallerGroups, BunchNum,
+        ContourExcl) = Item :-
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum, ContourExcl),
+    Link = deep_link(Cmd, yes(Prefs), Label, link_class_control),
+    Item = display_link(Link).
+
+%-----------------------------------------------------------------------------%
+%
 % Code to display proc_static and proc_dynamic dumps.
 %
 
@@ -537,7 +1014,7 @@
     PSPtr = proc_static_ptr(PSI),
     string.format("Dump of proc_dynamic %d", [i(PDI)], Title),
 
-    ProcStaticLink = deep_link(deep_cmd_proc_static(PSI), yes(Prefs),
+    ProcStaticLink = deep_link(deep_cmd_dump_proc_static(PSPtr), yes(Prefs),
         string.int_to_string(PSI), link_class_link),
     MainValues =
         [("Proc static:"            - td_l(ProcStaticLink)),
@@ -566,13 +1043,13 @@
 
 dump_psd_call_site(Prefs, CallSite, Rows, !CallSiteCounter) :-
     counter.allocate(CallSiteNum, !CallSiteCounter),
-    CallSiteNumCell = table_cell(td_i(CallSiteNum), 1),
+    CallSiteNumCell = table_cell(td_i(CallSiteNum)),
     (
         CallSite = slot_normal(CSDPtr),
         CSDPtr = call_site_dynamic_ptr(CSDI),
-        CSDLink = deep_link(deep_cmd_call_site_dynamic(CSDI), yes(Prefs),
-            string.int_to_string(CSDI), link_class_link),
-        CSDCell = table_cell(td_l(CSDLink), 1),
+        CSDLink = deep_link(deep_cmd_dump_call_site_dynamic(CSDPtr),
+            yes(Prefs), string.int_to_string(CSDI), link_class_link),
+        CSDCell = table_cell(td_l(CSDLink)),
         FirstRow = table_row([CallSiteNumCell, CSDCell]),
         Rows = [FirstRow]
     ;
@@ -588,7 +1065,7 @@
         NumCSDPtrs = list.length(CSDPtrs),
         string.format("multi, %d csds (%s)", [i(NumCSDPtrs), s(IsZeroedStr)],
             MultiCellStr),
-        MultiCell = table_cell(td_s(MultiCellStr), 1),
+        MultiCell = table_cell(td_s(MultiCellStr)),
         FirstRow = table_row([CallSiteNumCell, MultiCell]),
         list.map(dump_psd_call_site_multi_entry(Prefs), CSDPtrs, LaterRows),
         Rows = [FirstRow | LaterRows]
@@ -599,10 +1076,10 @@
 
 dump_psd_call_site_multi_entry(Prefs, CSDPtr, Row) :-
     CSDPtr = call_site_dynamic_ptr(CSDI),
-    CSDLink = deep_link(deep_cmd_call_site_dynamic(CSDI), yes(Prefs),
+    CSDLink = deep_link(deep_cmd_dump_call_site_dynamic(CSDPtr), yes(Prefs),
         string.int_to_string(CSDI), link_class_link),
-    CSDCell = table_cell(td_l(CSDLink), 1),
-    EmptyCell = table_cell(td_s(""), 1),
+    CSDCell = table_cell(td_l(CSDLink)),
+    EmptyCell = table_cell(td_s("")),
     Row = table_row([EmptyCell, CSDCell]).
 
     % Create a display_report structure for a call_site_static_dump report.
@@ -617,8 +1094,9 @@
     string.format("Dump of call_site_static %d", [i(CSSI)], Title),
     ContainingPSPtr = proc_static_ptr(ContainingPSI),
 
-    ContainingProcStaticLink = deep_link(deep_cmd_proc_static(ContainingPSI),
-        yes(Prefs), string.int_to_string(ContainingPSI), link_class_link),
+    ContainingProcStaticLink = deep_link(
+        deep_cmd_dump_proc_static(ContainingPSPtr), yes(Prefs),
+        string.int_to_string(ContainingPSI), link_class_link),
 
     (
         CallSiteKind = normal_call_and_callee(CalleePSPtr, TypeSpecDesc),
@@ -629,8 +1107,9 @@
         ;
             CalleeDesc = CalleeDesc0 ++ " typespec " ++ TypeSpecDesc
         ),
-        CalleeProcStaticLink = deep_link(deep_cmd_proc_static(CalleePSI),
-            yes(Prefs), CalleeDesc, link_class_link),
+        CalleeProcStaticLink = deep_link(
+            deep_cmd_dump_proc_static(CalleePSPtr), yes(Prefs), CalleeDesc,
+            link_class_link),
         CallSiteKindData = td_l(CalleeProcStaticLink)
     ;
         CallSiteKind = special_call_and_no_callee,
@@ -665,17 +1144,17 @@
 display_report_call_site_dynamic_dump(Prefs, CallSiteStaticDumpInfo,
         Display) :-
     CallSiteStaticDumpInfo = call_site_dynamic_dump_info(CSDPtr,
-        CallerPSPtr, CalleePSPtr, RowData),
+        CallerPDPtr, CalleePDPtr, RowData),
     CSDPtr = call_site_dynamic_ptr(CSDI),
     string.format("Dump of call_site_dynamic %d", [i(CSDI)], Title),
 
-    CallerPSPtr = proc_dynamic_ptr(CallerPSI),
-    CallerProcDynamicLink = deep_link(deep_cmd_proc_dynamic(CallerPSI),
-        yes(Prefs), string.int_to_string(CallerPSI), link_class_link),
-
-    CalleePSPtr = proc_dynamic_ptr(CalleePSI),
-    CalleeProcDynamicLink = deep_link(deep_cmd_proc_dynamic(CalleePSI),
-        yes(Prefs), string.int_to_string(CalleePSI), link_class_link),
+    CallerPDPtr = proc_dynamic_ptr(CallerPDI),
+    CallerProcDynamicLink = deep_link(deep_cmd_dump_proc_dynamic(CallerPDPtr),
+        yes(Prefs), string.int_to_string(CallerPDI), link_class_link),
+
+    CalleePDPtr = proc_dynamic_ptr(CalleePDI),
+    CalleeProcDynamicLink = deep_link(deep_cmd_dump_proc_dynamic(CalleePDPtr),
+        yes(Prefs), string.int_to_string(CalleePDI), link_class_link),
 
     FirstValues =
         [("Caller proc_dynamic:"    - td_l(CallerProcDynamicLink)),
@@ -688,7 +1167,8 @@
     maybe_ranked_proc_table_header(Prefs, non_ranked, MakeHeaderData,
         NumColumns, Header),
     maybe_ranked_subject_perf_table_row(Prefs, non_ranked,
-        call_site_desc_to_cell, RowData, PerfRow, 1, _),
+        total_columns_meaningful, call_site_desc_to_cell, RowData, PerfRow,
+        1, _),
     PerfTable = table(table_class_box, NumColumns, yes(Header), [PerfRow]),
 
     Display = display(yes(Title),
@@ -711,7 +1191,7 @@
     Criteria0 = Prefs0 ^ pref_criteria,
     Prefs = Prefs0 ^ pref_criteria := Criteria,
     ( Criteria = Criteria0 ->
-        % ZZZ Should we display a simple string to indicate that this link
+        % Should we display a simple string to indicate that this link
         % leads back to the same page, or would that be confusing?
         Link = deep_link(Cmd, yes(Prefs), Label, link_class_link),
         TableData = td_l(Link)
@@ -737,7 +1217,7 @@
         Criteria = by_cost(CostKind, InclDesc, Scope),
         Cmd = deep_cmd_top_procs(DisplayLimit0, CostKind, InclDesc, Scope),
         ( Cmd = Cmd0 ->
-            % ZZZ Should we display a simple string to indicate that this link
+            % Should we display a simple string to indicate that this link
             % leads back to the same page, or would that be confusing?
             Link = deep_link(Cmd, yes(Prefs0), Label, link_class_link),
             TableData = td_l(Link)
@@ -763,18 +1243,22 @@
 % Each pair of predicates should follow the exact same logic when selecting
 % what columns to display, and in what order.
 
+:- type total_columns_meaning
+    --->    total_columns_meaningful
+    ;       total_columns_not_meaningful.
+
     % Convert the performance information in a row data into the cells
     % of a table row according to the preferences.
     %
-:- pred perf_table_row(fields::in, perf_row_data(Subject)::in,
-    list(table_cell)::out) is det.
+:- pred perf_table_row(total_columns_meaning::in, fields::in,
+    perf_row_data(Subject)::in, list(table_cell)::out) is det.
 
-perf_table_row(Fields, RowData, PerfCells) :-
+perf_table_row(TotalsMeaningful, Fields, RowData, PerfCells) :-
     perf_table_row_ports(Fields, RowData, PortCells),
-    perf_table_row_time(Fields, RowData, TimeCells),
-    perf_table_row_callseqs(Fields, RowData, CallSeqsCells),
-    perf_table_row_allocs(Fields, RowData, AllocCells),
-    perf_table_row_memory(Fields, RowData, MemoryCells),
+    perf_table_row_time(TotalsMeaningful, Fields, RowData, TimeCells),
+    perf_table_row_callseqs(TotalsMeaningful, Fields, RowData, CallSeqsCells),
+    perf_table_row_allocs(TotalsMeaningful, Fields, RowData, AllocCells),
+    perf_table_row_memory(TotalsMeaningful, Fields, RowData, MemoryCells),
     PerfCells =
         PortCells ++ TimeCells ++ CallSeqsCells ++
         AllocCells ++ MemoryCells.
@@ -782,16 +1266,20 @@
     % Build the performance group of table headers
     % according to the preferences.
     %
-:- pred perf_table_header(preferences::in,
+:- pred perf_table_header(total_columns_meaning::in, preferences::in,
     (func(preferences, order_criteria, string) = table_data)::in,
     list(table_header_group)::out) is det.
 
-perf_table_header(Prefs, MakeHeaderData, HeaderGroups) :-
+perf_table_header(TotalsMeaningful, Prefs, MakeHeaderData, HeaderGroups) :-
     perf_table_header_ports(Prefs, MakeHeaderData, PortHeaderGroups),
-    perf_table_header_time(Prefs, MakeHeaderData, TimeHeaderGroups),
-    perf_table_header_callseqs(Prefs, MakeHeaderData, CallSeqsHeaderGroups),
-    perf_table_header_allocs(Prefs, MakeHeaderData, AllocHeaderGroups),
-    perf_table_header_memory(Prefs, MakeHeaderData, MemoryHeaderGroups),
+    perf_table_header_time(TotalsMeaningful, Prefs, MakeHeaderData,
+        TimeHeaderGroups),
+    perf_table_header_callseqs(TotalsMeaningful, Prefs, MakeHeaderData,
+        CallSeqsHeaderGroups),
+    perf_table_header_allocs(TotalsMeaningful, Prefs, MakeHeaderData,
+        AllocHeaderGroups),
+    perf_table_header_memory(TotalsMeaningful, Prefs, MakeHeaderData,
+        MemoryHeaderGroups),
     HeaderGroups =
         PortHeaderGroups ++ TimeHeaderGroups ++ CallSeqsHeaderGroups ++
         AllocHeaderGroups ++ MemoryHeaderGroups.
@@ -815,11 +1303,11 @@
         Redos = RowData ^ perf_row_redos,
         Excps = RowData ^ perf_row_excps,
 
-        CallsCell = table_cell(td_i(Calls), 1),
-        ExitsCell = table_cell(td_i(Exits), 1),
-        FailsCell = table_cell(td_i(Fails), 1),
-        RedosCell = table_cell(td_i(Redos), 1),
-        ExcpsCell = table_cell(td_i(Excps), 1),
+        CallsCell = table_cell(td_i(Calls)),
+        ExitsCell = table_cell(td_i(Exits)),
+        FailsCell = table_cell(td_i(Fails)),
+        RedosCell = table_cell(td_i(Redos)),
+        ExcpsCell = table_cell(td_i(Excps)),
 
         PortCells = [CallsCell, ExitsCell, FailsCell, RedosCell, ExcpsCell]
     ).
@@ -859,10 +1347,10 @@
     % Convert the time information in a row data into the cells
     % of a table row according to the preferences.
     %
-:- pred perf_table_row_time(fields::in, perf_row_data(Subject)::in,
-    list(table_cell)::out) is det.
+:- pred perf_table_row_time(total_columns_meaning::in, fields::in,
+    perf_row_data(Subject)::in, list(table_cell)::out) is det.
 
-perf_table_row_time(Fields, RowData, TimeCells) :-
+perf_table_row_time(TotalsMeaningful, Fields, RowData, TimeCells) :-
     TimeFields = Fields ^ time_fields,
     (
         TimeFields = no_time,
@@ -875,24 +1363,57 @@
         ; TimeFields = ticks_and_time_and_percall
         ),
 
-        SelfTicks =         RowData ^ perf_row_self_ticks,
-        SelfTime =          RowData ^ perf_row_self_time,
-        SelfTimePercent =   RowData ^ perf_row_self_time_percent,
-        SelfTimePerCall =   RowData ^ perf_row_self_time_percall,
-        TotalTicks =        RowData ^ perf_row_total_ticks,
-        TotalTime =         RowData ^ perf_row_total_time,
-        TotalTimePercent =  RowData ^ perf_row_total_time_percent,
-        TotalTimePerCall =  RowData ^ perf_row_total_time_percall,
-
-        SelfTicksCell =         table_cell(td_i(SelfTicks), 1),
-        SelfTimeCell =          table_cell(td_t(SelfTime), 1),
-        SelfTimePercentCell =   table_cell(td_p(SelfTimePercent), 1),
-        SelfTimePerCallCell =   table_cell(td_t(SelfTimePerCall), 1),
-        TotalTicksCell =        table_cell(td_i(TotalTicks), 1),
-        TotalTimeCell =         table_cell(td_t(TotalTime), 1),
-        TotalTimePercentCell =  table_cell(td_p(TotalTimePercent), 1),
-        TotalTimePerCallCell =  table_cell(td_t(TotalTimePerCall), 1),
-
+        Self = RowData ^ perf_row_self,
+        SelfTicks =             Self ^ perf_row_ticks,
+        SelfTime =              Self ^ perf_row_time,
+        SelfTimePercent =       Self ^ perf_row_time_percent,
+        SelfTimePerCall =       Self ^ perf_row_time_percall,
+        SelfTicksCell =         table_cell(td_i(SelfTicks)),
+        SelfTimeCell =          table_cell(td_t(SelfTime)),
+        SelfTimePercentCell =   table_cell(td_p(SelfTimePercent)),
+        SelfTimePerCallCell =   table_cell(td_t(SelfTimePerCall)),
+        (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
+                TimeFields = ticks,
+                TimeCells =
+                    [SelfTicksCell, SelfTimePercentCell]
+            ;
+                TimeFields = time,
+                TimeCells =
+                    [SelfTimeCell, SelfTimePercentCell]
+            ;
+                TimeFields = ticks_and_time,
+                TotalsMeaningful = total_columns_not_meaningful,
+                TimeCells =
+                    [SelfTicksCell, SelfTimeCell, SelfTimePercentCell]
+            ;
+                TimeFields = time_and_percall,
+                TimeCells =
+                    [SelfTimeCell, SelfTimePercentCell, SelfTimePerCallCell]
+            ;
+                TimeFields = ticks_and_time_and_percall,
+                TimeCells =
+                    [SelfTicksCell, SelfTimeCell,
+                    SelfTimePercentCell, SelfTimePerCallCell]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            MaybeTotal = RowData ^ perf_row_maybe_total,
+            (
+                MaybeTotal = yes(Total)
+            ;
+                MaybeTotal = no,
+                error("perf_table_row_time: no total")
+            ),
+            TotalTicks =            Total ^ perf_row_ticks,
+            TotalTime =             Total ^ perf_row_time,
+            TotalTimePercent =      Total ^ perf_row_time_percent,
+            TotalTimePerCall =      Total ^ perf_row_time_percall,
+            TotalTicksCell =        table_cell(td_i(TotalTicks)),
+            TotalTimeCell =         table_cell(td_t(TotalTime)),
+            TotalTimePercentCell =  table_cell(td_p(TotalTimePercent)),
+            TotalTimePerCallCell =  table_cell(td_t(TotalTimePerCall)),
         (
             TimeFields = ticks,
             TimeCells =
@@ -900,6 +1421,7 @@
                 TotalTicksCell, TotalTimePercentCell]
         ;
             TimeFields = time,
+                TotalsMeaningful = total_columns_meaningful,
             TimeCells =
                 [SelfTimeCell, SelfTimePercentCell,
                 TotalTimeCell, TotalTimePercentCell]
@@ -921,15 +1443,17 @@
                 TotalTicksCell, TotalTimeCell,
                 TotalTimePercentCell, TotalTimePerCallCell]
         )
+        )
     ).
 
     % Build the time group of table headers according to the preferences.
     %
-:- pred perf_table_header_time(preferences::in,
+:- pred perf_table_header_time(total_columns_meaning::in, preferences::in,
     (func(preferences, order_criteria, string) = table_data)::in,
     list(table_header_group)::out) is det.
 
-perf_table_header_time(Prefs, MakeHeaderData, HeaderGroups) :-
+perf_table_header_time(TotalsMeaningful, Prefs, MakeHeaderData,
+        HeaderGroups) :-
     Fields = Prefs ^ pref_fields,
     TimeFields = Fields ^ time_fields,
 
@@ -968,6 +1492,37 @@
                                     "/call"),
 
         (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
+                TimeFields = ticks,
+                Title = "Clock ticks",
+                SubHeaders =
+                    [SelfTicksData, SelfTimePercentData]
+            ;
+                TimeFields = time,
+                Title = "Time",
+                SubHeaders =
+                    [SelfTimeData, SelfTimePercentData]
+            ;
+                TimeFields = ticks_and_time,
+                Title = "Clock ticks and times",
+                SubHeaders =
+                    [SelfTicksData, SelfTimeData, SelfTimePercentData]
+            ;
+                TimeFields = time_and_percall,
+                Title = "Time",
+                SubHeaders =
+                    [SelfTimeData, SelfTimePercentData, SelfTimePerCallData]
+            ;
+                TimeFields = ticks_and_time_and_percall,
+                Title = "Clock ticks and times",
+                SubHeaders =
+                    [SelfTicksData, SelfTimeData,
+                    SelfTimePercentData, SelfTimePerCallData]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            (
             TimeFields = ticks,
             Title = "Clock ticks",
             SubHeaders =
@@ -999,6 +1554,7 @@
                 SelfTimePercentData, SelfTimePerCallData,
                 TotalTicksData, TotalTimeData,
                 TotalTimePercentData, TotalTimePerCallData]
+            )
         ),
 
         HeaderGroup = make_multi_table_header_group(Title, SubHeaders,
@@ -1009,51 +1565,76 @@
     % Convert the callseqs information in a row data into the cells
     % of a table row according to the preferences.
     %
-:- pred perf_table_row_callseqs(fields::in, perf_row_data(Subject)::in,
-    list(table_cell)::out) is det.
+:- pred perf_table_row_callseqs(total_columns_meaning::in, fields::in,
+    perf_row_data(Subject)::in, list(table_cell)::out) is det.
 
-perf_table_row_callseqs(Fields, RowData, CallSeqsCells) :-
+perf_table_row_callseqs(TotalsMeaningful, Fields, RowData, CallSeqsCells) :-
     CallSeqsFields = Fields ^ callseqs_fields,
     (
         CallSeqsFields = no_callseqs,
         CallSeqsCells = []
     ;
-        SelfCallSeqs =              RowData ^ perf_row_self_callseqs,
-        SelfCallSeqsPercent =       RowData ^ perf_row_self_callseqs_percent,
-        SelfCallSeqsPerCall =       RowData ^ perf_row_self_callseqs_percall,
-        TotalCallSeqs =             RowData ^ perf_row_total_callseqs,
-        TotalCallSeqsPercent =      RowData ^ perf_row_total_callseqs_percent,
-        TotalCallSeqsPerCall =      RowData ^ perf_row_total_callseqs_percall,
-
-        SelfCallSeqsCell =          table_cell(td_i(SelfCallSeqs), 1),
-        SelfCallSeqsPercentCell =   table_cell(td_p(SelfCallSeqsPercent), 1),
-        SelfCallSeqsPerCallCell =   table_cell(td_f(SelfCallSeqsPerCall), 1),
-        TotalCallSeqsCell =         table_cell(td_i(TotalCallSeqs), 1),
-        TotalCallSeqsPercentCell =  table_cell(td_p(TotalCallSeqsPercent), 1),
-        TotalCallSeqsPerCallCell =  table_cell(td_f(TotalCallSeqsPerCall), 1),
-
+        ( CallSeqsFields = callseqs
+        ; CallSeqsFields = callseqs_and_percall
+        ),
+        Self = RowData ^ perf_row_self,
+        SelfCallSeqs =              Self ^ perf_row_callseqs,
+        SelfCallSeqsPercent =       Self ^ perf_row_callseqs_percent,
+        SelfCallSeqsPerCall =       Self ^ perf_row_callseqs_percall,
+        SelfCallSeqsCell =          table_cell(td_i(SelfCallSeqs)),
+        SelfCallSeqsPercentCell =   table_cell(td_p(SelfCallSeqsPercent)),
+        SelfCallSeqsPerCallCell =   table_cell(td_f(SelfCallSeqsPerCall)),
+        (
+            TotalsMeaningful = total_columns_not_meaningful,
         (
             CallSeqsFields = callseqs,
             CallSeqsCells =
-                [SelfCallSeqsCell, SelfCallSeqsPercentCell,
-                TotalCallSeqsCell, TotalCallSeqsPercentCell]
+                    [SelfCallSeqsCell, SelfCallSeqsPercentCell]
         ;
             CallSeqsFields = callseqs_and_percall,
             CallSeqsCells =
                 [SelfCallSeqsCell, SelfCallSeqsPercentCell,
-                SelfCallSeqsPerCallCell,
-                TotalCallSeqsCell, TotalCallSeqsPercentCell,
-                TotalCallSeqsPerCallCell]
+                    SelfCallSeqsPerCallCell]
         )
-    ).
-
-    % Build the callseqs group of table headers according to the preferences.
-    %
-:- pred perf_table_header_callseqs(preferences::in,
-    (func(preferences, order_criteria, string) = table_data)::in,
-    list(table_header_group)::out) is det.
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            MaybeTotal = RowData ^ perf_row_maybe_total,
+            (
+                MaybeTotal = yes(Total)
+            ;
+                MaybeTotal = no,
+                error("perf_table_row_callseqs: no total")
+            ),
+            TotalCallSeqs =             Total ^ perf_row_callseqs,
+            TotalCallSeqsPercent =      Total ^ perf_row_callseqs_percent,
+            TotalCallSeqsPerCall =      Total ^ perf_row_callseqs_percall,
+            TotalCallSeqsCell =         table_cell(td_i(TotalCallSeqs)),
+            TotalCallSeqsPercentCell =  table_cell(td_p(TotalCallSeqsPercent)),
+            TotalCallSeqsPerCallCell =  table_cell(td_f(TotalCallSeqsPerCall)),
+            (
+                CallSeqsFields = callseqs,
+                CallSeqsCells =
+                    [SelfCallSeqsCell, SelfCallSeqsPercentCell,
+                    TotalCallSeqsCell, TotalCallSeqsPercentCell]
+            ;
+                CallSeqsFields = callseqs_and_percall,
+                CallSeqsCells =
+                    [SelfCallSeqsCell, SelfCallSeqsPercentCell,
+                    SelfCallSeqsPerCallCell,
+                    TotalCallSeqsCell, TotalCallSeqsPercentCell,
+                    TotalCallSeqsPerCallCell]
+            )
+        )
+    ).
 
-perf_table_header_callseqs(Prefs, MakeHeaderData, HeaderGroups) :-
+    % Build the callseqs group of table headers according to the preferences.
+    %
+:- pred perf_table_header_callseqs(total_columns_meaning::in, preferences::in,
+    (func(preferences, order_criteria, string) = table_data)::in,
+    list(table_header_group)::out) is det.
+
+perf_table_header_callseqs(TotalsMeaningful, Prefs, MakeHeaderData,
+        HeaderGroups) :-
     Fields = Prefs ^ pref_fields,
     CallSeqsFields = Fields ^ callseqs_fields,
     (
@@ -1077,14 +1658,29 @@
         TotalPerCallData =  MakeHeaderData(Prefs, TotalPerCallCrit, "/call"),
 
         (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
+                CallSeqsFields = callseqs,
+                SubHeaders =
+                    [SelfData, SelfPercentData]
+            ;
+                CallSeqsFields = callseqs_and_percall,
+                SubHeaders =
+                    [SelfData, SelfPercentData, SelfPerCallData]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            (
             CallSeqsFields = callseqs,
             SubHeaders =
-                [SelfData, SelfPercentData, TotalData, TotalPercentData]
+                    [SelfData, SelfPercentData,
+                    TotalData, TotalPercentData]
         ;
             CallSeqsFields = callseqs_and_percall,
             SubHeaders =
                 [SelfData, SelfPercentData, SelfPerCallData,
                 TotalData, TotalPercentData, TotalPerCallData]
+            )
         ),
         Title = "Call sequence numbers",
         HeaderGroup = make_multi_table_header_group(Title, SubHeaders,
@@ -1095,10 +1691,10 @@
     % Convert the allocation information in a row data into the cells
     % of a table row according to the preferences.
     %
-:- pred perf_table_row_allocs(fields::in, perf_row_data(Subject)::in,
-    list(table_cell)::out) is det.
+:- pred perf_table_row_allocs(total_columns_meaning::in, fields::in,
+    perf_row_data(Subject)::in, list(table_cell)::out) is det.
 
-perf_table_row_allocs(Fields, RowData, AllocCells) :-
+perf_table_row_allocs(TotalsMeaningful, Fields, RowData, AllocCells) :-
     AllocFields = Fields ^ alloc_fields,
     (
         AllocFields = no_alloc,
@@ -1108,20 +1704,40 @@
         ; AllocFields = alloc_and_percall
         ),
 
-        SelfAllocs =                RowData ^ perf_row_self_allocs,
-        SelfAllocsPercent =         RowData ^ perf_row_self_allocs_percent,
-        SelfAllocsPerCall =         RowData ^ perf_row_self_allocs_percall,
-        TotalAllocs =               RowData ^ perf_row_total_allocs,
-        TotalAllocsPercent =        RowData ^ perf_row_total_allocs_percent,
-        TotalAllocsPerCall =        RowData ^ perf_row_total_allocs_percall,
-
-        SelfAllocsCell =            table_cell(td_i(SelfAllocs), 1),
-        SelfAllocsPercentCell =     table_cell(td_p(SelfAllocsPercent), 1),
-        SelfAllocsPerCallCell =     table_cell(td_f(SelfAllocsPerCall), 1),
-        TotalAllocsCell =           table_cell(td_i(TotalAllocs), 1),
-        TotalAllocsPercentCell =    table_cell(td_p(TotalAllocsPercent), 1),
-        TotalAllocsPerCallCell =    table_cell(td_f(TotalAllocsPerCall), 1),
-
+        Self = RowData ^ perf_row_self,
+        SelfAllocs =                Self ^ perf_row_allocs,
+        SelfAllocsPercent =         Self ^ perf_row_allocs_percent,
+        SelfAllocsPerCall =         Self ^ perf_row_allocs_percall,
+        SelfAllocsCell =            table_cell(td_i(SelfAllocs)),
+        SelfAllocsPercentCell =     table_cell(td_p(SelfAllocsPercent)),
+        SelfAllocsPerCallCell =     table_cell(td_f(SelfAllocsPerCall)),
+        (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
+                AllocFields = alloc,
+                AllocCells =
+                    [SelfAllocsCell, SelfAllocsPercentCell]
+            ;
+                AllocFields = alloc_and_percall,
+                AllocCells =
+                    [SelfAllocsCell, SelfAllocsPercentCell,
+                    SelfAllocsPerCallCell]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            MaybeTotal = RowData ^ perf_row_maybe_total,
+            (
+                MaybeTotal = yes(Total)
+            ;
+                MaybeTotal = no,
+                error("perf_table_row_allocs: no total")
+            ),
+            TotalAllocs =               Total ^ perf_row_allocs,
+            TotalAllocsPercent =        Total ^ perf_row_allocs_percent,
+            TotalAllocsPerCall =        Total ^ perf_row_allocs_percall,
+            TotalAllocsCell =           table_cell(td_i(TotalAllocs)),
+            TotalAllocsPercentCell =    table_cell(td_p(TotalAllocsPercent)),
+            TotalAllocsPerCallCell =    table_cell(td_f(TotalAllocsPerCall)),
         (
             AllocFields = alloc,
             AllocCells =
@@ -1135,15 +1751,17 @@
                 TotalAllocsCell, TotalAllocsPercentCell,
                 TotalAllocsPerCallCell]
         )
+        )
     ).
 
     % Build the allocs group of table headers according to the preferences.
     %
-:- pred perf_table_header_allocs(preferences::in,
+:- pred perf_table_header_allocs(total_columns_meaning::in, preferences::in,
     (func(preferences, order_criteria, string) = table_data)::in,
     list(table_header_group)::out) is det.
 
-perf_table_header_allocs(Prefs, MakeHeaderData, HeaderGroups) :-
+perf_table_header_allocs(TotalsMeaningful, Prefs, MakeHeaderData,
+        HeaderGroups) :-
     Fields = Prefs ^ pref_fields,
     AllocFields = Fields ^ alloc_fields,
     (
@@ -1168,13 +1786,28 @@
 
         (
             AllocFields = alloc,
+            (
+                TotalsMeaningful = total_columns_not_meaningful,
             SubHeaders =
-                [SelfData, SelfPercentData, TotalData, TotalPercentData]
+                    [SelfData, SelfPercentData]
+            ;
+                TotalsMeaningful = total_columns_meaningful,
+                SubHeaders =
+                    [SelfData, SelfPercentData,
+                    TotalData, TotalPercentData]
+            )
         ;
             AllocFields = alloc_and_percall,
+            (
+                TotalsMeaningful = total_columns_not_meaningful,
+                SubHeaders =
+                    [SelfData, SelfPercentData, SelfPerCallData]
+            ;
+                TotalsMeaningful = total_columns_meaningful,
             SubHeaders =
                 [SelfData, SelfPercentData, SelfPerCallData,
                 TotalData, TotalPercentData, TotalPerCallData]
+            )
         ),
 
         Title = "Memory allocations",
@@ -1186,10 +1819,10 @@
     % Convert the memory information in a row data into the cells
     % of a table row according to the preferences.
     %
-:- pred perf_table_row_memory(fields::in, perf_row_data(Subject)::in,
-    list(table_cell)::out) is det.
+:- pred perf_table_row_memory(total_columns_meaning::in, fields::in,
+    perf_row_data(Subject)::in, list(table_cell)::out) is det.
 
-perf_table_row_memory(Fields, RowData, MemoryCells) :-
+perf_table_row_memory(TotalsMeaningful, Fields, RowData, MemoryCells) :-
     MemoryFields = Fields ^ memory_fields,
     (
         MemoryFields = no_memory,
@@ -1199,20 +1832,39 @@
         ; MemoryFields = memory_and_percall(Units)
         ),
 
-        SelfMem =               RowData ^ perf_row_self_mem,
-        SelfMemPerCall =        RowData ^ perf_row_self_mem_percall,
-        SelfMemPercent =        RowData ^ perf_row_self_mem_percent,
-        TotalMem =              RowData ^ perf_row_total_mem,
-        TotalMemPerCall =       RowData ^ perf_row_total_mem_percall,
-        TotalMemPercent =       RowData ^ perf_row_total_mem_percent,
-
-        SelfMemCell =           table_cell(td_m(SelfMem, Units, 0), 1),
-        SelfMemPerCallCell =    table_cell(td_m(SelfMemPerCall, Units, 2), 1),
-        SelfMemPercentCell =    table_cell(td_p(SelfMemPercent), 1),
-        TotalMemCell =          table_cell(td_m(TotalMem, Units, 0), 1),
-        TotalMemPerCallCell =   table_cell(td_m(TotalMemPerCall, Units, 2), 1),
-        TotalMemPercentCell =   table_cell(td_p(TotalMemPercent), 1),
-
+        Self = RowData ^ perf_row_self,
+        SelfMem =               Self ^ perf_row_mem,
+        SelfMemPerCall =        Self ^ perf_row_mem_percall,
+        SelfMemPercent =        Self ^ perf_row_mem_percent,
+        SelfMemCell =           table_cell(td_m(SelfMem, Units, 0)),
+        SelfMemPerCallCell =    table_cell(td_m(SelfMemPerCall, Units, 2)),
+        SelfMemPercentCell =    table_cell(td_p(SelfMemPercent)),
+        (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
+                MemoryFields = memory(_),
+                MemoryCells =
+                    [SelfMemCell, SelfMemPercentCell]
+            ;
+                MemoryFields = memory_and_percall(_),
+                MemoryCells =
+                    [SelfMemCell, SelfMemPercentCell, SelfMemPerCallCell]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            MaybeTotal = RowData ^ perf_row_maybe_total,
+            (
+                MaybeTotal = yes(Total)
+            ;
+                MaybeTotal = no,
+                error("perf_table_row_memory: no total")
+            ),
+            TotalMem =              Total ^ perf_row_mem,
+            TotalMemPerCall =       Total ^ perf_row_mem_percall,
+            TotalMemPercent =       Total ^ perf_row_mem_percent,
+            TotalMemCell =          table_cell(td_m(TotalMem, Units, 0)),
+            TotalMemPerCallCell =   table_cell(td_m(TotalMemPerCall, Units, 2)),
+            TotalMemPercentCell =   table_cell(td_p(TotalMemPercent)),
         (
             MemoryFields = memory(_),
             MemoryCells =
@@ -1224,15 +1876,17 @@
                 [SelfMemCell, SelfMemPercentCell, SelfMemPerCallCell,
                 TotalMemCell, TotalMemPercentCell, TotalMemPerCallCell]
         )
+        )
     ).
 
     % Build the memory group of table headers according to the preferences.
     %
-:- pred perf_table_header_memory(preferences::in,
+:- pred perf_table_header_memory(total_columns_meaning::in, preferences::in,
     (func(preferences, order_criteria, string) = table_data)::in,
     list(table_header_group)::out) is det.
 
-perf_table_header_memory(Prefs, MakeHeaderData, HeaderGroups) :-
+perf_table_header_memory(TotalsMeaningful, Prefs, MakeHeaderData,
+        HeaderGroups) :-
     Fields = Prefs ^ pref_fields,
     MemoryFields = Fields ^ memory_fields,
     (
@@ -1256,16 +1910,30 @@
         TotalPerCallData =  MakeHeaderData(Prefs, TotalPerCallCrit, "/call"),
 
         (
+            TotalsMeaningful = total_columns_not_meaningful,
+            (
             MemoryFields = memory(Units),
             SubHeaders =
-                [SelfData, SelfPercentData, TotalData, TotalPercentData]
+                    [SelfData, SelfPercentData]
+            ;
+                MemoryFields = memory_and_percall(Units),
+                SubHeaders =
+                    [SelfData, SelfPercentData, SelfPerCallData]
+            )
+        ;
+            TotalsMeaningful = total_columns_meaningful,
+            (
+                MemoryFields = memory(Units),
+                SubHeaders =
+                    [SelfData, SelfPercentData,
+                    TotalData, TotalPercentData]
         ;
             MemoryFields = memory_and_percall(Units),
             SubHeaders =
                 [SelfData, SelfPercentData, SelfPerCallData,
                 TotalData, TotalPercentData, TotalPerCallData]
+            )
         ),
-
         (
             Units = units_words,
             Title = "Memory words"
@@ -1307,13 +1975,13 @@
         RankedHeaderGroups = [RankedHeaderGroup]
     ),
 
-    % ZZZ SubjectHeaderFunc
     ProcHeaderGroup =
         make_single_table_header_group(td_s("Procedure"),
             table_column_class_proc, column_do_not_colour),
     ProcHeaderGroups = [ProcHeaderGroup],
 
-    perf_table_header(Prefs, MakeHeaderData, PerfHeaderGroups),
+    perf_table_header(total_columns_meaningful, Prefs, MakeHeaderData,
+        PerfHeaderGroups),
 
     AllHeaderGroups =
         RankedHeaderGroups ++ ProcHeaderGroups ++ PerfHeaderGroups,
@@ -1323,24 +1991,24 @@
     % according to the preferences.
     %
 :- pred maybe_ranked_subject_perf_table_row(preferences::in, ranked::in,
-    (func(preferences, Subject) = table_cell)::in,
+    total_columns_meaning::in, (func(preferences, Subject) = table_cell)::in,
     perf_row_data(Subject)::in, table_row::out, int::in, int::out) is det.
 
-maybe_ranked_subject_perf_table_row(Prefs, Ranked, SubjectCellFunc,
-        RowData, Row, Rank, Rank + 1) :-
+maybe_ranked_subject_perf_table_row(Prefs, Ranked, TotalsMeaningful,
+        SubjectCellFunc, RowData, Row, Rank, Rank + 1) :-
     (
         Ranked = non_ranked,
         RankCells = []
     ;
         Ranked = ranked,
-        RankCells = [table_cell(td_i(Rank), 1)]
+        RankCells = [table_cell(td_i(Rank))]
     ),
 
     % The name of the procedure,
     SubjectCells = [SubjectCellFunc(Prefs, RowData ^ perf_row_subject)],
 
     Fields = Prefs ^ pref_fields,
-    perf_table_row(Fields, RowData, PerfCells),
+    perf_table_row(TotalsMeaningful, Fields, RowData, PerfCells),
 
     Cells = RankCells ++ SubjectCells ++ PerfCells,
     Row = table_row(Cells).
@@ -1350,7 +2018,7 @@
 % The basic predicates for creating the controls at the bottoms of pages.
 %
 
-:- pred make_top_procs_cmds(preferences::in, display_limit::in,
+:- pred make_top_procs_cmd_items(preferences::in, display_limit::in,
     cost_kind::in, include_descendants::in, measurement_scope::in,
     maybe(string)::in,
     assoc_list(string,
@@ -1359,15 +2027,15 @@
         in(list_skel(pair(ground, (pred(in, in, in, in, out) is det)))),
     display_item::out) is det.
 
-make_top_procs_cmds(Prefs, DisplayLimit, CostKind, InclDesc, Scope, MaybeLabel,
-        LabelsCmdMakers, Item) :-
+make_top_procs_cmd_items(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+        MaybeLabel, LabelsCmdMakers, Item) :-
     list.map(
-        make_top_procs_cmd(Prefs, DisplayLimit, CostKind, InclDesc, Scope),
+        make_top_procs_cmd_item(Prefs, DisplayLimit, CostKind, InclDesc, Scope),
         LabelsCmdMakers, ControlItemLists),
     list.condense(ControlItemLists, ControlItems),
     Item = display_list(list_class_horizontal, MaybeLabel, ControlItems).
 
-:- pred make_top_procs_cmd(preferences::in, display_limit::in,
+:- pred make_top_procs_cmd_item(preferences::in, display_limit::in,
     cost_kind::in, include_descendants::in, measurement_scope::in,
     pair(string,
         (pred(display_limit, cost_kind, include_descendants, measurement_scope,
@@ -1375,7 +2043,7 @@
         in(pair(ground, (pred(in, in, in, in, out) is det))),
     list(display_item)::out) is det.
 
-make_top_procs_cmd(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+make_top_procs_cmd_item(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
         Label - CmdMaker, Items) :-
     Cmd0 = deep_cmd_top_procs(DisplayLimit, CostKind, InclDesc, Scope),
     CmdMaker(DisplayLimit, CostKind, InclDesc, Scope, Cmd),
@@ -1392,23 +2060,65 @@
         Items = [Item]
     ).
 
-:- pred make_prefs_controls(preferences::in, cmd::in, maybe(string)::in,
+:- pred make_first_proc_callers_cmds_item(preferences::in, cmd::in,
+    proc_static_ptr::in, caller_groups::in, contour_exclusion::in,
+    maybe(string)::in,
+    assoc_list(string,
+        (pred(proc_static_ptr, caller_groups, contour_exclusion, cmd)))::
+        in(list_skel(pair(ground, (pred(in, in, in, out) is det)))),
+    display_item::out) is det.
+
+make_first_proc_callers_cmds_item(Prefs, Cmd, PSPtr, CallerGroups, ContourExcl,
+        MaybeLabel, LabelsCmdMakers, Item) :-
+    list.map(
+        make_first_proc_callers_cmd_item(Prefs, Cmd, PSPtr, CallerGroups,
+            ContourExcl),
+        LabelsCmdMakers, ControlItemLists),
+    list.condense(ControlItemLists, ControlItems),
+    Item = display_list(list_class_horizontal, MaybeLabel, ControlItems).
+
+:- pred make_first_proc_callers_cmd_item(preferences::in, cmd::in,
+    proc_static_ptr::in, caller_groups::in, contour_exclusion::in,
+    pair(string,
+        (pred(proc_static_ptr, caller_groups, contour_exclusion, cmd)))::
+        in(pair(ground, (pred(in, in, in, out) is det))),
+    list(display_item)::out) is det.
+
+make_first_proc_callers_cmd_item(Prefs, Cmd0, PSPtr, CallerGroups, ContourExcl,
+        Label - CmdMaker, Items) :-
+    % When we just to a different kind of grouping or toggle contour exclusion,
+    % we always go to the first bunch of the resulting rows.
+    CmdMaker(PSPtr, CallerGroups, ContourExcl, Cmd),
+    ( Cmd = Cmd0 ->
+        Items = []
+        % We could use this code instead.
+        % CurLabel = Label ++ " (current setting)",
+        % PseudoLink = pseudo_link(CurLabel, link_class_control),
+        % Item = display_pseudo_link(PseudoLink),
+        % Items = [Item]
+    ;
+        Link = deep_link(Cmd, yes(Prefs), Label, link_class_control),
+        Item = display_link(Link),
+        Items = [Item]
+    ).
+
+:- pred make_prefs_controls_item(preferences::in, cmd::in, maybe(string)::in,
     assoc_list(string, (pred(preferences, preferences)))::
         in(list_skel(pair(ground, (pred(in, out) is det)))),
     display_item::out) is det.
 
-make_prefs_controls(Prefs0, Cmd, MaybeLabel, LabelsPrefMakers, Item) :-
-    list.map(make_prefs_control(Prefs0, Cmd), LabelsPrefMakers,
+make_prefs_controls_item(Prefs0, Cmd, MaybeLabel, LabelsPrefMakers, Item) :-
+    list.map(make_prefs_control_item(Prefs0, Cmd), LabelsPrefMakers,
         ControlItemLists),
     list.condense(ControlItemLists, ControlItems),
     Item = display_list(list_class_horizontal, MaybeLabel, ControlItems).
 
-:- pred make_prefs_control(preferences::in, cmd::in,
+:- pred make_prefs_control_item(preferences::in, cmd::in,
     pair(string, (pred(preferences, preferences)))::
         in(pair(ground, (pred(in, out) is det))),
     list(display_item)::out) is det.
 
-make_prefs_control(Prefs0, Cmd, Label - PrefMaker, Items) :-
+make_prefs_control_item(Prefs0, Cmd, Label - PrefMaker, Items) :-
     PrefMaker(Prefs0, Prefs),
     ( Prefs = Prefs0 ->
         Items = []
@@ -1433,14 +2143,14 @@
 
 top_procs_controls(Prefs, DisplayLimit, CostKind, InclDesc, Scope) =
         ControlsItem :-
-    make_top_procs_cmds(Prefs, DisplayLimit, CostKind, InclDesc, Scope, no,
-        top_procs_limit_toggles, LimitControls),
-    make_top_procs_cmds(Prefs, DisplayLimit, CostKind, InclDesc, Scope, no,
-        top_procs_sort_toggles, SortControls),
-    make_top_procs_cmds(Prefs, DisplayLimit, CostKind, InclDesc, Scope, no,
-        top_procs_incl_desc_toggles, InclDescControls),
-    make_top_procs_cmds(Prefs, DisplayLimit, CostKind, InclDesc, Scope, no,
-        top_procs_scope_toggles, ScopeControls),
+    make_top_procs_cmd_items(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+        no, top_procs_limit_toggles, LimitControls),
+    make_top_procs_cmd_items(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+        no, top_procs_sort_toggles, SortControls),
+    make_top_procs_cmd_items(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+        no, top_procs_incl_desc_toggles, InclDescControls),
+    make_top_procs_cmd_items(Prefs, DisplayLimit, CostKind, InclDesc, Scope,
+        no, top_procs_scope_toggles, ScopeControls),
     ControlsItem = display_list(list_class_vertical_no_bullets,
         yes("Toggle sorting criteria:"),
         [LimitControls, SortControls, InclDescControls, ScopeControls]).
@@ -1550,21 +2260,89 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Control how the proc command displays the procedure's callers.
+%
+
+:- func proc_callers_group_controls(preferences, cmd, proc_static_ptr,
+    caller_groups, contour_exclusion) = display_item.
+
+proc_callers_group_controls(Prefs, Cmd, PSPtr, CallerGroups, ContourExcl) =
+        ControlsItem :-
+    make_first_proc_callers_cmds_item(Prefs, Cmd, PSPtr, CallerGroups,
+        ContourExcl, no, proc_callers_group_toggles, GroupControls),
+    ( Cmd = deep_cmd_proc_callers(_, _, _, _) ->
+        make_first_proc_callers_cmds_item(Prefs, Cmd, PSPtr, CallerGroups,
+            ContourExcl, no, proc_callers_contour_excl_toggles,
+            ContourExclControls),
+        List = [GroupControls, ContourExclControls]
+    ;
+        List = [GroupControls]
+    ),
+    ControlsItem = display_list(list_class_vertical_no_bullets,
+        yes("The procedure's callers:"), List).
+
+:- func proc_callers_group_toggles =
+    (assoc_list(string,
+        (pred(proc_static_ptr, caller_groups, contour_exclusion, cmd)))::
+        out(list_skel(pair(ground, (pred(in, in, in, out) is det)))))
+    is det.
+
+proc_callers_group_toggles = [
+    "Group by call site" -
+        set_proc_callers_caller_groups(group_by_call_site),
+    "Group by procedure" -
+        set_proc_callers_caller_groups(group_by_proc),
+    "Group by module" -
+        set_proc_callers_caller_groups(group_by_module),
+    "Group by clique" -
+        set_proc_callers_caller_groups(group_by_clique)
+].
+
+:- func proc_callers_contour_excl_toggles =
+    (assoc_list(string,
+        (pred(proc_static_ptr, caller_groups, contour_exclusion, cmd)))::
+        out(list_skel(pair(ground, (pred(in, in, in, out) is det)))))
+    is det.
+
+proc_callers_contour_excl_toggles = [
+    "Apply contour exclusion" -
+        set_proc_callers_contour_excl(apply_contour_exclusion),
+    "Do not apply contour exclusion" -
+        set_proc_callers_contour_excl(do_not_apply_contour_exclusion)
+].
+
+:- pred set_proc_callers_caller_groups(caller_groups::in, proc_static_ptr::in,
+    caller_groups::in, contour_exclusion::in, cmd::out) is det.
+
+set_proc_callers_caller_groups(CallerGroups, PSPtr, _CallerGroups, ContourExcl,
+        Cmd) :-
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, 1, ContourExcl).
+
+:- pred set_proc_callers_contour_excl(contour_exclusion::in,
+    proc_static_ptr::in, caller_groups::in, contour_exclusion::in, cmd::out)
+    is det.
+
+set_proc_callers_contour_excl(ContourExcl, PSPtr, CallerGroups, _ContourExcl,
+        Cmd) :-
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, 1, ContourExcl).
+
+%-----------------------------------------------------------------------------%
+%
 % Control how the rows in procedure displays are sorted.
 %
 
 :- func sort_controls(preferences, cmd) = display_item.
 
 sort_controls(Prefs, Cmd) = ControlsItem :-
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         sort_main_toggles, SortMainControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         sort_time_toggles, SortTimeControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         sort_callseqs_toggles, SortCallSeqsControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         sort_allocs_toggles, SortAllocsControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         sort_memory_toggles, SortMemoryControls),
     ControlsItem = display_list(list_class_vertical_no_bullets,
         yes("Toggle sort options:"),
@@ -1661,7 +2439,7 @@
 :- func summarize_controls(preferences, cmd) = display_item.
 
 summarize_controls(Prefs, Cmd) = ControlsItem :-
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         summarize_toggles, SummarizeControls),
     ControlsItem = display_list(list_class_vertical_no_bullets,
         yes("Toggle summarize options:"), [SummarizeControls]).
@@ -1691,7 +2469,7 @@
 :- func format_controls(preferences, cmd) = display_item.
 
 format_controls(Prefs, Cmd) = ControlsItem :-
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         format_toggles, FormatControls),
     ControlsItem = display_list(list_class_vertical_no_bullets,
         yes("Toggle format options:"), [FormatControls]).
@@ -1725,21 +2503,83 @@
 
 %-----------------------------------------------------------------------------%
 %
+% Control whether we display inactive modules.
+%
+
+:- func inactive_module_controls(preferences, cmd) = display_item.
+
+inactive_module_controls(Prefs, Cmd) = ControlsItem :-
+    make_prefs_controls_item(Prefs, Cmd, no,
+        inactive_module_toggles, InactiveModuleControls),
+    Controls = [InactiveModuleControls],
+    ControlsItem = display_list(list_class_vertical_no_bullets,
+        yes("Toggle display of inactive modules:"), Controls).
+
+:- func inactive_module_toggles =
+    (assoc_list(string, (pred(preferences, preferences)))::
+    out(list_skel(pair(ground, (pred(in, out) is det))))) is det.
+
+inactive_module_toggles = [
+    "Do not display inactive modules" -
+        set_inactive_modules(inactive_hide),
+    "Display inactive modules" -
+        set_inactive_modules(inactive_show)
+].
+
+:- pred set_inactive_modules(inactive_status::in,
+    preferences::in, preferences::out) is det.
+
+set_inactive_modules(Status, !Prefs) :-
+    !Prefs ^ pref_inactive ^ inactive_modules := Status.
+
+%-----------------------------------------------------------------------------%
+%
+% Control whether we display inactive procedures.
+%
+
+:- func inactive_proc_controls(preferences, cmd) = display_item.
+
+inactive_proc_controls(Prefs, Cmd) = ControlsItem :-
+    make_prefs_controls_item(Prefs, Cmd, no,
+        inactive_proc_toggles, InactiveModuleControls),
+    Controls = [InactiveModuleControls],
+    ControlsItem = display_list(list_class_vertical_no_bullets,
+        yes("Toggle display of inactive procedures:"), Controls).
+
+:- func inactive_proc_toggles =
+    (assoc_list(string, (pred(preferences, preferences)))::
+    out(list_skel(pair(ground, (pred(in, out) is det))))) is det.
+
+inactive_proc_toggles = [
+    "Do not display inactive procedures" -
+        set_inactive_procs(inactive_hide),
+    "Display inactive procedures" -
+        set_inactive_procs(inactive_show)
+].
+
+:- pred set_inactive_procs(inactive_status::in,
+    preferences::in, preferences::out) is det.
+
+set_inactive_procs(Status, !Prefs) :-
+    !Prefs ^ pref_inactive ^ inactive_procs := Status.
+
+%-----------------------------------------------------------------------------%
+%
 % Control the set of displayed fields.
 %
 
 :- func field_controls(preferences, cmd) = display_item.
 
 field_controls(Prefs, Cmd) = ControlsItem :-
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         port_field_toggles, PortControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         time_field_toggles, TimeControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         callseqs_field_toggles, CallSeqsControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         alloc_field_toggles, AllocControls),
-    make_prefs_controls(Prefs, Cmd, no,
+    make_prefs_controls_item(Prefs, Cmd, no,
         memory_field_toggles, MemoryControls),
     Controls = [PortControls, TimeControls, CallSeqsControls,
         AllocControls, MemoryControls],
@@ -1886,23 +2726,33 @@
 % Convert procedure and call site descriptions into table cells.
 %
 
+:- func module_active_to_cell(preferences, module_active) = table_cell.
+
+module_active_to_cell(Prefs, ModuleActive) = table_cell(Data) :-
+    ModuleName = ModuleActive ^ ma_module_name,
+    Cmd = deep_cmd_module(ModuleName),
+    Data = td_l(deep_link(Cmd, yes(Prefs), ModuleName, link_class_link)).
+
+:- func proc_active_to_cell(preferences, proc_active) = table_cell.
+
+proc_active_to_cell(Prefs, ProcActive) =
+    proc_desc_to_cell(Prefs, ProcActive ^ pa_proc_desc).
+
 :- func proc_desc_to_cell(preferences, proc_desc) = table_cell.
 
-proc_desc_to_cell(Prefs, ProcDesc) = table_cell(Data, 1) :-
+proc_desc_to_cell(Prefs, ProcDesc) = table_cell(Data) :-
     ProcDesc = proc_desc(PSPtr, _FileName, _LineNumber, RefinedName),
-    PSPtr = proc_static_ptr(PSI),
-    Cmd = deep_cmd_proc(PSI),
+    Cmd = deep_cmd_proc(PSPtr),
     Data = td_l(deep_link(Cmd, yes(Prefs), RefinedName, link_class_link)).
 
 :- func call_site_desc_to_cell(preferences, call_site_desc) = table_cell.
 
-call_site_desc_to_cell(Prefs, CallSiteDesc) = table_cell(Data, 1) :-
+call_site_desc_to_cell(Prefs, CallSiteDesc) = table_cell(Data) :-
     CallSiteDesc = call_site_desc(CSSPtr, _ContainerPSPtr,
         _FileName, _LineNumber, RefinedName, SlotNumber, GoalPath),
     string.format("%s @ %s #%d", [s(RefinedName), s(GoalPath), i(SlotNumber)],
         Name),
-    CSSPtr = call_site_static_ptr(CSSI),
-    Cmd = deep_cmd_call_site_static(CSSI),
+    Cmd = deep_cmd_dump_call_site_static(CSSPtr),
     Data = td_l(deep_link(Cmd, yes(Prefs), Name, link_class_link)).
 
 %-----------------------------------------------------------------------------%
@@ -1915,7 +2765,7 @@
 :- func make_labelled_table_row(pair(string, table_data)) = table_row.
 
 make_labelled_table_row(Label - Value) =
-    table_row([table_cell(td_s(Label), 1), table_cell(Value, 1)]).
+    table_row([table_cell(td_s(Label)), table_cell(Value)]).
 
     % Make a link for use in the menu report.
     %
@@ -1954,8 +2804,8 @@
 compare_call_site_perfs_by_context(CallSitePerfA, CallSitePerfB, Result) :-
     CallSiteDescA = CallSitePerfA ^ csf_summary_perf ^ perf_row_subject,
     CallSiteDescB = CallSitePerfB ^ csf_summary_perf ^ perf_row_subject,
-    FileNameA = CallSiteDescA ^ call_site_desc_file_name,
-    FileNameB = CallSiteDescB ^ call_site_desc_file_name,
+    FileNameA = CallSiteDescA ^ csdesc_file_name,
+    FileNameB = CallSiteDescB ^ csdesc_file_name,
     compare(FileNameResult, FileNameA, FileNameB),
     (
         ( FileNameResult = (<)
@@ -1964,8 +2814,8 @@
         Result = FileNameResult
     ;
         FileNameResult = (=),
-        LineNumberA = CallSiteDescA ^ call_site_desc_line_number,
-        LineNumberB = CallSiteDescB ^ call_site_desc_line_number,
+        LineNumberA = CallSiteDescA ^ csdesc_line_number,
+        LineNumberB = CallSiteDescB ^ csdesc_line_number,
         compare(Result, LineNumberA, LineNumberB)
     ).
 
@@ -1975,8 +2825,8 @@
 compare_call_site_perfs_by_name(CallSitePerfA, CallSitePerfB, Result) :-
     CallSiteDescA = CallSitePerfA ^ csf_summary_perf ^ perf_row_subject,
     CallSiteDescB = CallSitePerfB ^ csf_summary_perf ^ perf_row_subject,
-    NameA = CallSiteDescA ^ call_site_desc_refined_name,
-    NameB = CallSiteDescB ^ call_site_desc_refined_name,
+    NameA = CallSiteDescA ^ csdesc_caller_refined_name,
+    NameB = CallSiteDescB ^ csdesc_caller_refined_name,
     compare(Result, NameA, NameB).
 
 :- pred compare_call_site_perfs_by_cost(
@@ -1992,27 +2842,87 @@
 
 %-----------------------------------------------------------------------------%
 %
-% Sort the procs at a multi call site by the preferred criteria of performance.
+% Sort perf_data_rows of call_site_descs by the preferred criteria.
+%
+
+:- pred sort_call_site_desc_rows_by_preferences(preferences::in,
+    list(perf_row_data(call_site_desc))::in,
+    list(perf_row_data(call_site_desc))::out) is det.
+
+sort_call_site_desc_rows_by_preferences(Prefs, !CallSiteRowDatas) :-
+    OrderCriteria = Prefs ^ pref_criteria,
+    (
+        OrderCriteria = by_context,
+        list.sort(compare_call_site_desc_rows_by_context, !CallSiteRowDatas)
+    ;
+        OrderCriteria = by_name,
+        list.sort(compare_call_site_desc_rows_by_name, !CallSiteRowDatas)
+    ;
+        OrderCriteria = by_cost(CostKind, InclDesc, Scope),
+        list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
+            !CallSiteRowDatas),
+        % We want the most expensive rows to appear first.
+        list.reverse(!CallSiteRowDatas)
+    ).
+
+:- pred compare_call_site_desc_rows_by_context(
+    perf_row_data(call_site_desc)::in, perf_row_data(call_site_desc)::in,
+    comparison_result::out) is det.
+
+compare_call_site_desc_rows_by_context(
+        CallSiteDescRowDataA, CallSiteDescRowDataB, Result) :-
+    CallSiteDescA = CallSiteDescRowDataA ^ perf_row_subject,
+    CallSiteDescB = CallSiteDescRowDataB ^ perf_row_subject,
+    FileNameA = CallSiteDescA ^ csdesc_file_name,
+    FileNameB = CallSiteDescB ^ csdesc_file_name,
+    compare(FileNameResult, FileNameA, FileNameB),
+    (
+        ( FileNameResult = (<)
+        ; FileNameResult = (>)
+        ),
+        Result = FileNameResult
+    ;
+        FileNameResult = (=),
+        LineNumberA = CallSiteDescA ^ csdesc_line_number,
+        LineNumberB = CallSiteDescB ^ csdesc_line_number,
+        compare(Result, LineNumberA, LineNumberB)
+    ).
+
+:- pred compare_call_site_desc_rows_by_name(
+    perf_row_data(call_site_desc)::in, perf_row_data(call_site_desc)::in,
+    comparison_result::out) is det.
+
+compare_call_site_desc_rows_by_name(CallSiteDescRowDataA, CallSiteDescRowDataB,
+        Result) :-
+    CallSiteDescA = CallSiteDescRowDataA ^ perf_row_subject,
+    CallSiteDescB = CallSiteDescRowDataB ^ perf_row_subject,
+    NameA = CallSiteDescA ^ csdesc_caller_refined_name,
+    NameB = CallSiteDescB ^ csdesc_caller_refined_name,
+    compare(Result, NameA, NameB).
+
+%-----------------------------------------------------------------------------%
+%
+% Sort perf_data_rows of proc_descs by the preferred criteria.
 %
 
 :- pred sort_proc_desc_rows_by_preferences(preferences::in,
     list(perf_row_data(proc_desc))::in, list(perf_row_data(proc_desc))::out)
     is det.
 
-sort_proc_desc_rows_by_preferences(Prefs, !CalleePerfs) :-
+sort_proc_desc_rows_by_preferences(Prefs, !ProcDescRowDatas) :-
     OrderCriteria = Prefs ^ pref_criteria,
     (
         OrderCriteria = by_context,
-        list.sort(compare_proc_desc_rows_by_context, !CalleePerfs)
+        list.sort(compare_proc_desc_rows_by_context, !ProcDescRowDatas)
     ;
         OrderCriteria = by_name,
-        list.sort(compare_proc_desc_rows_by_name, !CalleePerfs)
+        list.sort(compare_proc_desc_rows_by_name, !ProcDescRowDatas)
     ;
         OrderCriteria = by_cost(CostKind, InclDesc, Scope),
         list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
-            !CalleePerfs),
+            !ProcDescRowDatas),
         % We want the most expensive rows to appear first.
-        list.reverse(!CalleePerfs)
+        list.reverse(!ProcDescRowDatas)
     ).
 
 :- pred compare_proc_desc_rows_by_context(
@@ -2023,8 +2933,25 @@
             Result) :-
     ProcDescA = ProcDescRowDataA ^ perf_row_subject,
     ProcDescB = ProcDescRowDataB ^ perf_row_subject,
-    FileNameA = ProcDescA ^ proc_desc_file_name,
-    FileNameB = ProcDescB ^ proc_desc_file_name,
+    compare_proc_descs_by_context(ProcDescA, ProcDescB, Result).
+
+:- pred compare_proc_desc_rows_by_name(
+    perf_row_data(proc_desc)::in, perf_row_data(proc_desc)::in,
+    comparison_result::out) is det.
+
+compare_proc_desc_rows_by_name(ProcDescRowDataA, ProcDescRowDataB, Result) :-
+    ProcDescA = ProcDescRowDataA ^ perf_row_subject,
+    ProcDescB = ProcDescRowDataB ^ perf_row_subject,
+    NameA = ProcDescA ^ pdesc_refined_name,
+    NameB = ProcDescB ^ pdesc_refined_name,
+    compare(Result, NameA, NameB).
+
+:- pred compare_proc_descs_by_context(proc_desc::in, proc_desc::in,
+    comparison_result::out) is det.
+
+compare_proc_descs_by_context(ProcDescA, ProcDescB, Result) :-
+    FileNameA = ProcDescA ^ pdesc_file_name,
+    FileNameB = ProcDescB ^ pdesc_file_name,
     compare(FileNameResult, FileNameA, FileNameB),
     (
         ( FileNameResult = (<)
@@ -2033,21 +2960,190 @@
         Result = FileNameResult
     ;
         FileNameResult = (=),
-        LineNumberA = ProcDescA ^ proc_desc_line_number,
-        LineNumberB = ProcDescB ^ proc_desc_line_number,
+        LineNumberA = ProcDescA ^ pdesc_line_number,
+        LineNumberB = ProcDescB ^ pdesc_line_number,
         compare(Result, LineNumberA, LineNumberB)
     ).
 
-:- pred compare_proc_desc_rows_by_name(
-    perf_row_data(proc_desc)::in, perf_row_data(proc_desc)::in,
+%-----------------------------------------------------------------------------%
+%
+% Sort perf_data_rows of proc_actives by the preferred criteria.
+%
+
+:- pred sort_proc_active_rows_by_preferences(preferences::in,
+    list(perf_row_data(proc_active))::in,
+    list(perf_row_data(proc_active))::out) is det.
+
+sort_proc_active_rows_by_preferences(Prefs, !ProcRowDatas) :-
+    OrderCriteria = Prefs ^ pref_criteria,
+    (
+        OrderCriteria = by_context,
+        list.sort(compare_proc_active_rows_by_context, !ProcRowDatas)
+    ;
+        OrderCriteria = by_name,
+        list.sort(compare_proc_active_rows_by_name, !ProcRowDatas)
+    ;
+        OrderCriteria = by_cost(CostKind, InclDesc, Scope),
+        list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
+            !ProcRowDatas),
+        % We want the most expensive rows to appear first.
+        list.reverse(!ProcRowDatas)
+    ).
+
+:- pred compare_proc_active_rows_by_context(
+    perf_row_data(proc_active)::in, perf_row_data(proc_active)::in,
     comparison_result::out) is det.
 
-compare_proc_desc_rows_by_name(ProcDescRowDataA, ProcDescRowDataB, Result) :-
-    ProcDescA = ProcDescRowDataA ^ perf_row_subject,
-    ProcDescB = ProcDescRowDataB ^ perf_row_subject,
-    NameA = ProcDescA ^ proc_desc_refined_name,
-    NameB = ProcDescB ^ proc_desc_refined_name,
-    compare(Result, NameA, NameB).
+compare_proc_active_rows_by_context(ProcRowDataA, ProcRowDataB, Result) :-
+    ProcActiveA = ProcRowDataA ^ perf_row_subject,
+    ProcActiveB = ProcRowDataB ^ perf_row_subject,
+    ProcDescA = ProcActiveA ^ pa_proc_desc,
+    ProcDescB = ProcActiveB ^ pa_proc_desc,
+    compare_proc_descs_by_context(ProcDescA, ProcDescB, Result).
+
+:- pred compare_proc_active_rows_by_name(
+    perf_row_data(proc_active)::in, perf_row_data(proc_active)::in,
+    comparison_result::out) is det.
+
+compare_proc_active_rows_by_name(ModuleRowDataA, ModuleRowDataB, Result) :-
+    ProcActiveA = ModuleRowDataA ^ perf_row_subject,
+    ProcActiveB = ModuleRowDataB ^ perf_row_subject,
+    ProcNameA = ProcActiveA ^ pa_proc_desc ^ pdesc_refined_name,
+    ProcNameB = ProcActiveB ^ pa_proc_desc ^ pdesc_refined_name,
+    compare(Result, ProcNameA, ProcNameB).
+
+%-----------------------------------------------------------------------------%
+%
+% Sort perf_data_rows of module_actives by the preferred criteria.
+%
+
+:- pred sort_module_active_rows_by_preferences(preferences::in,
+    list(perf_row_data(module_active))::in,
+    list(perf_row_data(module_active))::out) is det.
+
+sort_module_active_rows_by_preferences(Prefs, !ModuleRowDatas) :-
+    OrderCriteria = Prefs ^ pref_criteria,
+    (
+        % A context is a filename and line number. The filename is derived
+        % from the module name, and for modules, the line number part of the
+        % context isn't relevant. Therefore sorting by context is equivalent to
+        % sorting by name.
+        ( OrderCriteria = by_context
+        ; OrderCriteria = by_name
+        ),
+        list.sort(compare_module_active_rows_by_name, !ModuleRowDatas)
+    ;
+        OrderCriteria = by_cost(CostKind, InclDesc, Scope),
+        list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
+            !ModuleRowDatas),
+        % We want the most expensive rows to appear first.
+        list.reverse(!ModuleRowDatas)
+    ).
+
+:- pred compare_module_active_rows_by_name(
+    perf_row_data(module_active)::in, perf_row_data(module_active)::in,
+    comparison_result::out) is det.
+
+compare_module_active_rows_by_name(ModuleRowDataA, ModuleRowDataB, Result) :-
+    ModuleDescA = ModuleRowDataA ^ perf_row_subject,
+    ModuleDescB = ModuleRowDataB ^ perf_row_subject,
+    ModuleNameA = ModuleDescA ^ ma_module_name,
+    ModuleNameB = ModuleDescB ^ ma_module_name,
+    compare(Result, ModuleNameA, ModuleNameB).
+
+%-----------------------------------------------------------------------------%
+%
+% Sort perf_data_rows of module names by the preferred criteria.
+%
+
+:- pred sort_module_name_rows_by_preferences(preferences::in,
+    list(perf_row_data(string))::in, list(perf_row_data(string))::out) is det.
+
+sort_module_name_rows_by_preferences(Prefs, !ModuleRowDatas) :-
+    OrderCriteria = Prefs ^ pref_criteria,
+    (
+        % A context is a filename and line number. The filename is derived
+        % from the module name, and for modules, the line number part of the
+        % context isn't relevant. Therefore sorting by context is equivalent to
+        % sorting by name.
+        ( OrderCriteria = by_context
+        ; OrderCriteria = by_name
+        ),
+        list.sort(compare_module_name_rows_by_name, !ModuleRowDatas)
+    ;
+        OrderCriteria = by_cost(CostKind, InclDesc, Scope),
+        list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
+            !ModuleRowDatas),
+        % We want the most expensive rows to appear first.
+        list.reverse(!ModuleRowDatas)
+    ).
+
+:- pred compare_module_name_rows_by_name(
+    perf_row_data(string)::in, perf_row_data(string)::in,
+    comparison_result::out) is det.
+
+compare_module_name_rows_by_name(ModuleRowDataA, ModuleRowDataB, Result) :-
+    ModuleNameA = ModuleRowDataA ^ perf_row_subject,
+    ModuleNameB = ModuleRowDataB ^ perf_row_subject,
+    compare(Result, ModuleNameA, ModuleNameB).
+
+%-----------------------------------------------------------------------------%
+%
+% Sort perf_data_rows of cliques by the preferred criteria.
+%
+
+:- pred sort_clique_rows_by_preferences(preferences::in,
+    list(perf_row_data(clique_desc))::in, list(perf_row_data(clique_desc))::out)
+    is det.
+
+sort_clique_rows_by_preferences(Prefs, !CliqueRowDatas) :-
+    OrderCriteria = Prefs ^ pref_criteria,
+    (
+        OrderCriteria = by_context,
+        % For cliques, we don't have have a single context. We could use the
+        % contexts of the procedures in the clique, but using the clique number
+        % seems more useful.
+        list.sort(compare_clique_rows_by_number, !CliqueRowDatas)
+    ;
+        OrderCriteria = by_name,
+        list.sort(compare_clique_rows_by_first_proc_name, !CliqueRowDatas)
+    ;
+        OrderCriteria = by_cost(CostKind, InclDesc, Scope),
+        list.sort(compare_perf_row_datas_by_cost(CostKind, InclDesc, Scope),
+            !CliqueRowDatas),
+        % We want the most expensive rows to appear first.
+        list.reverse(!CliqueRowDatas)
+    ).
+
+:- pred compare_clique_rows_by_number(
+    perf_row_data(clique_desc)::in, perf_row_data(clique_desc)::in,
+    comparison_result::out) is det.
+
+compare_clique_rows_by_number(CliqueRowDataA, CliqueRowDataB, Result) :-
+    CliqueDescA = CliqueRowDataA ^ perf_row_subject,
+    CliqueDescB = CliqueRowDataB ^ perf_row_subject,
+    CliqueDescA ^ cdesc_clique_ptr = clique_ptr(CliqueNumA),
+    CliqueDescB ^ cdesc_clique_ptr = clique_ptr(CliqueNumB),
+    compare(Result, CliqueNumA, CliqueNumB).
+
+:- pred compare_clique_rows_by_first_proc_name(
+    perf_row_data(clique_desc)::in, perf_row_data(clique_desc)::in,
+    comparison_result::out) is det.
+
+compare_clique_rows_by_first_proc_name(CliqueRowDataA, CliqueRowDataB,
+        Result) :-
+    CliqueDescA = CliqueRowDataA ^ perf_row_subject,
+    CliqueDescB = CliqueRowDataB ^ perf_row_subject,
+    ProcDescsA = CliqueDescA ^ cdesc_members,
+    ProcDescsB = CliqueDescB ^ cdesc_members,
+    (
+        ProcDescsA = [FirstProcDescA | _],
+        ProcDescsB = [FirstProcDescB | _]
+    ->
+        compare_proc_descs_by_context(FirstProcDescA, FirstProcDescB, Result)
+    ;
+        error("compare_clique_rows_by_first_proc_name: missing first proc")
+    ).
 
 %-----------------------------------------------------------------------------%
 %
@@ -2074,110 +3170,162 @@
         CostKind = cost_time,
         (
             InclDesc = self,
+            SelfA = PerfA ^ perf_row_self,
+            SelfB = PerfB ^ perf_row_self,
+            (
             Scope = overall,
-            TimeA = PerfA ^ perf_row_self_time,
-            TimeB = PerfB ^ perf_row_self_time,
+                TimeA = SelfA ^ perf_row_time,
+                TimeB = SelfB ^ perf_row_time,
             compare(Result, TimeA, TimeB)
         ;
-            InclDesc = self,
             Scope = per_call,
-            TimeA = PerfA ^ perf_row_self_time_percall,
-            TimeB = PerfB ^ perf_row_self_time_percall,
+                TimeA = SelfA ^ perf_row_time_percall,
+                TimeB = SelfB ^ perf_row_time_percall,
             compare(Result, TimeA, TimeB)
+            )
         ;
             InclDesc = self_and_desc,
+            MaybeTotalA = PerfA ^ perf_row_maybe_total,
+            MaybeTotalB = PerfB ^ perf_row_maybe_total,
+            (
+                MaybeTotalA = yes(TotalA),
+                MaybeTotalB = yes(TotalB)
+            ->
+                (
             Scope = overall,
-            TimeA = PerfA ^ perf_row_total_time,
-            TimeB = PerfB ^ perf_row_total_time,
+                    TimeA = TotalA ^ perf_row_time,
+                    TimeB = TotalB ^ perf_row_time,
             compare(Result, TimeA, TimeB)
         ;
-            InclDesc = self_and_desc,
             Scope = per_call,
-            TimeA = PerfA ^ perf_row_total_time_percall,
-            TimeB = PerfB ^ perf_row_total_time_percall,
+                    TimeA = TotalA ^ perf_row_time_percall,
+                    TimeB = TotalB ^ perf_row_time_percall,
             compare(Result, TimeA, TimeB)
         )
     ;
+                error("compare_perf_row_datas_by_cost: self_and_desc")
+            )
+        )
+    ;
         CostKind = cost_callseqs,
         (
             InclDesc = self,
+            SelfA = PerfA ^ perf_row_self,
+            SelfB = PerfB ^ perf_row_self,
+            (
             Scope = overall,
-            CallSeqsA = PerfA ^ perf_row_self_callseqs,
-            CallSeqsB = PerfB ^ perf_row_self_callseqs,
+                CallSeqsA = SelfA ^ perf_row_callseqs,
+                CallSeqsB = SelfB ^ perf_row_callseqs,
             compare(Result, CallSeqsA, CallSeqsB)
         ;
-            InclDesc = self,
             Scope = per_call,
-            CallSeqsA = PerfA ^ perf_row_self_callseqs_percall,
-            CallSeqsB = PerfB ^ perf_row_self_callseqs_percall,
+                CallSeqsA = SelfA ^ perf_row_callseqs_percall,
+                CallSeqsB = SelfB ^ perf_row_callseqs_percall,
             compare(Result, CallSeqsA, CallSeqsB)
+            )
         ;
             InclDesc = self_and_desc,
+            MaybeTotalA = PerfA ^ perf_row_maybe_total,
+            MaybeTotalB = PerfB ^ perf_row_maybe_total,
+            (
+                MaybeTotalA = yes(TotalA),
+                MaybeTotalB = yes(TotalB)
+            ->
+                (
             Scope = overall,
-            CallSeqsA = PerfA ^ perf_row_total_callseqs,
-            CallSeqsB = PerfB ^ perf_row_total_callseqs,
+                    CallSeqsA = TotalA ^ perf_row_callseqs,
+                    CallSeqsB = TotalB ^ perf_row_callseqs,
             compare(Result, CallSeqsA, CallSeqsB)
         ;
-            InclDesc = self_and_desc,
             Scope = per_call,
-            CallSeqsA = PerfA ^ perf_row_total_callseqs_percall,
-            CallSeqsB = PerfB ^ perf_row_total_callseqs_percall,
+                    CallSeqsA = TotalA ^ perf_row_callseqs_percall,
+                    CallSeqsB = TotalB ^ perf_row_callseqs_percall,
             compare(Result, CallSeqsA, CallSeqsB)
         )
     ;
+                error("compare_perf_row_datas_by_cost: self_and_desc")
+            )
+        )
+    ;
         CostKind = cost_allocs,
         (
             InclDesc = self,
+            SelfA = PerfA ^ perf_row_self,
+            SelfB = PerfB ^ perf_row_self,
+            (
             Scope = overall,
-            AllocsA = PerfA ^ perf_row_self_allocs,
-            AllocsB = PerfB ^ perf_row_self_allocs,
+                AllocsA = SelfA ^ perf_row_allocs,
+                AllocsB = SelfB ^ perf_row_allocs,
             compare(Result, AllocsA, AllocsB)
         ;
-            InclDesc = self,
             Scope = per_call,
-            AllocsA = PerfA ^ perf_row_self_allocs_percall,
-            AllocsB = PerfB ^ perf_row_self_allocs_percall,
+                AllocsA = SelfA ^ perf_row_allocs_percall,
+                AllocsB = SelfB ^ perf_row_allocs_percall,
             compare(Result, AllocsA, AllocsB)
+            )
         ;
             InclDesc = self_and_desc,
+            MaybeTotalA = PerfA ^ perf_row_maybe_total,
+            MaybeTotalB = PerfB ^ perf_row_maybe_total,
+            (
+                MaybeTotalA = yes(TotalA),
+                MaybeTotalB = yes(TotalB)
+            ->
+                (
             Scope = overall,
-            AllocsA = PerfA ^ perf_row_total_allocs,
-            AllocsB = PerfB ^ perf_row_total_allocs,
+                    AllocsA = TotalA ^ perf_row_allocs,
+                    AllocsB = TotalB ^ perf_row_allocs,
             compare(Result, AllocsA, AllocsB)
         ;
-            InclDesc = self_and_desc,
             Scope = per_call,
-            AllocsA = PerfA ^ perf_row_total_allocs_percall,
-            AllocsB = PerfB ^ perf_row_total_allocs_percall,
+                    AllocsA = TotalA ^ perf_row_allocs_percall,
+                    AllocsB = TotalB ^ perf_row_allocs_percall,
             compare(Result, AllocsA, AllocsB)
         )
     ;
+                error("compare_perf_row_datas_by_cost: self_and_desc")
+            )
+        )
+    ;
         CostKind = cost_words,
         (
             InclDesc = self,
+            SelfA = PerfA ^ perf_row_self,
+            SelfB = PerfB ^ perf_row_self,
+            (
             Scope = overall,
-            MemoryA = PerfA ^ perf_row_self_mem,
-            MemoryB = PerfB ^ perf_row_self_mem,
+                MemoryA = SelfA ^ perf_row_mem,
+                MemoryB = SelfB ^ perf_row_mem,
             compare_memory(MemoryA, MemoryB, Result)
         ;
-            InclDesc = self,
             Scope = per_call,
-            MemoryA = PerfA ^ perf_row_self_mem_percall,
-            MemoryB = PerfB ^ perf_row_self_mem_percall,
+                MemoryA = SelfA ^ perf_row_mem_percall,
+                MemoryB = SelfB ^ perf_row_mem_percall,
             compare_memory(MemoryA, MemoryB, Result)
+            )
         ;
             InclDesc = self_and_desc,
+            MaybeTotalA = PerfA ^ perf_row_maybe_total,
+            MaybeTotalB = PerfB ^ perf_row_maybe_total,
+            (
+                MaybeTotalA = yes(TotalA),
+                MaybeTotalB = yes(TotalB)
+            ->
+                (
             Scope = overall,
-            MemoryA = PerfA ^ perf_row_total_mem,
-            MemoryB = PerfB ^ perf_row_total_mem,
+                    MemoryA = TotalA ^ perf_row_mem,
+                    MemoryB = TotalB ^ perf_row_mem,
             compare_memory(MemoryA, MemoryB, Result)
         ;
-            InclDesc = self_and_desc,
             Scope = per_call,
-            MemoryA = PerfA ^ perf_row_total_mem_percall,
-            MemoryB = PerfB ^ perf_row_total_mem_percall,
+                    MemoryA = TotalA ^ perf_row_mem_percall,
+                    MemoryB = TotalB ^ perf_row_mem_percall,
             compare_memory(MemoryA, MemoryB, Result)
         )
+            ;
+                error("compare_perf_row_datas_by_cost: self_and_desc")
+            )
+        )
     ).
 
 %-----------------------------------------------------------------------------%
Index: exclude.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/exclude.m,v
retrieving revision 1.11
diff -u -b -r1.11 exclude.m
--- exclude.m	1 Dec 2006 15:03:46 -0000	1.11
+++ exclude.m	19 Aug 2008 05:41:23 -0000
@@ -52,8 +52,8 @@
 
 :- type exclude_file.
 
-:- pred read_exclude_file(string::in, deep::in, maybe_error(exclude_file)::out,
-    io::di, io::uo) is det.
+:- pred read_exclude_file(string::in, deep::in,
+    maybe(maybe_error(exclude_file))::out, io::di, io::uo) is det.
 
 :- func apply_contour_exclusion(deep, exclude_file, call_site_dynamic_ptr)
     = call_site_dynamic_ptr.
@@ -90,23 +90,25 @@
 
 %-----------------------------------------------------------------------------%
 
-read_exclude_file(FileName, Deep, Res, !IO) :-
-    io.open_input(FileName, Res0, !IO),
+read_exclude_file(FileName, Deep, MaybeMaybeExcludeFile, !IO) :-
+    io.open_input(FileName, MaybeStream, !IO),
     (
-        Res0 = ok(InputStream),
-        read_exclude_lines(FileName, InputStream, [], Res1, !IO),
+        MaybeStream = ok(InputStream),
+        read_exclude_lines(FileName, InputStream, [], MaybeSpecs, !IO),
         io.close_input(InputStream, !IO),
         (
-            Res1 = ok(Specs),
-            validate_exclude_lines(FileName, Specs, Deep, Res)
+            MaybeSpecs = ok(Specs),
+            validate_exclude_lines(FileName, Specs, Deep, MaybeExcludeFile),
+            MaybeMaybeExcludeFile = yes(MaybeExcludeFile)
         ;
-            Res1 = error(Msg),
-            Res = error(Msg)
+            MaybeSpecs = error(Msg),
+            MaybeMaybeExcludeFile = yes(error(Msg))
         )
     ;
-        Res0 = error(Err),
-        io.error_message(Err, Msg),
-        Res = error(Msg)
+        MaybeStream = error(_),
+        % If we cannot open the file, simply return `no' as an indication
+        % that there is no exclude file there, at least not a readable one.
+        MaybeMaybeExcludeFile = no
     ).
 
 :- pred read_exclude_lines(string::in, io.input_stream::in,
Index: html_format.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/html_format.m,v
retrieving revision 1.29
diff -u -b -r1.29 html_format.m
--- html_format.m	18 Aug 2008 02:14:51 -0000	1.29
+++ html_format.m	25 Aug 2008 04:12:16 -0000
@@ -16,7 +16,7 @@
 % linear over the length of both input strings, building a long string
 % from many short strings would take quadratic time. This is why we represent
 % HTML as a cord of strings instead. This cord is then converted to a list of
-% strings and then a single list just before being given to the browser.
+% strings and then a single string just before being given to the browser.
 %
 %-----------------------------------------------------------------------------%
 
@@ -299,7 +299,8 @@
                 Class = list_class_horizontal,
                 PostTitleHTML = empty_html
             ;
-                ( Class = list_class_vertical_bullets
+                ( Class = list_class_horizontal_except_title
+                ; Class = list_class_vertical_bullets
                 ; Class = list_class_vertical_no_bullets
                 ),
                 PostTitleHTML = str_to_html("<br>\n")
@@ -310,26 +311,28 @@
             PostTitleHTML = empty_html
         ),
         (
-            Class = list_class_vertical_bullets,
-            OutsideStartTag = "<ul>\n",
-            OutsideEndTag = "</ul>\n",
-            InnerStartTag = "<li>\n",
-            InnerEndTag = "</li>\n",
-            Separator = empty_html
-        ;
-            Class = list_class_vertical_no_bullets,
+            ( Class = list_class_horizontal
+            ; Class = list_class_horizontal_except_title
+            ),
             OutsideStartTag = "",
             OutsideEndTag = "\n",
             InnerStartTag = "",
             InnerEndTag = "\n",
-            Separator = str_to_html("<br>\n")
+            Separator = str_to_html("")
         ;
-            Class = list_class_horizontal,
+            Class = list_class_vertical_no_bullets,
             OutsideStartTag = "",
             OutsideEndTag = "\n",
             InnerStartTag = "",
             InnerEndTag = "\n",
-            Separator = str_to_html("")
+            Separator = str_to_html("<br>\n")
+        ;
+            Class = list_class_vertical_bullets,
+            OutsideStartTag = "<ul>\n",
+            OutsideEndTag = "</ul>\n",
+            InnerStartTag = "<li>\n",
+            InnerEndTag = "</li>\n",
+            Separator = empty_html
         ),
         sep_map_join_html(Separator,
             item_to_html(InnerStartTag, InnerEndTag, FormatInfo),
@@ -602,7 +605,12 @@
         !:ColumnNum = !.ColumnNum + 1,
         HTML = str_to_html("<td/>")
     ;
-        Cell = table_cell(CellData, Span),
+        (
+            Cell = table_cell(CellData),
+            Span = 1
+        ;
+            Cell = table_multi_cell(CellData, Span)
+        ),
         (
             MaybeClassMap = yes(ClassMap),
             ( map.search(ClassMap, !.ColumnNum, ColumnClassStrPrime) ->
@@ -675,8 +683,10 @@
 
 table_column_class_to_string(table_column_class_no_class) = "default".
 table_column_class_to_string(table_column_class_allocations) = "allocations".
+table_column_class_to_string(table_column_class_clique) = "clique".
 table_column_class_to_string(table_column_class_callseqs) = "callseqs".
 table_column_class_to_string(table_column_class_memory) = "memory".
+table_column_class_to_string(table_column_class_module_name) = "module_name".
 table_column_class_to_string(table_column_class_number) = "number".
 table_column_class_to_string(table_column_class_ordinal_rank) = "ordinal_rank".
 table_column_class_to_string(table_column_class_port_counts) = "port_counts".
@@ -745,11 +755,21 @@
                 style_element("text-align")     - "right"
             ])
         ),
+        ( style_control("td.clique") -
+            map.from_assoc_list([
+                style_element("text-align")     - "right"
+            ])
+        ),
         ( style_control("td.memory") -
             map.from_assoc_list([
                 style_element("text-align")     - "right"
             ])
         ),
+        ( style_control("td.module_name") -
+            map.from_assoc_list([
+                style_element("text-align")     - "left"
+            ])
+        ),
         ( style_control("td.number") -
             map.from_assoc_list([
                 style_element("text-align")     - "right"
@@ -1251,18 +1271,18 @@
 command_relevant_toggles(deep_cmd_timeout(_)) = [].
 command_relevant_toggles(deep_cmd_menu) = [].
 command_relevant_toggles(deep_cmd_root(_)) =
-    % The clique num doesn't matter.
-    command_relevant_toggles(deep_cmd_clique(1)).
+    % The clique_ptr doesn't matter.
+    command_relevant_toggles(deep_cmd_clique(clique_ptr(1))).
 command_relevant_toggles(deep_cmd_clique(_)) =
     [toggle_fields, toggle_box, toggle_colour, toggle_ancestor_limit,
     toggle_summarize, toggle_order_criteria, toggle_time_format].
 command_relevant_toggles(deep_cmd_proc(_)) =
     [toggle_fields, toggle_box, toggle_colour, toggle_summarize,
     toggle_order_criteria, toggle_time_format].
-command_relevant_toggles(deep_cmd_proc_callers(_, _, _)) =
+command_relevant_toggles(deep_cmd_proc_callers(_, _, _, _)) =
     [toggle_fields, toggle_box, toggle_colour, toggle_order_criteria,
     toggle_contour, toggle_time_format].
-command_relevant_toggles(deep_cmd_modules) =
+command_relevant_toggles(deep_cmd_program_modules) =
     [toggle_fields, toggle_box, toggle_colour, toggle_order_criteria,
     toggle_time_format, toggle_inactive_modules].
 command_relevant_toggles(deep_cmd_module(_)) =
@@ -1270,11 +1290,11 @@
     toggle_time_format, toggle_inactive_procs].
 command_relevant_toggles(deep_cmd_top_procs(_, _, _, _)) =
     [toggle_fields, toggle_box, toggle_colour, toggle_time_format].
-command_relevant_toggles(deep_cmd_proc_static(_)) = [].
-command_relevant_toggles(deep_cmd_proc_dynamic(_)) = [].
-command_relevant_toggles(deep_cmd_call_site_static(_)) = [].
-command_relevant_toggles(deep_cmd_call_site_dynamic(_)) = [].
-command_relevant_toggles(deep_cmd_raw_clique(_)) = [].
+command_relevant_toggles(deep_cmd_dump_proc_static(_)) = [].
+command_relevant_toggles(deep_cmd_dump_proc_dynamic(_)) = [].
+command_relevant_toggles(deep_cmd_dump_call_site_static(_)) = [].
+command_relevant_toggles(deep_cmd_dump_call_site_dynamic(_)) = [].
+command_relevant_toggles(deep_cmd_dump_clique(_)) = [].
 
 :- func footer_field_toggle(cmd, preferences, deep) = string.
 
@@ -1613,12 +1633,12 @@
 
 footer_contour_toggle(Cmd, Pref, Deep) = HTML :-
     (
-        Pref ^ pref_contour = no_contour,
-        Pref1 = Pref ^ pref_contour := apply_contour,
+        Pref ^ pref_contour = do_not_apply_contour_exclusion,
+        Pref1 = Pref ^ pref_contour := apply_contour_exclusion,
         Msg1 = "[Apply contour exclusion]"
     ;
-        Pref ^ pref_contour = apply_contour,
-        Pref1 = Pref ^ pref_contour := no_contour,
+        Pref ^ pref_contour = apply_contour_exclusion,
+        Pref1 = Pref ^ pref_contour := do_not_apply_contour_exclusion,
         Msg1 = "[Don't apply contour exclusion]"
     ),
     HTML = string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
@@ -3070,8 +3090,7 @@
     ).
 
 proc_static_to_html_ref(Pref, Deep, PSPtr) = HTML :-
-    PSPtr = proc_static_ptr(PSI),
-    URL = deep_cmd_pref_to_url(Pref, Deep, deep_cmd_proc(PSI)),
+    URL = deep_cmd_pref_to_url(Pref, Deep, deep_cmd_proc(PSPtr)),
     deep_lookup_proc_statics(Deep, PSPtr, PS),
     ProcName = PS ^ ps_refined_id,
     HTML = string.format("<A HREF=""%s"">%s</A>",
@@ -3083,8 +3102,7 @@
         [s(URL), s(escape_break_html_string(ModuleName))]).
 
 clique_ptr_to_html_ref(Pref, Deep, ProcName, CliquePtr) = HTML :-
-    CliquePtr = clique_ptr(CliqueNum),
-    URL = deep_cmd_pref_to_url(Pref, Deep, deep_cmd_clique(CliqueNum)),
+    URL = deep_cmd_pref_to_url(Pref, Deep, deep_cmd_clique(CliquePtr)),
     HTML = string.format("<A HREF=""%s"">%s</A>",
         [s(URL), s(escape_break_html_string(ProcName))]).
 
Index: mdprof_cgi.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/mdprof_cgi.m,v
retrieving revision 1.24
diff -u -b -r1.24 mdprof_cgi.m
--- mdprof_cgi.m	18 Aug 2008 02:14:51 -0000	1.24
+++ mdprof_cgi.m	25 Aug 2008 04:12:29 -0000
@@ -883,11 +883,11 @@
     ( Root = yes ->
         Cmd = deep_cmd_root(no)
     ; Modules = yes ->
-        Cmd = deep_cmd_modules
+        Cmd = deep_cmd_program_modules
     ; CliqueNum > 0 ->
-        Cmd = deep_cmd_clique(CliqueNum)
+        Cmd = deep_cmd_clique(clique_ptr(CliqueNum))
     ; ProcNum > 0 ->
-        Cmd = deep_cmd_proc(ProcNum)
+        Cmd = deep_cmd_proc(proc_static_ptr(ProcNum))
     ; Quit = yes ->
         Cmd = deep_cmd_quit
     ;
Index: mdprof_test.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/mdprof_test.m,v
retrieving revision 1.17
diff -u -b -r1.17 mdprof_test.m
--- mdprof_test.m	4 Aug 2008 03:17:45 -0000	1.17
+++ mdprof_test.m	19 Aug 2008 11:04:45 -0000
@@ -232,7 +232,7 @@
 
 test_cliques(Cur, Max, DirName, Pref, Deep, !IO) :-
     ( Cur =< Max ->
-        try_exec(deep_cmd_clique(Cur), Pref, Deep, HTML, !IO),
+        try_exec(deep_cmd_clique(clique_ptr(Cur)), Pref, Deep, HTML, !IO),
         write_test_html(DirName, "clique", Cur, HTML, !IO),
         test_cliques(Cur + 1, Max, DirName, Pref, Deep, !IO)
     ;
@@ -244,7 +244,7 @@
 
 test_procs(Cur, Max, DirName, Pref, Deep, !IO) :-
     ( Cur =< Max ->
-        try_exec(deep_cmd_proc(Cur), Pref, Deep, HTML, !IO),
+        try_exec(deep_cmd_proc(proc_static_ptr(Cur)), Pref, Deep, HTML, !IO),
         write_test_html(DirName, "proc", Cur, HTML, !IO),
         test_procs(Cur + 1, Max, DirName, Pref, Deep, !IO)
     ;
Index: measurements.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/measurements.m,v
retrieving revision 1.12
diff -u -b -r1.12 measurements.m
--- measurements.m	12 Oct 2006 06:30:22 -0000	1.12
+++ measurements.m	21 Aug 2008 13:43:09 -0000
@@ -70,11 +70,15 @@
 
 :- func own_to_string(own_prof_info) = string.
 
-    % Tests if this profiling information represents an entity in the
-    % program that was inactive during the profiling run, e.g. a module
-    % or procedure that has had no calls made to it.
+:- type is_active
+    --->    is_active
+    ;       is_not_active.
+
+    % Tests if this profiling information represents an entity in the program
+    % that was inactive during the profiling run, e.g. a module or procedure
+    % that has had no calls made to it.
     %
-:- pred is_inactive(own_prof_info::in) is semidet.
+:- func compute_is_active(own_prof_info) = is_active.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -388,10 +392,18 @@
     string.int_to_string(CallSeqs) ++
     ")".
 
-is_inactive(own_prof_all(0, 0, 0, 0, _, _, _, _)).
-is_inactive(own_prof_det(0, _, _, _, _)).
-is_inactive(own_prof_fast_det(0, _, _, _)).
-is_inactive(own_prof_fast_nomem_semi(0, 0, _)).
+compute_is_active(Own) = IsActive :-
+    (
+        ( Own = own_prof_all(0, 0, 0, 0, _, _, _, _)
+        ; Own = own_prof_det(0, _, _, _, _)
+        ; Own = own_prof_fast_det(0, _, _, _)
+        ; Own = own_prof_fast_nomem_semi(0, 0, _)
+        )
+    ->
+        IsActive = is_not_active
+    ;
+        IsActive = is_active
+    ).
 
 %----------------------------------------------------------------------------%
 :- end_module measurements.
Index: profile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/profile.m,v
retrieving revision 1.21
diff -u -b -r1.21 profile.m
--- profile.m	18 Aug 2008 02:14:51 -0000	1.21
+++ profile.m	21 Aug 2008 13:42:46 -0000
@@ -23,6 +23,7 @@
 :- module profile.
 :- interface.
 
+:- import_module exclude.
 :- import_module measurements.
 :- import_module mdbcomp.
 :- import_module mdbcomp.program_representation.
@@ -115,7 +116,15 @@
                 csd_comp_table          :: array(compensation_table),
 
                 % Information about modules.
-                module_data             :: map(string, module_data)
+                module_data             :: map(string, module_data),
+
+                % If this field is `no', then there is no (readable) contour
+                % exclusion file. If this field is yes(MaybeExcludeFile),
+                % then there are again two possibilities. The normal case is
+                % MaybeExcludeFile = ok(ExcludeFile). The other case is
+                % MaybeExcludeFile = error(ErrorMsg), which shows that the
+                % contour exclusion file was malformed.
+                exclude_contour_file    :: maybe(maybe_error(exclude_file))
             ).
 
 :- type compensation_table == map(proc_static_ptr, inherit_prof_info).
@@ -246,15 +255,18 @@
     %
 :- type coverage_point
     --->    coverage_point(
-                int,
                     % The number of times execution reached this point,
-                goal_path,
-                    % Identifies the goal that this coverage point is near.  If
-                    % cp_type is cp_type_branch_arm the coverage point is
+                int,
+
+                % Identifies the goal that this coverage point is near.
+                % If cp_type is cp_type_branch_arm the coverage point is
                     % immediately before this goal, otherwise it is immediately
                     % after.
-                cp_type
+
+                goal_path,
+
                     % The type of this coverage point.
+                cp_type
             ).
 
 :- pred is_call_site_kind(int::in, call_site_kind::out) is semidet.
Index: query.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/query.m,v
retrieving revision 1.26
diff -u -b -r1.26 query.m
--- query.m	18 Aug 2008 02:14:51 -0000	1.26
+++ query.m	25 Aug 2008 04:09:46 -0000
@@ -51,24 +51,56 @@
 :- type cmd
     --->    deep_cmd_quit
     ;       deep_cmd_restart
-    ;       deep_cmd_timeout(int)
+    ;       deep_cmd_timeout(
+                cmd_timeout_minutes         :: int
+            )
     ;       deep_cmd_menu
-    ;       deep_cmd_root(maybe(int))
-    ;       deep_cmd_clique(int)
-    ;       deep_cmd_proc(int)
-    ;       deep_cmd_proc_callers(int, caller_groups, int)
-    ;       deep_cmd_modules
-    ;       deep_cmd_module(string)
-    ;       deep_cmd_top_procs(display_limit, cost_kind, include_descendants,
-                measurement_scope)
+    ;       deep_cmd_root(
+                % If set to yes(Action), chase the dominant call sites
+                % until we get to a clique that is responsible for less than
+                % or equal to Action percent of the program's total callseqs.
+                cmd_root_maybe_action       :: maybe(int)
+            )
+    ;       deep_cmd_clique(
+                cmd_clique_clique_id        :: clique_ptr
+            )
+    ;       deep_cmd_proc(
+                cmd_proc_proc_id            :: proc_static_ptr
+            )
+    ;       deep_cmd_proc_callers(
+                cmd_pc_proc_id              :: proc_static_ptr,
+                cmd_pc_called_groups        :: caller_groups,
+                cmd_pc_bunch_number         :: int,
+                cmd_pc_contour_exclusion    :: contour_exclusion
+            )
+    ;       deep_cmd_program_modules
+    ;       deep_cmd_module(
+                cmd_module_module_name      :: string
+            )
+    ;       deep_cmd_top_procs(
+                cmd_tp_display_limit        :: display_limit,
+                cmd_tp_sort_cost_kind       :: cost_kind,
+                cmd_tp_incl_desc            :: include_descendants,
+                cmd_tp_scope                :: measurement_scope
+            )
 
     % The following commands are for debugging.
 
-    ;       deep_cmd_proc_static(int)
-    ;       deep_cmd_proc_dynamic(int)
-    ;       deep_cmd_call_site_static(int)
-    ;       deep_cmd_call_site_dynamic(int)
-    ;       deep_cmd_raw_clique(int).
+    ;       deep_cmd_dump_proc_static(
+                cmd_dps_id                  :: proc_static_ptr
+            )
+    ;       deep_cmd_dump_proc_dynamic(
+                cmd_dpd_id                  :: proc_dynamic_ptr
+            )
+    ;       deep_cmd_dump_call_site_static(
+                cmd_dcss_id                 :: call_site_static_ptr
+            )
+    ;       deep_cmd_dump_call_site_dynamic(
+                cmd_dcsd_id                 :: call_site_dynamic_ptr
+            )
+    ;       deep_cmd_dump_clique(
+                cmd_dcl_id                  :: clique_ptr
+            ).
 
 :- type caller_groups
     --->    group_by_call_site
@@ -88,6 +120,10 @@
     --->    self
     ;       self_and_desc.
 
+:- type descendants_meaningful
+    --->    descendants_meaningful
+    ;       descendants_not_meaningful.
+
 :- type display_limit
     --->    rank_range(int, int)
             % rank_range(M, N): display procedures with rank M to N,
@@ -127,8 +163,15 @@
                 % doesn't specify otherwise.
                 pref_criteria       :: order_criteria,
 
-                % Whether contour exclusion should be applied.
-                pref_contour        :: contour,
+                % Whether contour exclusion should be applied. The commands
+                % that depend on this setting take a contour value as an
+                % argument that will override this setting. However, we do not
+                % want to require users to restate their preferences about
+                % contour exclusion over and over again, so we store their
+                % preference here. A link from a page for which contour
+                % exclusion is irrelevant to a page for which it is relevant
+                % can pick up the preferred value of this parameter from here.
+                pref_contour        :: contour_exclusion,
 
                 pref_time           :: time_format,
 
@@ -198,9 +241,9 @@
     --->    per_call
     ;       overall.
 
-:- type contour
-    --->    apply_contour
-    ;       no_contour.
+:- type contour_exclusion
+    --->    apply_contour_exclusion
+    ;       do_not_apply_contour_exclusion.
 
 :- type time_format
     --->    no_scale
@@ -237,7 +280,7 @@
 :- func default_cost_kind = cost_kind.
 :- func default_incl_desc = include_descendants.
 :- func default_scope = measurement_scope.
-:- func default_contour = contour.
+:- func default_contour_exclusion = contour_exclusion.
 :- func default_time_format = time_format.
 :- func default_inactive_items = inactive_items.
 
@@ -254,6 +297,7 @@
 
 :- implementation.
 
+:- import_module apply_exclusion.
 :- import_module create_report.
 :- import_module display_report.
 :- import_module exclude.
@@ -334,12 +378,15 @@
         ; Cmd = deep_cmd_restart
         ; Cmd = deep_cmd_timeout(_)
         ; Cmd = deep_cmd_menu
+        ; Cmd = deep_cmd_program_modules
+        ; Cmd = deep_cmd_module(_)
         ; Cmd = deep_cmd_top_procs(_, _, _, _)
         ; Cmd = deep_cmd_proc(_)
-        ; Cmd = deep_cmd_proc_static(_)
-        ; Cmd = deep_cmd_proc_dynamic(_)
-        ; Cmd = deep_cmd_call_site_static(_)
-        ; Cmd = deep_cmd_call_site_dynamic(_)
+        ; Cmd = deep_cmd_proc_callers(_, _, _, _)
+        ; Cmd = deep_cmd_dump_proc_static(_)
+        ; Cmd = deep_cmd_dump_proc_dynamic(_)
+        ; Cmd = deep_cmd_dump_call_site_static(_)
+        ; Cmd = deep_cmd_dump_call_site_dynamic(_)
         ),
         (
             FileExists = yes,
@@ -350,18 +397,11 @@
             Display = report_to_display(Deep, Prefs, Report),
             HTML = htmlize_display(Deep, Prefs, Display),
             HTMLStr = html_to_string(HTML)
-            % ZZZ
-            % io.write_string("<!--\n", !IO),
-            % io.write(Display, !IO),
-            % io.write_string("-->\n", !IO)
         )
     ;
         ( Cmd = deep_cmd_root(_)
         ; Cmd = deep_cmd_clique(_)
-        ; Cmd = deep_cmd_proc_callers(_, _, _)
-        ; Cmd = deep_cmd_modules
-        ; Cmd = deep_cmd_module(_)
-        ; Cmd = deep_cmd_raw_clique(_)
+        ; Cmd = deep_cmd_dump_clique(_)
         ),
         old_exec(Cmd, Prefs, Deep, HTMLStr, !IO)
     ).
@@ -388,17 +428,16 @@
     Cmd = deep_cmd_top_procs(Limit, CostKind, InclDesc, Scope),
     HTML = generate_top_procs_page(Cmd, Limit, CostKind, InclDesc, Scope,
         Pref, Deep).
-old_exec(deep_cmd_proc_static(PSI), _Pref, Deep, HTML, !IO) :-
-    HTML = generate_proc_static_debug_page(PSI, Deep).
-old_exec(deep_cmd_proc_dynamic(PDI), _Pref, Deep, HTML, !IO) :-
-    HTML = generate_proc_dynamic_debug_page(PDI, Deep).
-old_exec(deep_cmd_call_site_static(CSSI), _Pref, Deep, HTML, !IO) :-
-    HTML = generate_call_site_static_debug_page(CSSI, Deep).
-old_exec(deep_cmd_call_site_dynamic(CSDI), _Pref, Deep, HTML, !IO) :-
-    HTML = generate_call_site_dynamic_debug_page(CSDI, Deep).
+old_exec(deep_cmd_dump_proc_static(PSPtr), _Pref, Deep, HTML, !IO) :-
+    HTML = generate_proc_static_debug_page(PSPtr, Deep).
+old_exec(deep_cmd_dump_proc_dynamic(PDPtr), _Pref, Deep, HTML, !IO) :-
+    HTML = generate_proc_dynamic_debug_page(PDPtr, Deep).
+old_exec(deep_cmd_dump_call_site_static(CSSPtr), _Pref, Deep, HTML, !IO) :-
+    HTML = generate_call_site_static_debug_page(CSSPtr, Deep).
+old_exec(deep_cmd_dump_call_site_dynamic(CSDPtr), _Pref, Deep, HTML, !IO) :-
+    HTML = generate_call_site_dynamic_debug_page(CSDPtr, Deep).
 old_exec(Cmd, Pref, Deep, HTML, !IO) :-
-    Cmd = deep_cmd_proc(PSI),
-    PSPtr = proc_static_ptr(PSI),
+    Cmd = deep_cmd_proc(PSPtr),
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         HTML = generate_proc_page(Cmd, PSPtr, Pref, Deep)
     ;
@@ -410,28 +449,26 @@
 old_exec(Cmd, Pref, Deep, HTML, !IO) :-
     Cmd = deep_cmd_root(MaybePercent),
     deep_lookup_clique_index(Deep, Deep ^ root, RootCliquePtr),
-    RootCliquePtr = clique_ptr(RootCliqueNum),
     (
         MaybePercent = yes(Percent),
-        HTML = chase_the_action(Cmd, RootCliqueNum, Pref, Deep, Percent)
+        HTML = chase_the_action(Cmd, RootCliquePtr, Pref, Deep, Percent)
     ;
         MaybePercent = no,
-        generate_clique_page(Cmd, RootCliqueNum, Pref, Deep, HTML, 100, _)
+        generate_clique_page(Cmd, RootCliquePtr, Pref, Deep, HTML, 100, _)
     ).
 old_exec(Cmd, Pref, Deep, HTML, !IO) :-
-    Cmd = deep_cmd_clique(CliqueNum),
-    CliquePtr = clique_ptr(CliqueNum),
+    Cmd = deep_cmd_clique(CliquePtr),
     ( valid_clique_ptr(Deep, CliquePtr) ->
-        generate_clique_page(Cmd, CliqueNum, Pref, Deep, HTML, 100, _)
+        generate_clique_page(Cmd, CliquePtr, Pref, Deep, HTML, 100, _)
     ;
         HTML =
             page_banner(Cmd, Pref) ++
             "There is no clique with that number.\n" ++
             page_footer(Cmd, Pref, Deep)
     ).
-old_exec(Cmd, Pref, Deep, HTML, !IO) :-
-    Cmd = deep_cmd_proc_callers(PSI, CallerGroups, BunchNum),
-    PSPtr = proc_static_ptr(PSI),
+old_exec(Cmd, Pref0, Deep, HTML, !IO) :-
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum, Contour),
+    Pref = Pref0 ^ pref_contour := Contour,
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         generate_proc_callers_page(Cmd, PSPtr, CallerGroups, BunchNum,
             Pref, Deep, HTML, !IO)
@@ -442,7 +479,7 @@
             page_footer(Cmd, Pref, Deep)
     ).
 old_exec(Cmd, Pref, Deep, HTML, !IO) :-
-    Cmd = deep_cmd_modules,
+    Cmd = deep_cmd_program_modules,
     HTML = generate_modules_page(Cmd, Pref, Deep).
 old_exec(Cmd, Pref, Deep, HTML, !IO) :-
     Cmd = deep_cmd_module(ModuleName),
@@ -454,15 +491,14 @@
             "There is no procedure with that number.\n" ++
             page_footer(Cmd, Pref, Deep)
     ).
-old_exec(deep_cmd_raw_clique(CI), _Pref, Deep, HTML, !IO) :-
-    HTML = generate_clique_debug_page(CI, Deep).
+old_exec(deep_cmd_dump_clique(CliquePtr), _Pref, Deep, HTML, !IO) :-
+    HTML = generate_clique_debug_page(CliquePtr, Deep).
 
 %-----------------------------------------------------------------------------%
 
-:- func generate_proc_static_debug_page(int, deep) = string.
+:- func generate_proc_static_debug_page(proc_static_ptr, deep) = string.
 
-generate_proc_static_debug_page(PSI, Deep) = HTML :-
-    PSPtr = proc_static_ptr(PSI),
+generate_proc_static_debug_page(PSPtr, Deep) = HTML :-
     ( valid_proc_static_ptr(Deep, PSPtr) ->
         deep_lookup_proc_statics(Deep, PSPtr, PS),
         Refined = PS ^ ps_refined_id,
@@ -480,10 +516,9 @@
             "</HTML>\n"
     ).
 
-:- func generate_proc_dynamic_debug_page(int, deep) = string.
+:- func generate_proc_dynamic_debug_page(proc_dynamic_ptr, deep) = string.
 
-generate_proc_dynamic_debug_page(PDI, Deep) = HTML :-
-    PDPtr = proc_dynamic_ptr(PDI),
+generate_proc_dynamic_debug_page(PDPtr, Deep) = HTML :-
     ( valid_proc_dynamic_ptr(Deep, PDPtr) ->
         deep_lookup_proc_dynamics(Deep, PDPtr, PD),
         PSPtr = PD ^ pd_proc_static,
@@ -500,10 +535,10 @@
             "</HTML>\n"
     ).
 
-:- func generate_call_site_static_debug_page(int, deep) = string.
+:- func generate_call_site_static_debug_page(call_site_static_ptr, deep)
+    = string.
 
-generate_call_site_static_debug_page(CSSI, Deep) = HTML :-
-    CSSPtr = call_site_static_ptr(CSSI),
+generate_call_site_static_debug_page(CSSPtr, Deep) = HTML :-
     ( valid_call_site_static_ptr(Deep, CSSPtr) ->
         deep_lookup_call_site_statics(Deep, CSSPtr, CSS),
         ContainerPtr = CSS ^ css_container,
@@ -523,10 +558,10 @@
             "</HTML>\n"
     ).
 
-:- func generate_call_site_dynamic_debug_page(int, deep) = string.
+:- func generate_call_site_dynamic_debug_page(call_site_dynamic_ptr, deep)
+    = string.
 
-generate_call_site_dynamic_debug_page(CSDI, Deep) = HTML :-
-    CSDPtr = call_site_dynamic_ptr(CSDI),
+generate_call_site_dynamic_debug_page(CSDPtr, Deep) = HTML :-
     ( valid_call_site_dynamic_ptr(Deep, CSDPtr) ->
         deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
         CSD ^ csd_caller = proc_dynamic_ptr(CallerPDI),
@@ -544,14 +579,13 @@
             "</HTML>\n"
     ).
 
-:- func generate_clique_debug_page(int, deep) = string.
+:- func generate_clique_debug_page(clique_ptr, deep) = string.
 
-generate_clique_debug_page(CI, Deep) = HTML :-
-    CliquePtr = clique_ptr(CI),
+generate_clique_debug_page(CliquePtr, Deep) = HTML :-
     ( valid_clique_ptr(Deep, CliquePtr) ->
-        deep_lookup_clique_parents(Deep, CliquePtr, Parent),
-        Parent = call_site_dynamic_ptr(ParentPDI),
-        ParentStr = string.format("%d ->", [i(ParentPDI)]),
+        deep_lookup_clique_parents(Deep, CliquePtr, ParentCSDPtr),
+        ParentCSDPtr = call_site_dynamic_ptr(ParentCSDI),
+        ParentStr = string.format("%d ->", [i(ParentCSDI)]),
         deep_lookup_clique_members(Deep, CliquePtr, Members),
         HTML =
             "<HTML>\n" ++
@@ -645,7 +679,7 @@
         menu_item(Deep, Pref, deep_cmd_root(yes(90)),
             "Exploring the call graph, starting at the action.") ++
         "<li>\n" ++
-        menu_item(Deep, Pref, deep_cmd_modules,
+        menu_item(Deep, Pref, deep_cmd_program_modules,
             "Exploring the program module by module.") ++
         ( ShouldDisplayTimes = yes ->
             "<li>\n" ++
@@ -798,31 +832,31 @@
 
 %-----------------------------------------------------------------------------%
 
-:- func chase_the_action(cmd, int, preferences, deep, int) = string.
+:- func chase_the_action(cmd, clique_ptr, preferences, deep, int) = string.
 
-chase_the_action(Cmd, CliqueNum, Pref, Deep, Percent) = HTML :-
-    generate_clique_page(Cmd, CliqueNum, Pref, Deep, HTML0,
+chase_the_action(Cmd, CliquePtr, Pref, Deep, Percent) = HTML :-
+    generate_clique_page(Cmd, CliquePtr, Pref, Deep, HTML0,
         Percent, ActionPtrs),
-    ( ActionPtrs = [clique_ptr(ActionCliqueNum)] ->
-        HTML = chase_the_action(Cmd, ActionCliqueNum, Pref, Deep, Percent)
+    ( ActionPtrs = [ActionCliquePtr] ->
+        HTML = chase_the_action(Cmd, ActionCliquePtr, Pref, Deep, Percent)
     ;
         HTML = HTML0
     ).
 
 %-----------------------------------------------------------------------------%
 
-:- pred generate_clique_page(cmd::in, int::in, preferences::in, deep::in,
-    string::out, int::in, list(clique_ptr)::out) is det.
+:- pred generate_clique_page(cmd::in, clique_ptr::in, preferences::in,
+    deep::in, string::out, int::in, list(clique_ptr)::out) is det.
 
-generate_clique_page(Cmd, CliqueNum, Pref, Deep, HTML, Percent, ActionPtrs) :-
-    clique_to_html(Pref, Deep, clique_ptr(CliqueNum), CliqueHTML, Percent,
-        ActionPtrs),
+generate_clique_page(Cmd, CliquePtr, Pref, Deep, HTML, Percent, ActionPtrs) :-
+    clique_to_html(Pref, Deep, CliquePtr, CliqueHTML, Percent, ActionPtrs),
+    CliquePtr = clique_ptr(CliqueNum),
     HTML =
         page_banner(Cmd, Pref) ++
         string.format("<H3>Clique %d:</H3>\n", [i(CliqueNum)]) ++
         table_start(Pref) ++
         fields_header(Pref, source_proc, totals_meaningful,
-            wrap_clique_links(clique_ptr(CliqueNum), Pref, Deep)) ++
+            wrap_clique_links(CliquePtr, Pref, Deep)) ++
         CliqueHTML ++
         table_end(Pref) ++
         page_footer(Cmd, Pref, Deep).
@@ -1005,7 +1039,7 @@
     ModuleData = module_data(Own, Desc, _),
     not (
         Pref ^ pref_inactive ^ inactive_modules = inactive_hide,
-        is_inactive(Own)
+        compute_is_active(Own) = is_not_active
     ),
     HTML = string.format("<TD><A HREF=""%s"">%s</A></TD>\n",
         [s(deep_cmd_pref_to_url(Pref, Deep, deep_cmd_module(ModuleName))),
@@ -1248,7 +1282,7 @@
     deep_lookup_ps_own(Deep, PSPtr, Own),
     not (
         Pref ^ pref_inactive ^ inactive_procs = inactive_hide,
-        is_inactive(Own)
+        compute_is_active(Own) = is_not_active
     ),
     deep_lookup_ps_desc(Deep, PSPtr, Desc),
     LineGroup = proc_total_to_html(Pref, Deep, Bold, Prefix, PSPtr, Own, Desc).
@@ -1711,9 +1745,8 @@
         CallSiteDisplay ^ display_url = callee_clique,
         ChosenCliquePtr = CalleeCliquePtr
     ),
-    ChosenCliquePtr = clique_ptr(ChosenCliqueNum),
     WrappedProcName = string.format("<A HREF=""%s"">%s</A>",
-        [s(deep_cmd_pref_to_url(Pref, Deep, deep_cmd_clique(ChosenCliqueNum))),
+        [s(deep_cmd_pref_to_url(Pref, Deep, deep_cmd_clique(ChosenCliquePtr))),
         s(escape_break_html_string(ProcName))]),
     (
         CallSiteDisplay ^ display_wrap = wrap_url_always,
@@ -1776,31 +1809,43 @@
 proc_callers_to_html(Pref, Deep, PSPtr, CallerGroups, BunchNum0, MaybePage,
         !IO) :-
     deep_lookup_proc_callers(Deep, PSPtr, CallerCSDPtrs),
+    PrefContour = Pref ^ pref_contour,
+    (
+        PrefContour = do_not_apply_contour_exclusion,
+        CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs),
+        MaybeErrorMsg = no
+    ;
+        PrefContour = apply_contour_exclusion,
+        MaybeMaybeExcludeFile = Deep ^ exclude_contour_file,
     (
-        Pref ^ pref_contour = no_contour,
+            MaybeMaybeExcludeFile = no,
+            % There is no contour exclusion file, so do the same as for
+            % do_not_apply_contour_exclusion.
         CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs),
         MaybeErrorMsg = no
     ;
-        Pref ^ pref_contour = apply_contour,
-        read_exclude_file(contour_file_name(Deep ^ data_file_name),
-            Deep, Result, !IO),
+            MaybeMaybeExcludeFile = yes(MaybeExcludeFile),
         (
-            Result = ok(ExcludeSpec),
+                MaybeExcludeFile = ok(ExcludeSpec),
             CallerCSDPtrPairs = list.map(pair_contour(Deep, ExcludeSpec),
                 CallerCSDPtrs),
             MaybeErrorMsg = no
         ;
-            Result = error(ErrorMsg),
+                MaybeExcludeFile = error(ErrorMsg),
             MaybeErrorMsg = yes(ErrorMsg ++ "\n<br>"),
             CallerCSDPtrPairs = list.map(pair_self, CallerCSDPtrs)
         )
+        )
     ),
     ProcName = proc_static_name(Deep, PSPtr),
-    PSPtr = proc_static_ptr(PSI),
-    CmdSite    = deep_cmd_proc_callers(PSI, group_by_call_site, 1),
-    CmdProc    = deep_cmd_proc_callers(PSI, group_by_proc, 1),
-    CmdModule  = deep_cmd_proc_callers(PSI, group_by_module, 1),
-    CmdClique  = deep_cmd_proc_callers(PSI, group_by_clique, 1),
+    CmdSite    = deep_cmd_proc_callers(PSPtr, group_by_call_site, 1,
+        PrefContour),
+    CmdProc    = deep_cmd_proc_callers(PSPtr, group_by_proc, 1,
+        PrefContour),
+    CmdModule  = deep_cmd_proc_callers(PSPtr, group_by_module, 1,
+        PrefContour),
+    CmdClique  = deep_cmd_proc_callers(PSPtr, group_by_clique, 1,
+        PrefContour),
     LinkSite   = "[Group callers by call site]",
     LinkProc   = "[Group callers by procedure]",
     LinkModule = "[Group callers by module]",
@@ -1810,9 +1855,7 @@
     BunchSize = 100,
     (
         CallerGroups = group_by_call_site,
-        GroupMap = list.foldl(accumulate_csds_by_call_site(Deep),
-            CallerCSDPtrPairs, map.init),
-        map.to_assoc_list(GroupMap, GroupList),
+        GroupList = group_csds_by_call_site(Deep, CallerCSDPtrPairs),
         Lines = list.map(proc_callers_call_site_to_html(Pref, Deep, PSPtr),
             GroupList),
         SortedLines = sort_line_groups(Pref ^ pref_criteria, Lines),
@@ -1830,9 +1873,7 @@
                 s(LinkClique)])
     ;
         CallerGroups = group_by_proc,
-        GroupMap = list.foldl(accumulate_csds_by_procedure(Deep),
-            CallerCSDPtrPairs, map.init),
-        map.to_assoc_list(GroupMap, GroupList),
+        GroupList = group_csds_by_procedure(Deep, CallerCSDPtrPairs),
         Lines = list.map(proc_callers_proc_to_html(Pref, Deep, PSPtr),
             GroupList),
         SortedLines = sort_line_groups(Pref ^ pref_criteria, Lines),
@@ -1850,9 +1891,7 @@
                 s(LinkClique)])
     ;
         CallerGroups = group_by_module,
-        GroupMap = list.foldl(accumulate_csds_by_module(Deep),
-            CallerCSDPtrPairs, map.init),
-        map.to_assoc_list(GroupMap, GroupList),
+        GroupList = group_csds_by_module(Deep, CallerCSDPtrPairs),
         RawLines = list.map(proc_callers_module_to_html(Pref, Deep, PSPtr),
             GroupList),
         SortedRawLines = sort_line_groups(Pref ^ pref_criteria, RawLines),
@@ -1871,9 +1910,7 @@
                 s(LinkClique)])
     ;
         CallerGroups = group_by_clique,
-        GroupMap = list.foldl(accumulate_csds_by_clique(Deep),
-            CallerCSDPtrPairs, map.init),
-        map.to_assoc_list(GroupMap, GroupList),
+        GroupList = group_csds_by_clique(Deep, CallerCSDPtrPairs),
         RawLines = list.map(proc_callers_clique_to_html(Pref, Deep, PSPtr),
             GroupList),
         SortedRawLines = sort_line_groups(Pref ^ pref_criteria, RawLines),
@@ -1898,14 +1935,14 @@
     list.length(SortedLines, NumLines),
     select_line_bunch(NumLines, BunchNum0, BunchNum, BunchSize,
         SortedLines, DisplayedLines),
-    Banner = proc_callers_banner(PSI, ProcName, Pref, Deep,
+    Banner = proc_callers_banner(PSPtr, ProcName, Pref, Deep,
         NumLines, BunchSize, BunchNum, Entity),
     DisplayedHTMLs = list.map(
         two_id_line_to_html(Pref, Deep, totals_meaningful),
         DisplayedLines),
     HTML = string.append_list(DisplayedHTMLs),
     ( BunchNum > 1 ->
-        FirstCmd = deep_cmd_proc_callers(PSI, CallerGroups, 1),
+        FirstCmd = deep_cmd_proc_callers(PSPtr, CallerGroups, 1, PrefContour),
         FirstLink = "First group",
         FirstToggle =
             string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
@@ -1914,7 +1951,8 @@
         FirstToggle = ""
     ),
     ( BunchNum > 2 ->
-        PrevCmd = deep_cmd_proc_callers(PSI, CallerGroups, BunchNum - 1),
+        PrevCmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum - 1,
+            PrefContour),
         PrevLink = "Previous group",
         PrevToggle =
             string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
@@ -1923,7 +1961,8 @@
         PrevToggle = ""
     ),
     ( NumLines > BunchNum * BunchSize ->
-        NextCmd = deep_cmd_proc_callers(PSI, CallerGroups, BunchNum + 1),
+        NextCmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum + 1,
+            PrefContour),
         NextLink = "Next group",
         NextToggle =
             string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
@@ -1964,12 +2003,12 @@
         DisplayedLines = RemainingLines
     ).
 
-:- func proc_callers_banner(int, string, preferences, deep, int, int, int,
-    string) = string.
+:- func proc_callers_banner(proc_static_ptr, string, preferences, deep,
+    int, int, int, string) = string.
 
-proc_callers_banner(PSI, ProcName, Pref, Deep, NumLines, BunchSize, BunchNum,
+proc_callers_banner(PSPtr, ProcName, Pref, Deep, NumLines, BunchSize, BunchNum,
         Parent) = HTML :-
-    Cmd = deep_cmd_proc(PSI),
+    Cmd = deep_cmd_proc(PSPtr),
     WrappedProcName = string.format("<A HREF=""%s"">%s</A>",
         [s(deep_cmd_pref_to_url(Pref, Deep, Cmd)),
             s(escape_break_html_string(ProcName))]),
@@ -2009,8 +2048,7 @@
     CallerPSPtr = CSS ^ css_container,
     deep_lookup_proc_statics(Deep, CallerPSPtr, CallerPS),
     CallerProcName = CallerPS ^ ps_refined_id,
-    list.foldl2(accumulate_parent_csd_prof_info(Deep, CalleePSPtr), CSDPtrs,
-        zero_own_prof_info, Own, zero_inherit_prof_info, Desc),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
     HTML =
         string.format("<TD CLASS=id>%s:%d</TD>\n",
             [s(escape_break_html_string(FileName)), i(LineNumber)]) ++
@@ -2027,8 +2065,7 @@
     proc_static_context(Deep, CallerPSPtr, FileName, LineNumber),
     deep_lookup_proc_statics(Deep, CallerPSPtr, CallerPS),
     CallerProcName = CallerPS ^ ps_refined_id,
-    list.foldl2(accumulate_parent_csd_prof_info(Deep, CalleePSPtr), CSDPtrs,
-        zero_own_prof_info, Own, zero_inherit_prof_info, Desc),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
     HTML =
         string.format("<TD CLASS=id>%s:%d</TD>\n",
             [s(escape_break_html_string(FileName)), i(LineNumber)]) ++
@@ -2042,8 +2079,7 @@
 
 proc_callers_module_to_html(Pref, Deep, CalleePSPtr, ModuleName - CSDPtrs)
         = LineGroup :-
-    list.foldl2(accumulate_parent_csd_prof_info(Deep, CalleePSPtr), CSDPtrs,
-        zero_own_prof_info, Own, zero_inherit_prof_info, Desc),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
     HTML = string.format("<TD CLASS=id>%s</TD>\n",
         [s(module_name_to_html_ref(Pref, Deep, ModuleName))]),
     % We don't have filename information for modules, and line numbers
@@ -2056,8 +2092,7 @@
 
 proc_callers_clique_to_html(Pref, Deep, CalleePSPtr, CliquePtr - CSDPtrs)
         = LineGroup :-
-    list.foldl2(accumulate_parent_csd_prof_info(Deep, CalleePSPtr), CSDPtrs,
-        zero_own_prof_info, Own, zero_inherit_prof_info, Desc),
+    compute_parent_csd_prof_info(Deep, CalleePSPtr, CSDPtrs, Own, Desc),
     deep_lookup_clique_parents(Deep, CliquePtr, EntryCSDPtr),
     deep_lookup_call_site_dynamics(Deep, EntryCSDPtr, EntryCSD),
     EntryPDPtr = EntryCSD ^ csd_callee,
@@ -2068,113 +2103,6 @@
     LineGroup = line_group(FileName, LineNumber, ProcName,
         Own, Desc, HTML, unit).
 
-:- func accumulate_csds_by_call_site(deep, pair(call_site_dynamic_ptr),
-    map(call_site_static_ptr, list(call_site_dynamic_ptr))) =
-    map(call_site_static_ptr, list(call_site_dynamic_ptr)).
-
-accumulate_csds_by_call_site(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
-    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
-    ( map.search(Map0, GroupCSSPtr, CostCSDPtrs0) ->
-        map.det_update(Map0, GroupCSSPtr, [CostCSDPtr | CostCSDPtrs0], Map)
-    ;
-        map.det_insert(Map0, GroupCSSPtr, [CostCSDPtr], Map)
-    ).
-
-:- func accumulate_csds_by_procedure(deep, pair(call_site_dynamic_ptr),
-    map(proc_static_ptr, list(call_site_dynamic_ptr))) =
-    map(proc_static_ptr, list(call_site_dynamic_ptr)).
-
-accumulate_csds_by_procedure(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
-    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
-    deep_lookup_call_site_statics(Deep, GroupCSSPtr, GroupCSS),
-    GroupPSPtr = GroupCSS ^ css_container,
-    ( map.search(Map0, GroupPSPtr, CostCSDPtrs0) ->
-        map.det_update(Map0, GroupPSPtr, [CostCSDPtr | CostCSDPtrs0], Map)
-    ;
-        map.det_insert(Map0, GroupPSPtr, [CostCSDPtr], Map)
-    ).
-
-:- func accumulate_csds_by_module(deep, pair(call_site_dynamic_ptr),
-    map(string, list(call_site_dynamic_ptr))) =
-    map(string, list(call_site_dynamic_ptr)).
-
-accumulate_csds_by_module(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
-    deep_lookup_call_site_static_map(Deep, GroupCSDPtr, GroupCSSPtr),
-    deep_lookup_call_site_statics(Deep, GroupCSSPtr, GroupCSS),
-    GroupPSPtr = GroupCSS ^ css_container,
-    deep_lookup_proc_statics(Deep, GroupPSPtr, GroupPS),
-    GroupModuleName = GroupPS ^ ps_decl_module,
-    ( map.search(Map0, GroupModuleName, CostCSDPtrs0) ->
-        map.det_update(Map0, GroupModuleName, [CostCSDPtr | CostCSDPtrs0], Map)
-    ;
-        map.det_insert(Map0, GroupModuleName, [CostCSDPtr], Map)
-    ).
-
-:- func accumulate_csds_by_clique(deep, pair(call_site_dynamic_ptr),
-    map(clique_ptr, list(call_site_dynamic_ptr))) =
-    map(clique_ptr, list(call_site_dynamic_ptr)).
-
-accumulate_csds_by_clique(Deep, GroupCSDPtr - CostCSDPtr, Map0) = Map :-
-    deep_lookup_call_site_dynamics(Deep, GroupCSDPtr, GroupCSD),
-    CallerPDPtr = GroupCSD ^ csd_caller,
-    deep_lookup_clique_index(Deep, CallerPDPtr, CliquePtr),
-    ( map.search(Map0, CliquePtr, CostCSDPtrs0) ->
-        map.det_update(Map0, CliquePtr, [CostCSDPtr | CostCSDPtrs0], Map)
-    ;
-        map.det_insert(Map0, CliquePtr, [CostCSDPtr], Map)
-    ).
-
-:- pred accumulate_parent_csd_prof_info(deep::in, proc_static_ptr::in,
-    call_site_dynamic_ptr::in,
-    own_prof_info::in, own_prof_info::out,
-    inherit_prof_info::in, inherit_prof_info::out) is det.
-
-accumulate_parent_csd_prof_info(Deep, CallerPSPtr, CSDPtr,
-        Own0, Own, Desc0, Desc) :-
-    deep_lookup_call_site_dynamics(Deep, CSDPtr, CSD),
-    ( CSD ^ csd_callee = CSD ^ csd_caller ->
-        % We want to sum only cross-clique callers.
-        Own = Own0,
-        Desc = Desc0
-    ;
-        deep_lookup_csd_own(Deep, CSDPtr, CSDOwn),
-        deep_lookup_csd_desc(Deep, CSDPtr, CSDDesc),
-        add_own_to_own(Own0, CSDOwn) = Own,
-        add_inherit_to_inherit(Desc0, CSDDesc) = Desc1,
-
-        deep_lookup_clique_index(Deep, CSD ^ csd_callee, CalleeCliquePtr),
-        deep_lookup_clique_members(Deep, CalleeCliquePtr, CalleeCliquePDPtrs),
-        list.foldl(compensate_using_comp_table(Deep, CallerPSPtr),
-            CalleeCliquePDPtrs, Desc1, Desc)
-    ).
-
-:- pred compensate_using_comp_table(deep::in, proc_static_ptr::in,
-    proc_dynamic_ptr::in, inherit_prof_info::in, inherit_prof_info::out)
-    is det.
-
-compensate_using_comp_table(Deep, CallerPSPtr, PDPtr, Desc0, Desc) :-
-    deep_lookup_pd_comp_table(Deep, PDPtr, CompTableArray),
-    ( map.search(CompTableArray, CallerPSPtr, InnerTotal) ->
-        Desc = subtract_inherit_from_inherit(InnerTotal, Desc0)
-    ;
-        Desc = Desc0
-    ).
-
-:- func pair_self(call_site_dynamic_ptr) = pair(call_site_dynamic_ptr).
-
-pair_self(CSDPtr) = CSDPtr - CSDPtr.
-
-:- func pair_contour(deep, exclude_file, call_site_dynamic_ptr)
-    = pair(call_site_dynamic_ptr).
-
-pair_contour(Deep, ExcludeSpec, CSDPtr) =
-    apply_contour_exclusion(Deep, ExcludeSpec, CSDPtr) - CSDPtr.
-
-:- func contour_file_name(string) = string.
-
-contour_file_name(DataFileName) =
-    DataFileName ++ ".contour".
-
 %-----------------------------------------------------------------------------%
 
 :- func proc_summary_to_html(preferences, deep, proc_static_ptr) = string.
@@ -2210,15 +2138,15 @@
     = string.
 
 proc_summary_toggles_to_html(Pref, Deep, PSPtr) = HTML :-
-    PSPtr = proc_static_ptr(PSI),
+    PrefContour = Pref ^ pref_contour,
     Msg1 = "[Parent call sites]",
-    Cmd1 = deep_cmd_proc_callers(PSI, group_by_call_site, 1),
+    Cmd1 = deep_cmd_proc_callers(PSPtr, group_by_call_site, 1, PrefContour),
     Msg2 = "[Parent procedures]",
-    Cmd2 = deep_cmd_proc_callers(PSI, group_by_proc, 1),
+    Cmd2 = deep_cmd_proc_callers(PSPtr, group_by_proc, 1, PrefContour),
     Msg3 = "[Parent modules]",
-    Cmd3 = deep_cmd_proc_callers(PSI, group_by_module, 1),
+    Cmd3 = deep_cmd_proc_callers(PSPtr, group_by_module, 1, PrefContour),
     Msg4 = "[Parent cliques]",
-    Cmd4 = deep_cmd_proc_callers(PSI, group_by_clique, 1),
+    Cmd4 = deep_cmd_proc_callers(PSPtr, group_by_clique, 1, PrefContour),
     Link1 = string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
         [s(deep_cmd_pref_to_url(Pref, Deep, Cmd1)), s(Msg1)]),
     Link2 = string.format("<A CLASS=""button"" HREF=""%s"">%s</A>\n",
@@ -2239,8 +2167,7 @@
     order_criteria) = string.
 
 wrap_clique_links(CliquePtr, Pref0, Deep, Str0, Criteria) = Str :-
-    CliquePtr = clique_ptr(CI),
-    Cmd = deep_cmd_clique(CI),
+    Cmd = deep_cmd_clique(CliquePtr),
     Pref = Pref0 ^ pref_criteria := Criteria,
     URL = deep_cmd_pref_to_url(Pref, Deep, Cmd),
     Str = string.format("<A HREF=%s>%s</A>",
@@ -2250,8 +2177,7 @@
     order_criteria) = string.
 
 wrap_proc_links(PSPtr, Pref0, Deep, Str0, Criteria) = Str :-
-    PSPtr = proc_static_ptr(PSI),
-    Cmd = deep_cmd_proc(PSI),
+    Cmd = deep_cmd_proc(PSPtr),
     Pref = Pref0 ^ pref_criteria := Criteria,
     URL = deep_cmd_pref_to_url(Pref, Deep, Cmd),
     Str = string.format("<A HREF=%s>%s</A>",
@@ -2262,8 +2188,8 @@
 
 wrap_proc_callers_links(PSPtr, CallerGroups, BunchNum, Pref0, Deep,
         Str0, Criteria) = Str :-
-    PSPtr = proc_static_ptr(PSI),
-    Cmd = deep_cmd_proc_callers(PSI, CallerGroups, BunchNum),
+    PrefContour = Pref0 ^ pref_contour,
+    Cmd = deep_cmd_proc_callers(PSPtr, CallerGroups, BunchNum, PrefContour),
     Pref = Pref0 ^ pref_criteria := Criteria,
     URL = deep_cmd_pref_to_url(Pref, Deep, Cmd),
     Str = string.format("<A HREF=%s>%s</A>",
@@ -2282,7 +2208,7 @@
 :- func wrap_modules_links(preferences, deep, string, order_criteria) = string.
 
 wrap_modules_links(Pref0, Deep, Str0, Criteria) = Str :-
-    Cmd = deep_cmd_modules,
+    Cmd = deep_cmd_program_modules,
     Pref = Pref0 ^ pref_criteria := Criteria,
     URL = deep_cmd_pref_to_url(Pref, Deep, Cmd),
     Str = string.format("<A HREF=%s>%s</A>",
@@ -2340,7 +2266,7 @@
         default_ancestor_limit,
         default_summarize,
         default_order_criteria,
-        default_contour,
+        default_contour_exclusion,
         default_time_format,
         default_inactive_items
     ).
@@ -2367,7 +2293,7 @@
 default_cost_kind = cost_callseqs.
 default_incl_desc = self_and_desc.
 default_scope = overall.
-default_contour = no_contour.
+default_contour_exclusion = do_not_apply_contour_exclusion.
 default_time_format = scale_by_thousands.
 default_inactive_items = inactive_items(inactive_hide, inactive_hide).
 
@@ -2414,23 +2340,28 @@
                 [c(cmd_separator_char), s("no")])
         )
     ;
-        Cmd = deep_cmd_clique(CliqueNum),
+        Cmd = deep_cmd_clique(CliquePtr),
+        CliquePtr = clique_ptr(CliqueNum),
         CmdStr = string.format("clique%c%d",
             [c(cmd_separator_char), i(CliqueNum)])
     ;
-        Cmd = deep_cmd_proc(ProcNum),
+        Cmd = deep_cmd_proc(PSPtr),
+        PSPtr = proc_static_ptr(PSI),
         CmdStr = string.format("proc%c%d",
-            [c(cmd_separator_char), i(ProcNum)])
+            [c(cmd_separator_char), i(PSI)])
     ;
-        Cmd = deep_cmd_proc_callers(ProcNum, GroupCallers, BunchNum),
+        Cmd = deep_cmd_proc_callers(PSPtr, GroupCallers, BunchNum, Contour),
+        PSPtr = proc_static_ptr(PSI),
         GroupCallersStr = caller_groups_to_string(GroupCallers),
-        CmdStr = string.format("proc_callers%c%d%c%s%c%d",
-            [c(cmd_separator_char), i(ProcNum),
+        ContourStr = contour_exclusion_to_string(Contour),
+        CmdStr = string.format("proc_callers%c%d%c%s%c%d%c%s",
+            [c(cmd_separator_char), i(PSI),
             c(cmd_separator_char), s(GroupCallersStr),
-            c(cmd_separator_char), i(BunchNum)])
+            c(cmd_separator_char), i(BunchNum),
+            c(cmd_separator_char), s(ContourStr)])
     ;
-        Cmd = deep_cmd_modules,
-        CmdStr = "modules"
+        Cmd = deep_cmd_program_modules,
+        CmdStr = "program_modules"
     ;
         Cmd = deep_cmd_module(ModuleName),
         CmdStr = string.format("module%c%s",
@@ -2447,25 +2378,30 @@
             c(cmd_separator_char), s(InclDescStr),
             c(cmd_separator_char), s(ScopeStr)])
     ;
-        Cmd = deep_cmd_proc_static(PSI),
-        CmdStr = string.format("proc_static%c%d",
+        Cmd = deep_cmd_dump_proc_static(PSPtr),
+        PSPtr = proc_static_ptr(PSI),
+        CmdStr = string.format("dump_proc_static%c%d",
             [c(cmd_separator_char), i(PSI)])
     ;
-        Cmd = deep_cmd_proc_dynamic(PDI),
-        CmdStr = string.format("proc_dynamic%c%d",
+        Cmd = deep_cmd_dump_proc_dynamic(PDPtr),
+        PDPtr = proc_dynamic_ptr(PDI),
+        CmdStr = string.format("dump_proc_dynamic%c%d",
             [c(cmd_separator_char), i(PDI)])
     ;
-        Cmd = deep_cmd_call_site_static(CSSI),
-        CmdStr = string.format("call_site_static%c%d",
+        Cmd = deep_cmd_dump_call_site_static(CSSPtr),
+        CSSPtr = call_site_static_ptr(CSSI),
+        CmdStr = string.format("dump_call_site_static%c%d",
             [c(cmd_separator_char), i(CSSI)])
     ;
-        Cmd = deep_cmd_call_site_dynamic(CSDI),
-        CmdStr = string.format("call_site_dynamic%c%d",
+        Cmd = deep_cmd_dump_call_site_dynamic(CSDPtr),
+        CSDPtr = call_site_dynamic_ptr(CSDI),
+        CmdStr = string.format("dump_call_site_dynamic%c%d",
             [c(cmd_separator_char), i(CSDI)])
     ;
-        Cmd = deep_cmd_raw_clique(CI),
-        CmdStr = string.format("raw_clique%c%d",
-            [c(cmd_separator_char), i(CI)])
+        Cmd = deep_cmd_dump_clique(CliquePtr),
+        CliquePtr = clique_ptr(CliqueNum),
+        CmdStr = string.format("dump_clique%c%d",
+            [c(cmd_separator_char), i(CliqueNum)])
     ).
 
 preferences_to_string(Pref) = PrefStr :-
@@ -2486,7 +2422,7 @@
         c(pref_separator_char), s(MaybeAncestorLimitStr),
         c(pref_separator_char), s(summarize_to_string(Summarize)),
         c(pref_separator_char), s(order_criteria_to_string(Order)),
-        c(pref_separator_char), s(contour_to_string(Contour)),
+        c(pref_separator_char), s(contour_exclusion_to_string(Contour)),
         c(pref_separator_char), s(time_format_to_string(Time)),
         c(pref_separator_char), s(inactive_items_to_string(InactiveItems))
     ]).
@@ -2512,32 +2448,43 @@
             fail
         )
     ->
-        MaybeCmd = yes(deep_cmd_root(MaybePercent))
+        Cmd = deep_cmd_root(MaybePercent),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["clique", CliqueNumStr],
         string.to_int(CliqueNumStr, CliqueNum)
     ->
-        MaybeCmd = yes(deep_cmd_clique(CliqueNum))
+        CliquePtr = clique_ptr(CliqueNum),
+        Cmd = deep_cmd_clique(CliquePtr),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["proc", PSIStr],
         string.to_int(PSIStr, PSI)
     ->
-        MaybeCmd = yes(deep_cmd_proc(PSI))
+        PSPtr = proc_static_ptr(PSI),
+        Cmd = deep_cmd_proc(PSPtr),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["proc_callers", PSIStr, GroupCallersStr, BunchNumStr],
+        Pieces = ["proc_callers", PSIStr, GroupCallersStr, BunchNumStr,
+            ContourStr],
         string.to_int(PSIStr, PSI),
+        string_to_caller_groups(GroupCallersStr, GroupCallers),
         string.to_int(BunchNumStr, BunchNum),
-        string_to_caller_groups(GroupCallersStr, GroupCallers)
+        string_to_contour_exclusion(ContourStr, Contour)
     ->
-        MaybeCmd = yes(deep_cmd_proc_callers(PSI, GroupCallers, BunchNum))
+        PSPtr = proc_static_ptr(PSI),
+        Cmd = deep_cmd_proc_callers(PSPtr, GroupCallers, BunchNum, Contour),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["modules"]
+        Pieces = ["program_modules"]
     ->
-        MaybeCmd = yes(deep_cmd_modules)
+        Cmd = deep_cmd_program_modules,
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["module", ModuleName]
     ->
-        MaybeCmd = yes(deep_cmd_module(ModuleName))
+        Cmd = deep_cmd_module(ModuleName),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["top_procs", LimitStr, CostKindStr, InclDescStr, ScopeStr],
         string_to_limit(LimitStr, Limit),
@@ -2545,49 +2492,64 @@
         string_to_incl_desc(InclDescStr, InclDesc),
         string_to_scope(ScopeStr, Scope)
     ->
-        MaybeCmd = yes(deep_cmd_top_procs(Limit, CostKind, InclDesc, Scope))
+        Cmd = deep_cmd_top_procs(Limit, CostKind, InclDesc, Scope),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["menu"]
     ->
-        MaybeCmd = yes(deep_cmd_menu)
+        Cmd = deep_cmd_menu,
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["proc_static", PSIStr],
+        Pieces = ["dump_proc_static", PSIStr],
         string.to_int(PSIStr, PSI)
     ->
-        MaybeCmd = yes(deep_cmd_proc_static(PSI))
+        PSPtr = proc_static_ptr(PSI),
+        Cmd = deep_cmd_dump_proc_static(PSPtr),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["proc_dynamic", PDIStr],
+        Pieces = ["dump_proc_dynamic", PDIStr],
         string.to_int(PDIStr, PDI)
     ->
-        MaybeCmd = yes(deep_cmd_proc_dynamic(PDI))
+        PDPtr = proc_dynamic_ptr(PDI),
+        Cmd = deep_cmd_dump_proc_dynamic(PDPtr),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["call_site_static", CSSIStr],
+        Pieces = ["dump_call_site_static", CSSIStr],
         string.to_int(CSSIStr, CSSI)
     ->
-        MaybeCmd = yes(deep_cmd_call_site_static(CSSI))
+        CSSPtr = call_site_static_ptr(CSSI),
+        Cmd = deep_cmd_dump_call_site_static(CSSPtr),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["call_site_dynamic", CSDIStr],
+        Pieces = ["dump_call_site_dynamic", CSDIStr],
         string.to_int(CSDIStr, CSDI)
     ->
-        MaybeCmd = yes(deep_cmd_call_site_dynamic(CSDI))
+        CSDPtr = call_site_dynamic_ptr(CSDI),
+        Cmd = deep_cmd_dump_call_site_dynamic(CSDPtr),
+        MaybeCmd = yes(Cmd)
     ;
-        Pieces = ["raw_clique", CliqueNumStr],
+        Pieces = ["dump_clique", CliqueNumStr],
         string.to_int(CliqueNumStr, CliqueNum)
     ->
-        MaybeCmd = yes(deep_cmd_raw_clique(CliqueNum))
+        CliquePtr = clique_ptr(CliqueNum),
+        Cmd = deep_cmd_dump_clique(CliquePtr),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["timeout", TimeOutStr],
         string.to_int(TimeOutStr, TimeOut)
     ->
-        MaybeCmd = yes(deep_cmd_timeout(TimeOut))
+        Cmd = deep_cmd_timeout(TimeOut),
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["restart"]
     ->
-        MaybeCmd = yes(deep_cmd_restart)
+        Cmd = deep_cmd_restart,
+        MaybeCmd = yes(Cmd)
     ;
         Pieces = ["quit"]
     ->
-        MaybeCmd = yes(deep_cmd_quit)
+        Cmd = deep_cmd_quit,
+        MaybeCmd = yes(Cmd)
     ;
         MaybeCmd = no
     ).
@@ -2609,7 +2571,7 @@
         ),
         string_to_summarize(SummarizeStr, Summarize),
         string_to_order_criteria(OrderStr, Order),
-        string_to_contour(ContourStr, Contour),
+        string_to_contour_exclusion(ContourStr, Contour),
         string_to_time_format(TimeStr, Time),
         string_to_inactive_items(InactiveItemsStr, InactiveItems)
     ->
@@ -2854,17 +2816,17 @@
 string_to_scope("pc", per_call).
 string_to_scope("oa",  overall).
 
-:- func contour_to_string(contour) = string.
+:- func contour_exclusion_to_string(contour_exclusion) = string.
 
-contour_to_string(Contour) = String :-
-    string_to_contour(String, Contour).
+contour_exclusion_to_string(Contour) = String :-
+    string_to_contour_exclusion(String, Contour).
 
-:- pred string_to_contour(string, contour).
-:- mode string_to_contour(in, out) is semidet.
-:- mode string_to_contour(out, in) is det.
+:- pred string_to_contour_exclusion(string, contour_exclusion).
+:- mode string_to_contour_exclusion(in, out) is semidet.
+:- mode string_to_contour_exclusion(out, in) is det.
 
-string_to_contour("ac", apply_contour).
-string_to_contour("nc", no_contour).
+string_to_contour_exclusion("ac", apply_contour_exclusion).
+string_to_contour_exclusion("nc", do_not_apply_contour_exclusion).
 
 :- func time_format_to_string(time_format) = string.
 
Index: report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/report.m,v
retrieving revision 1.6
diff -u -b -r1.6 report.m
--- report.m	18 Aug 2008 02:14:52 -0000	1.6
+++ report.m	25 Aug 2008 04:45:35 -0000
@@ -36,8 +36,11 @@
 :- type deep_report
     --->    report_message(message_report)
     ;       report_menu(maybe_error(menu_report))
+    ;       report_program_modules(maybe_error(program_modules_report))
+    ;       report_module(maybe_error(module_report))
     ;       report_top_procs(maybe_error(top_procs_report))
     ;       report_proc(maybe_error(proc_report))
+    ;       report_proc_callers(maybe_error(proc_callers_report))
     ;       report_proc_static_dump(maybe_error(proc_static_dump_info))
     ;       report_proc_dynamic_dump(maybe_error(proc_dynamic_dump_info))
     ;       report_call_site_static_dump(
@@ -72,6 +75,21 @@
                 menu_num_clique             :: int
             ).
 
+:- type program_modules_report
+    --->    program_modules_report(
+                % Summary information about all the modules of the program.
+                program_modules             :: list(
+                                                perf_row_data(module_active))
+            ).
+
+:- type module_report
+    --->    module_report(
+                % Summary information about all the procedures in one module
+                % of the program.
+                mr_module_name              :: string,
+                mr_procs                    :: list(perf_row_data(proc_active))
+            ).
+
 :- type top_procs_report
     --->    top_procs_report(
                 % Information about the most expensive procedures. The ordering
@@ -86,7 +104,6 @@
     --->    proc_report(
                 % The proc description is inside the proc_summary field.
 
-                proc_psptr                  :: proc_static_ptr,
                 proc_summary                :: perf_row_data(proc_desc),
                 proc_call_site_summaries    :: list(call_site_perf)
             ).
@@ -122,6 +139,45 @@
                 nci_type_subst              :: string
             ).
 
+:- type proc_callers_report
+    --->    proc_callers_report(
+                % The id of the procedure.
+                pc_proc_desc                :: proc_desc,
+
+                % The call sites that call this procedure.
+                pc_callers                  :: proc_callers,
+
+                % Which batch of rows to show; transmitted without processing
+                % from the request.
+                pc_batch_number             :: int,
+
+                % Whether contour exclusion was applied in computing the
+                % pc_callers field.
+                pc_contour_exclusion        :: contour_exclusion,
+
+                % If contour exclusion was asked for, this field may contain
+                % the pieces of an error message.
+                pc_contour_error_messages   :: list(string)
+            ).
+
+:- type proc_callers
+    --->    proc_caller_call_sites(
+                pc_caller_call_sites        :: list(
+                                                perf_row_data(call_site_desc))
+            )
+    ;       proc_caller_procedures(
+                pc_caller_procedures        :: list(
+                                                perf_row_data(proc_desc))
+            )
+    ;       proc_caller_modules(
+                pc_caller_modules           :: list(
+                                                perf_row_data(string))
+            )
+    ;       proc_caller_cliques(
+                pc_caller_cliques           :: list(
+                                                perf_row_data(clique_desc))
+            ).
+
 :- type proc_static_dump_info
     --->    proc_static_dump_info(
                 psdi_psptr                  :: proc_static_ptr,
@@ -172,51 +228,42 @@
                 perf_row_redos                  :: int,
                 perf_row_excps                  :: int,
 
+                perf_row_bytes_per_word         :: int,
+                perf_row_self                   :: inheritable_perf,
+                perf_row_maybe_total            :: maybe(inheritable_perf)
+            ).
+
+:- type inheritable_perf
+    --->    inheritable_perf(
                 % Clock ticks and times. We always use simple integers to
                 % represent clock ticks, whereas for time, we use more
                 % user-friendly units. When the total time for the program
-                % is close to zero, the percentage may be NaN representing
-                % 'not_applicable' or 'do not know'.
-                perf_row_self_ticks             :: int,
-                perf_row_self_time              :: time,
-                perf_row_self_time_percent      :: percent,
-                perf_row_self_time_percall      :: time,
-
-                perf_row_total_ticks            :: int,
-                perf_row_total_time             :: time,
-                perf_row_total_time_percent     :: percent,
-                perf_row_total_time_percall     :: time,
+                % is close to zero, i.e. the number of ticks or quanta is zero
+                % for the whole programs, then the percentage may be zero
+                % for everyhing (it used to be a NaN for 0/0, but we now
+                % check explicitly for division by zero).
+                perf_row_ticks             :: int,
+                perf_row_time              :: time,
+                perf_row_time_percent      :: percent,
+                perf_row_time_percall      :: time,
 
                 % Call sequence counts.
-                perf_row_self_callseqs          :: int,
-                perf_row_self_callseqs_percent  :: percent,
-                perf_row_self_callseqs_percall  :: float,
-
-                perf_row_total_callseqs         :: int,
-                perf_row_total_callseqs_percent :: percent,
-                perf_row_total_callseqs_percall :: float,
+                perf_row_callseqs          :: int,
+                perf_row_callseqs_percent  :: percent,
+                perf_row_callseqs_percall  :: float,
 
                 % Memory allocations.
-                perf_row_self_allocs            :: int,
-                perf_row_self_allocs_percent    :: percent,
-                perf_row_self_allocs_percall    :: float,
-
-                perf_row_total_allocs           :: int,
-                perf_row_total_allocs_percent   :: percent,
-                perf_row_total_allocs_percall   :: float,
+                perf_row_allocs            :: int,
+                perf_row_allocs_percent    :: percent,
+                perf_row_allocs_percall    :: float,
 
                 % Memory used. We try to use the most appropriate units
                 % for representing each given amount of memory.
                 % XXX Memory per call might not be an integer, so we should
                 % make sure that the memory type can represent fractions.
-                perf_row_bytes_per_word         :: int,
-                perf_row_self_mem               :: memory,
-                perf_row_self_mem_percent       :: percent,
-                perf_row_self_mem_percall       :: memory,
-
-                perf_row_total_mem              :: memory,
-                perf_row_total_mem_percent      :: percent,
-                perf_row_total_mem_percall      :: memory
+                perf_row_mem               :: memory,
+                perf_row_mem_percent       :: percent,
+                perf_row_mem_percall       :: memory
             ).
 
     % This type is used to define 'most expensive procedures'. It contains all
@@ -232,15 +279,37 @@
                 scope                       :: measurement_scope
             ).
 
+    % The representation of a module in a report structure.
+    %
+:- type module_active
+    --->    module_active(
+                ma_module_name              :: string,
+                ma_is_active                :: module_is_active
+            ).
+
+:- type module_is_active
+    --->    module_is_active
+    ;       module_is_not_active.
+
+:- type proc_active
+    --->    proc_active(
+                pa_proc_desc                :: proc_desc,
+                pa_is_active                :: proc_is_active
+            ).
+
+:- type proc_is_active
+    --->    proc_is_active
+    ;       proc_is_not_active.
+
     % The representation of a procedure in a report structure, including
     % information about its location in Mercury source code.
     %
 :- type proc_desc
     --->    proc_desc(
-                proc_desc_static_ptr        :: proc_static_ptr,
-                proc_desc_file_name         :: string,
-                proc_desc_line_number       :: int,
-                proc_desc_refined_name      :: string
+                pdesc_ps_ptr                :: proc_static_ptr,
+                pdesc_file_name             :: string,
+                pdesc_line_number           :: int,
+                pdesc_refined_name          :: string
             ).
 
     % The representation of a call site in a report structure, including
@@ -248,13 +317,21 @@
     %
 :- type call_site_desc
     --->    call_site_desc(
-                call_site_desc_static_ptr   :: call_site_static_ptr,
-                call_site_desc_container    :: proc_static_ptr,
-                call_site_desc_file_name    :: string,
-                call_site_desc_line_number  :: int,
-                call_site_desc_refined_name :: string,
-                call_site_desc_slot_number  :: int,
-                call_site_desc_goal_path    :: string
+                csdesc_css_ptr              :: call_site_static_ptr,
+                csdesc_container            :: proc_static_ptr,
+                csdesc_file_name            :: string,
+                csdesc_line_number          :: int,
+                csdesc_caller_refined_name  :: string,
+                csdesc_slot_number          :: int,
+                csdesc_goal_path            :: string
+            ).
+
+    % The description of a clique in a report structure.
+    %
+:- type clique_desc
+    --->    clique_desc(
+                cdesc_clique_ptr            :: clique_ptr,
+                cdesc_members               :: list(proc_desc)
             ).
 
 %-----------------------------------------------------------------------------%
Index: startup.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/startup.m,v
retrieving revision 1.20
diff -u -b -r1.20 startup.m
--- startup.m	18 Aug 2008 02:14:52 -0000	1.20
+++ startup.m	19 Aug 2008 05:47:05 -0000
@@ -45,6 +45,7 @@
 :- import_module array_util.
 :- import_module callgraph.
 :- import_module canonical.
+:- import_module exclude.
 :- import_module measurements.
 :- import_module profile.
 :- import_module read_profile.
@@ -100,7 +101,7 @@
     initial_deep::in, deep::out, io::di, io::uo) is det.
 
 startup(Machine, ScriptName, DataFileName, Canonical, MaybeOutputStream,
-        DumpStages, DumpOptions, InitDeep0, Deep, !IO) :-
+        DumpStages, DumpOptions, InitDeep0, !:Deep, !IO) :-
     InitDeep0 = initial_deep(InitStats, Root,
         CallSiteDynamics0, ProcDynamics, CallSiteStatics0, ProcStatics0),
     maybe_dump(DataFileName, DumpStages, 0,
@@ -229,36 +230,48 @@
     array.init(NCSDs, map.init, CSDCompTable0),
 
     ModuleData = map.map_values(initialize_module_data, ModuleProcs),
-    Deep0 = deep(InitStats, Machine, ScriptName, DataFileName, Root,
+    % The field holding DummyExcludeError is given its proper, non-dummy value
+    % a few calls below.
+    DummyMaybeExcludeFile = no,
+    !:Deep = deep(InitStats, Machine, ScriptName, DataFileName, Root,
         CallSiteDynamics, ProcDynamics, CallSiteStatics, ProcStatics,
         CliqueIndex, Cliques, CliqueParents, CliqueMaybeChildren,
         ProcCallers, CallSiteStaticMap, CallSiteCalls,
         PDOwn, PDDesc0, CSDDesc0,
         PSOwn0, PSDesc0, CSSOwn0, CSSDesc0,
-        PDCompTable0, CSDCompTable0, ModuleData),
+        PDCompTable0, CSDCompTable0, ModuleData, DummyMaybeExcludeFile),
+
+    read_exclude_file(contour_file_name(DataFileName), !.Deep,
+        MaybeMaybeExcludeFile, !IO),
+    !Deep ^ exclude_contour_file := MaybeMaybeExcludeFile,
 
     maybe_dump(DataFileName, DumpStages, 30,
-        dump_deep(Deep0, DumpOptions), !IO),
+        dump_deep(!.Deep, DumpOptions), !IO),
 
-    array_foldl_from_1(propagate_to_clique, Cliques, Deep0, Deep1),
+    array_foldl_from_1(propagate_to_clique, Cliques, !Deep),
     maybe_report_msg(MaybeOutputStream,
         "% Done.\n", !IO),
     maybe_report_stats(MaybeOutputStream, !IO),
 
     maybe_dump(DataFileName, DumpStages, 40,
-        dump_deep(Deep1, DumpOptions), !IO),
+        dump_deep(!.Deep, DumpOptions), !IO),
 
     maybe_report_msg(MaybeOutputStream,
         "% Summarizing information...\n", !IO),
-    summarize_proc_dynamics(Deep1, Deep2),
-    summarize_call_site_dynamics(Deep2, Deep3),
-    summarize_modules(Deep3, Deep),
+    summarize_proc_dynamics(!Deep),
+    summarize_call_site_dynamics(!Deep),
+    summarize_modules(!Deep),
     maybe_report_msg(MaybeOutputStream,
         "% Done.\n", !IO),
     maybe_report_stats(MaybeOutputStream, !IO),
 
     maybe_dump(DataFileName, DumpStages, 50,
-        dump_deep(Deep, DumpOptions), !IO).
+        dump_deep(!.Deep, DumpOptions), !IO).
+
+:- func contour_file_name(string) = string.
+
+contour_file_name(DataFileName) =
+    DataFileName ++ ".contour".
 
 :- pred count_quanta(int::in, call_site_dynamic::in, int::in, int::out) is det.
 
cvs diff: Diffing notes
--------------------------------------------------------------------------
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