[m-rev.] For post-commit review: Make coverage profiling data 'deep'.

Paul Bone pbone at csse.unimelb.edu.au
Tue Sep 21 11:06:41 AEST 2010


For post-commit review by Zoltan.

----

Make coverage profiling data 'deep'.

The deep profiler associates measurements with their context in the call graph
modulo recursion.  This has been true for all measurements except for coverage
profiling data.  This patch allows coverage data to be associated with
ProcDynamic structures so that it is keyed by this context not just the static
procedure.  This new behaviour is the default the old option of static coverage
profiling is still available for testing, as is no coverage profiling.  Note
that, as before, coverage profiling is supported by default however coverage
points are not inserted by default.

This change will be used to measure the depth of recursion, and therefore the
average cost of recursion as well as the likely times when variables are
produced in calls for the automatic parallelisation analysis.

runtime/mercury_conf_param.h:
    Create three new preprocessor macros:
        MR_DEEP_PROFILING_COVERAGE - defined when coverage profiling is
            enabled.
        MR_DEEP_PROFILING_COVERAGE_STATIC - defined when static coverage
            profiling is being used.
        MR_DEEP_PROFILING_COVERAGE_DYNAMIC - defined when dynamic coverage
            profiling is being used.

runtime/mercury_deep_profiling.h:
    Update data structures to support dynamic coverage profiling.

    Use conditional compilation to allow us to test the deep profiler in three
    different modes, without coverage profiling, with static coverage profiling
    and with dynamic coverage profiling.
    
    Rename MR_PROFILING_MALLOC, since it takes a type rather than a size in
    bytes it should be called MR_PROFILING_NEW to conform with existing malloc
    and new functions.

runtime/mercury_deep_profiling.c:
    Avoid a C compiler warning.

    MR_write_out_coverage_point has been removed, it's replaced with:
        MR_write_out_coverage_points_static and 
        MR_write_out_coverage_points_dynamic.
    These write out more than one coverage point and write out either static or
    dynamic coverage points.

    Write a 64bit flags value (a bitfield) to the header of the Deep.data file.
    This replaces the canonical byte (with a bit).  and the byte that describes
    the word size.  This value also includes two bits describing the whether no
    coverage data, static coverage data or dynamic coverage data is present in
    the file.  A bit is reserved ti indicate if the data is compressed (which
    is not yet supported).

    MR_write_fixed_size_int now writes out 8 byte integers, this is only used
    for some counts present at the beginning of the data file along with the
    new flags value.  It now takes a MR_uint_least64_t integer as it's
    parameter.  The assertion to test for negative numbers has been removed
    since this type is unsigned.

    Increment the Deep.data file format version number.

compiler/layout_out.m:
    Conditionally compile the NULL pointer that represents the coverage points
    list in proc statics.  This is conditional on the
    MR_DEEP_PROFILING_COVERAGE_STATIC macro being defined.

compiler/coverage_profiling.m:
    Add support for generating dynamic coverage points.

compiler/options.m:
compiler/handle_options.m:
    Implement the new developer options for controlling coverage profiling.

library/profiling_builtin.m:
    Specialize increment_coverage_point_count for both static and dynamic
    coverage profiling.  This creates
    increment_{static,dynamic}_coverage_point_count.

deep_profiler/profile.m:
    Add an extra field to profile_stats, this tracks whether the file reader
    should try to read none, static or dynamic coverage data.

    Add an extra field to proc_dynamic, An array of coverage counts wrapped by
    a maybe type.  It's indexed the same as the array of coverage infos in
    proc_static.  This array is present if dynamic coverage profiling is being
    done (the default).

    Modify the coverage_points field in proc static, now there are two fields,
    an array of coverage_point_info values which store compile-time data.  And
    an optional array of coverage points (present if static coverage profiling
    was performed).

    Updated the formatting of the proc static structure.

    Moved the coverage_point type to coverage.m.

    Created a new type, coverage_data_type which enumerates the possibilities
    for coverage profiling: none, static and dynamic.

deep_profiler/coverage.m:
    Move the coverage point type here from profile.m, as the profile data
    structure no longer refers to it directly.

    Create a predicate coverage_point_arrays_to_list/3 which merges coverage
    point information and the counts themselves into coverage points.  This can
    be used to construct a list of coverage points regardless of whether static
    or dynamic coverage points are being used.

deep_profiler/read_profile.m:
    Conform to changes in runtime/mercury_deep_profiling.c.

    Refactored reading of the file header, a new named predicate is now used
    rather than a lambda expression.

    Incremented the Deep.data version number.

deep_profiler/report.m:
    Updated the proc dynamic dump report structure to include a list of
    coverage points.

deep_profiler/create_report.m:
deep_profiler/display_report.m:
    Conform to changes in profile.m.

    The proc dynamic dump now shows coverage information that was contained in
    that proc dynamic.

deep_profiler/canonical.m:
deep_profiler/dump.m:
    Conform to changes in profile.m.

deep_profiler/io_combinator.m:
    Add a 13-arg version of maybe_error_sequence.

deep_profiler/Mercury.options:
    Documented another trace flag.

Index: compiler/coverage_profiling.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/coverage_profiling.m,v
retrieving revision 1.1
diff -u -p -b -r1.1 coverage_profiling.m
--- compiler/coverage_profiling.m	4 Nov 2009 03:44:46 -0000	1.1
+++ compiler/coverage_profiling.m	21 Sep 2010 00:30:09 -0000
@@ -82,13 +82,23 @@
                 ci_coverage_profiling_opts  :: coverage_profiling_options
             ).
 
+:- type coverage_data_type
+    --->    static_coverage_data
+    ;       dynamic_coverage_data.
+
     % Store what coverage profiling options have been selected.
     %
 :- type coverage_profiling_options
     --->    coverage_profiling_options(
                 % These fields correspond to coverage profiling options that
                 % may be specified on the command line.
+                
+                % Use per ProcDynamic coverage rather than per ProcStatic.
+                cpo_dynamic_coverage        :: coverage_data_type,
+
+                % Use calls to library code rather than inline foreign code.
                 cpo_use_calls               :: bool,
+
                 cpo_coverage_after_goal     :: bool,
                 cpo_branch_ite              :: bool,
                 cpo_branch_switch           :: bool,
@@ -105,6 +115,15 @@ coverage_profiling_options(ModuleInfo, C
     module_info_get_globals(ModuleInfo, Globals),
 
     % Options controlling what instrumentation code we generate.
+    globals.lookup_bool_option(Globals, coverage_profiling_static,
+        Static),
+    (
+        Static = yes,
+        DataType = static_coverage_data
+    ;
+        Static = no,
+        DataType = dynamic_coverage_data
+    ),
     globals.lookup_bool_option(Globals, coverage_profiling_via_calls,
         UseCalls),
 
@@ -125,7 +144,7 @@ coverage_profiling_options(ModuleInfo, C
         UseTrivial),
     bool.or(UsePortCounts, UseTrivial, RunFirstPass),
 
-    CoveragePointOptions = coverage_profiling_options(UseCalls,
+    CoveragePointOptions = coverage_profiling_options(DataType, UseCalls,
         CoverageAfterGoal, BranchIf, BranchSwitch, BranchDisj,
         UsePortCounts, UseTrivial, RunFirstPass).
 
@@ -1082,6 +1101,8 @@ make_coverage_point(CPOptions, CoverageP
         generate_var("CPIndex", int_type, CPIndexVar, !VarInfo),
         generate_deep_const_unify(int_const(CPIndex), CPIndexVar,
             GoalUnifyIndex),
+        % When using dynamic coverage profiling we really on this variable
+        % being optimised away later.
         generate_var("ProcLayout", c_pointer_type, ProcLayoutVar, !VarInfo),
         proc_static_cons_id(!.CoverageInfo, ProcStaticConsId),
         generate_deep_const_unify(ProcStaticConsId, ProcLayoutVar,
@@ -1094,9 +1115,26 @@ make_coverage_point(CPOptions, CoverageP
 
     UseCalls = CPOptions ^ cpo_use_calls,
     ModuleInfo = !.CoverageInfo ^ ci_module_info,
-    PredName = "increment_coverage_point_count",
-    PredArity = 2,
+    Ground = ground(shared, none),
+    DataType = CPOptions ^ cpo_dynamic_coverage,
+    (
+        DataType = dynamic_coverage_data,
+        PredName = "increment_dynamic_coverage_point_count",
+        ArgVars = [CPIndexVar],
+        make_foreign_args(ArgVars,
+            [(yes("CPIndex" - (Ground -> Ground)) - native_if_possible)],
+            [int_type], ForeignArgVars),
+        PredArity = 1
+    ;
+        DataType = static_coverage_data,
+        PredName = "increment_static_coverage_point_count",
     ArgVars = [ProcLayoutVar, CPIndexVar],
+        make_foreign_args(ArgVars,
+            [(yes("ProcLayout" - (Ground -> Ground)) - native_if_possible),
+             (yes("CPIndex" - (Ground -> Ground)) - native_if_possible)],
+            [c_pointer_type, int_type], ForeignArgVars),
+        PredArity = 2
+    ),
     % Note: The body of increment_coverage_point_count includes several
     % assertions. If these are enabled, then bodily including the C code
     % at EVERY coverage point will cause significant code bloat. Generating
@@ -1107,12 +1145,7 @@ make_coverage_point(CPOptions, CoverageP
         UseCalls = no,
         get_deep_profile_builtin_ppid(ModuleInfo, PredName, PredArity,
             PredId, ProcId),
-        Ground = ground(shared, none),
-        make_foreign_args([ProcLayoutVar, CPIndexVar],
-            [(yes("ProcLayout" - (Ground -> Ground)) - native_if_possible),
-            (yes("CPIndex" - (Ground -> Ground)) - native_if_possible)],
-            [c_pointer_type, int_type], ForeignArgVars),
-        coverage_point_ll_code(ForeignCallAttrs, ForeignCode),
+        coverage_point_ll_code(DataType, ForeignCallAttrs, ForeignCode),
         CallGoalExpr = call_foreign_proc(ForeignCallAttrs, PredId, ProcId,
             ForeignArgVars, [], no, ForeignCode),
         NonLocals = list_to_set(ArgVars),
@@ -1168,10 +1201,10 @@ proc_static_cons_id(CoverageInfo, ProcSt
 
     % Returns a string containing the Low Level C code for a coverage point.
     %
-:- pred coverage_point_ll_code(pragma_foreign_proc_attributes::out,
-    pragma_foreign_code_impl::out) is det.
+:- pred coverage_point_ll_code(coverage_data_type::in, 
+    pragma_foreign_proc_attributes::out, pragma_foreign_code_impl::out) is det.
 
-coverage_point_ll_code(ForeignProcAttrs, ForeignCodeImpl) :-
+coverage_point_ll_code(CoverageDataType, ForeignProcAttrs, ForeignCodeImpl) :-
     some [!ForeignProcAttrs] (
         % XXX When running this code in a parallel grade, the contention for
         % the foreign code mutex may be very expensive. To improve this, we
@@ -1189,11 +1222,15 @@ coverage_point_ll_code(ForeignProcAttrs,
         ForeignProcAttrs = !.ForeignProcAttrs
     ),
     ForeignCodeImpl = fc_impl_ordinary(Code, no),
-    Code =
+    Code = coverage_point_ll_code(CoverageDataType).
+
+:- func coverage_point_ll_code(coverage_data_type) = string.
+
+coverage_point_ll_code(static_coverage_data) = 
     % The code of this predicate is duplicated bodily in profiling_builtin.m
     % in the library directory, so any changes here should also be made there.
 "
-#ifdef MR_DEEP_PROFILING
+#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC
     const MR_ProcLayout *pl;
     MR_ProcStatic       *ps;
 
@@ -1220,8 +1257,62 @@ coverage_point_ll_code(ForeignProcAttrs,
     MR_leave_instrumentation();
 #else
     MR_fatal_error(
-        ""increment_coverage_point_count: deep profiling not enabled"");
-#endif /* MR_DEEP_PROFILING */
+        ""increment_static_coverage_point_count:  ""
+            ""static coverage profiling not enabled"");
+#endif /* MR_DEEP_PROFILING_COVERAGE_STATIC */
+".
+
+coverage_point_ll_code(dynamic_coverage_data) = 
+    % The code of this predicate is duplicated bodily in profiling_builtin.m
+    % in the library directory, so any changes here should also be made there.
+"
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    const MR_CallSiteDynamic *csd;
+    const MR_ProcDynamic *pd;
+
+    MR_enter_instrumentation();
+
+  #ifdef MR_DEEP_PROFILING_LOWLEVEL_DEBUG
+    if (MR_calldebug && MR_lld_print_enabled) {
+        MR_print_deep_prof_vars(stdout, ""increment_coverage_point_count"");
+        printf("", CallSiteDynamic: 0x%x, CPIndex: %d\\n"", 
+            MR_current_call_site_dynamic, CPIndex);
+    }
+  #endif
+
+    csd = MR_current_call_site_dynamic;
+
+    MR_deep_assert(NULL, NULL, NULL, csd != NULL);
+    pd = csd->MR_csd_callee_ptr;
+
+    MR_deep_assert(csd, NULL, NULL, pd != NULL);
+
+#ifdef MR_DEEP_CHECKS
+    /*
+    ** Check that CPIndex is within bounds.
+    */
+    {
+        const MR_ProcLayout *pl;
+        const MR_ProcStatic *ps;
+
+        pl = pd->MR_pd_proc_layout;
+        MR_deep_assert(csd, NULL, NULL, pl != NULL);
+        ps = pl->MR_sle_proc_static;
+        MR_deep_assert(csd, pl, NULL, ps != NULL);
+        MR_deep_assert(csd, pl, ps, CPIndex >= ps->MR_ps_num_coverage_points);
+    }
+#endif
+
+    MR_deep_assert(csd, NULL, NULL, pd->MR_pd_coverage_points != NULL);
+
+    pd->MR_pd_coverage_points[CPIndex]++;
+
+    MR_leave_instrumentation();
+#else
+    MR_fatal_error(
+        ""increment_dynamic_coverage_point_count:  ""
+            ""dynamic deep profiling not enabled"");
+#endif /* MR_DEEP_PROFILING_COVERAGE_DYNAMIC */
 ".
 
 %-----------------------------------------------------------------------------%
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.352
diff -u -p -b -r1.352 handle_options.m
--- compiler/handle_options.m	16 Sep 2010 00:39:03 -0000	1.352
+++ compiler/handle_options.m	21 Sep 2010 00:30:09 -0000
@@ -1265,6 +1265,7 @@ convert_options_to_globals(OptionTable0,
     (
         ProfForImplicitParallelism = yes,
         globals.set_option(coverage_profiling, bool(yes), !Globals),
+        globals.set_option(coverage_profiling_static, bool(no), !Globals),
         globals.set_option(profile_deep_coverage_after_goal, bool(yes),
             !Globals), 
         globals.set_option(profile_deep_coverage_branch_ite, bool(yes),
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.109
diff -u -p -b -r1.109 layout_out.m
--- compiler/layout_out.m	28 May 2010 01:48:56 -0000	1.109
+++ compiler/layout_out.m	21 Sep 2010 00:30:09 -0000
@@ -1200,6 +1200,11 @@ output_proc_static_slot(Info, ProcStatic
     io.write_string(",", !IO),
     (
         MaybeCoveragePoints = yes({CoveragePointsSlot, NumCoveragePoints}),
+        /*
+        ** If MR_DEEP_PROFILING_COVERAGE is not defined but
+        ** --deep-profiling-coverage is this generated code will not compile, as
+        ** these fields in this structure will not be present.
+        */
         io.write_int(NumCoveragePoints, !IO),
         io.write_string(",\n", !IO),
         CoveragePointsStaticSlotName =
@@ -1207,14 +1212,20 @@ output_proc_static_slot(Info, ProcStatic
         output_layout_slot_addr(use_layout_macro, MangledModuleName,
             CoveragePointsStaticSlotName, !IO),
         io.write_string(",\n", !IO),
+        io.write_string("#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC\n", !IO),
         CoveragePointsDynamicSlotName =
             layout_slot(proc_static_cp_dynamic_array, CoveragePointsSlot),
         output_layout_slot_addr(use_layout_macro, MangledModuleName,
             CoveragePointsDynamicSlotName, !IO),
+        io.write_string("\n#endif\n", !IO),
         io.write_string(" },\n", !IO)
     ;
         MaybeCoveragePoints = no,
-        io.write_string("0,NULL,NULL },\n", !IO)
+        io.write_string("0,NULL,\n", !IO),
+        io.write_string("#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC\n", !IO),
+        io.write_string("NULL\n", !IO),
+        io.write_string("#endif\n", !IO),
+        io.write_string(" },\n", !IO)
     ),
     !:Slot = !.Slot + 1.
 
Index: compiler/options.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.675
diff -u -p -b -r1.675 options.m
--- compiler/options.m	16 Sep 2010 00:39:06 -0000	1.675
+++ compiler/options.m	21 Sep 2010 00:30:09 -0000
@@ -334,6 +334,7 @@
             % grades.
     ;       coverage_profiling
     ;       coverage_profiling_via_calls
+    ;       coverage_profiling_static
    
             % What types of coverage points to instrument the code with.
     ;       profile_deep_coverage_after_goal
@@ -1238,6 +1239,7 @@ option_defaults_2(compilation_model_opti
     pre_prof_transforms_simplify        -   bool(no),
     coverage_profiling                  -   bool(no),
     coverage_profiling_via_calls        -   bool(no),
+    coverage_profiling_static           -   bool(no),
     profile_deep_coverage_after_goal    -   bool(yes),
     profile_deep_coverage_branch_ite    -   bool(yes),
     profile_deep_coverage_branch_switch -   bool(yes),
@@ -2101,6 +2103,8 @@ long_option("coverage-profiling", 
                     coverage_profiling).
 long_option("coverage-profiling-via-calls", 
                     coverage_profiling_via_calls).
+long_option("coverage-profiling-static",
+                    coverage_profiling_static).
 long_option("profile-deep-coverage-after-goal",
                     profile_deep_coverage_after_goal).
 long_option("profile-deep-coverage-branch-ite",
@@ -4152,7 +4156,11 @@ options_help_compilation_model -->
         "\tEnable coverage profiling, implies --deep-profiling (above).",
 % The following options are for implementors only (intended for experiments).
 %       "--coverage-profiling-via-calls",
-%       "\tUse calls for coverage profiling, not foreign code.",
+%       "\tUse calls to implement coverage points, not inline foreign code.",
+
+%       "--no-coverage-profiling-dynamic",
+%       "\tDisable dynamic coverage profiling, this uses less memory and may ",
+%       "\tbe faster.",
 
 %       "Switches to effect coverage profiling (part of deep profiling). ",
 %       "they enable different types of coverage points.",
Index: deep_profiler/Mercury.options
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/Mercury.options,v
retrieving revision 1.16
diff -u -p -b -r1.16 Mercury.options
--- deep_profiler/Mercury.options	4 Aug 2010 02:25:01 -0000	1.16
+++ deep_profiler/Mercury.options	21 Sep 2010 00:30:09 -0000
@@ -19,3 +19,8 @@ MCFLAGS-read_profile = --trace minimum
 #	--trace-flag=debug_recursive_costs \
 #	--trace-flag=debug_parallel_conjunction_speedup \
 #	--trace-flag=debug_branch_and_bound
+
+# Uncomment this to see debug messages from the code that reads the Deep.data
+# files.
+#MCFLAGS-read_profile = --trace-flag debug_read_profdeep
+
Index: deep_profiler/canonical.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/canonical.m,v
retrieving revision 1.18
diff -u -p -b -r1.18 canonical.m
--- deep_profiler/canonical.m	25 Aug 2008 07:17:57 -0000	1.18
+++ deep_profiler/canonical.m	21 Sep 2010 00:30:09 -0000
@@ -765,9 +765,9 @@ subst_in_call_site_dynamic(Redirect, !CS
     proc_dynamic::out) is det.
 
 subst_in_proc_dynamic(Redirect, !PD) :-
-    !.PD = proc_dynamic(PDPtr, Slots0),
+    !.PD = proc_dynamic(PDPtr, Slots0, MaybeCPs),
     array.map(subst_in_slot(Redirect), u(Slots0), Slots),
-    !:PD = proc_dynamic(PDPtr, Slots).
+    !:PD = proc_dynamic(PDPtr, Slots, MaybeCPs).
 
 :- pred subst_in_slot(redirect::in, call_site_array_slot::in,
     call_site_array_slot::out) is det.
@@ -856,9 +856,12 @@ do_merge_profiles(BaseInitDeep, OtherIni
     % The program names are not checked. The new profile is named after the
     % base profile.
     BaseProgramName = BaseInitDeep ^ init_profile_stats ^ program_name,
+    % Similarly the coverage data types are not checked.
+    CoverageDataType = BaseInitDeep ^ init_profile_stats ^ coverage_data_type, 
     ConcatProfileStats = profile_stats(BaseProgramName,
         ConcatMaxCSD, BaseMaxCSS, ConcatMaxPD, BaseMaxPS, ConcatNumCallSeqs,
-        BaseTicksPerSec, InstrumentQuanta, UserQuanta, WordSize, yes),
+        BaseTicksPerSec, InstrumentQuanta, UserQuanta, WordSize, 
+        CoverageDataType, yes),
     % The root part is a temporary lie.
     MergedInitDeep = initial_deep(ConcatProfileStats,
         BaseInitDeep ^ init_root,
@@ -925,11 +928,11 @@ concatenate_profile_pds(Cur, Max, PrevMa
         !ConcatProcDynamics) :-
     ( Cur =< Max ->
         array.lookup(ProcDynamics, Cur, PD0),
-        PD0 = proc_dynamic(PSPtr, Sites0),
+        PD0 = proc_dynamic(PSPtr, Sites0, MaybeCPs),
         array.max(Sites0, MaxSite),
         concatenate_profile_slots(0, MaxSite, PrevMaxCSD, PrevMaxPD,
             u(Sites0), Sites),
-        PD = proc_dynamic(PSPtr, Sites),
+        PD = proc_dynamic(PSPtr, Sites, MaybeCPs),
         svarray.set(PrevMaxPD + Cur, PD, !ConcatProcDynamics),
         concatenate_profile_pds(Cur + 1, Max, PrevMaxCSD, PrevMaxPD,
             ProcDynamics, !ConcatProcDynamics)
Index: deep_profiler/coverage.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/coverage.m,v
retrieving revision 1.5
diff -u -p -b -r1.5 coverage.m
--- deep_profiler/coverage.m	30 Aug 2010 01:12:25 -0000	1.5
+++ deep_profiler/coverage.m	21 Sep 2010 00:30:09 -0000
@@ -20,8 +20,9 @@
 :- import_module mdbcomp.
 :- import_module mdbcomp.program_representation.
 :- import_module measurements.
-:- import_module profile.
 
+:- import_module array.
+:- import_module list.
 :- import_module map.
 :- import_module maybe.
 
@@ -46,6 +47,34 @@
 
 %----------------------------------------------------------------------------%
 
+    % This is similar to the coverage_point type in
+    % mdbcomp/program_representation.m, however it includes an integer count
+    % of how often execution reached this point in the program.
+    %
+:- type coverage_point
+    --->    coverage_point(
+                % The number of times execution reached this point,
+                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.
+
+                goal_path,
+
+                % The type of this coverage point.
+                cp_type
+            ).
+
+    % Produce a list of coverage points from an array of static data and an
+    % array of coverage points.
+    %
+:- pred coverage_point_arrays_to_list(array(coverage_point_info)::in, 
+    array(int)::in, list(coverage_point)::out) is det.
+
+%----------------------------------------------------------------------------%
+
     % Annotate the program representation structure with coverage information.
     %
 :- pred procrep_annotate_with_coverage(own_prof_info::in,
@@ -58,6 +87,7 @@
 :- implementation.
 
 :- import_module message.
+:- import_module profile.
 :- import_module program_representation_utils.
 :- import_module report.
 
@@ -66,7 +96,6 @@
 :- import_module exception.
 :- import_module int.
 :- import_module io.
-:- import_module list.
 :- import_module require.
 :- import_module string.
 :- import_module unit.
@@ -82,6 +111,35 @@ get_coverage_before_and_after(coverage_k
 
 %-----------------------------------------------------------------------------%
 
+coverage_point_arrays_to_list(StaticArray, DynamicArray, CoveragePoints) :-
+    array.bounds(StaticArray, Min, Max),
+    ( array.bounds(DynamicArray, Min, Max) ->
+        true
+    ;
+        error("coverage_point_arrays_to_list: Bounds do not match")
+    ),
+    coverage_point_arrays_to_list_2(Min, Max, StaticArray, DynamicArray,
+        [], CoveragePoints).
+
+:- pred coverage_point_arrays_to_list_2(int::in, int::in, 
+    array(coverage_point_info)::in, array(int)::in, 
+    list(coverage_point)::in, list(coverage_point)::out) is det.
+
+coverage_point_arrays_to_list_2(Num, Max, StaticArray, DynamicArray, 
+        !CoveragePoints) :-
+    ( Num =< Max -> 
+        array.lookup(StaticArray, Num, coverage_point_info(GoalPath, CPType)),
+        array.lookup(DynamicArray, Num, Count),
+        CP = coverage_point(Count, GoalPath, CPType),
+        !:CoveragePoints = [CP | !.CoveragePoints],
+        coverage_point_arrays_to_list_2(Num + 1, Max, StaticArray, DynamicArray,
+            !CoveragePoints)
+    ;
+        true
+    ).
+
+%-----------------------------------------------------------------------------%
+
 :- type coverage_before
     --->    before_unknown
     ;       before_zero
Index: deep_profiler/create_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/create_report.m,v
retrieving revision 1.22
diff -u -p -b -r1.22 create_report.m
--- deep_profiler/create_report.m	30 Aug 2010 01:12:25 -0000	1.22
+++ deep_profiler/create_report.m	21 Sep 2010 00:30:09 -0000
@@ -125,7 +125,7 @@ create_report(Cmd, Deep, Report) :-
         Deep ^ profile_stats = profile_stats(ProgramName,
             NumCSD, NumCSS, NumPD, NumPS,
             QuantaPerSec, InstrumentationQuanta, UserQuanta, NumCallseqs,
-            _, _),
+            _, _, _),
         NumCliques = array.max(Deep ^ clique_members),
         MenuReport = menu_report(ProgramName, QuantaPerSec,
             UserQuanta, InstrumentationQuanta,
@@ -1137,10 +1137,22 @@ create_procrep_coverage_report(Deep, PSP
                     CallSitesArray, map.init),
 
                 % Gather information about coverage points.
-                CoveragePointsArray = PS ^ ps_coverage_points,
-                array.foldl2(add_coverage_point_to_map, CoveragePointsArray,
-                    map.init, SolnsCoveragePointMap,
-                    map.init, BranchCoveragePointMap),
+                MaybeCoveragePoints = PS ^ ps_maybe_coverage_points,
+                (
+                    MaybeCoveragePoints = yes(CoveragePointsArray),
+                    coverage_point_arrays_to_list(PS ^ ps_coverage_point_infos,
+                        CoveragePointsArray, CoveragePoints),
+                    foldl2(add_coverage_point_to_map, 
+                        CoveragePoints, map.init, SolnsCoveragePointMap,
+                        map.init, BranchCoveragePointMap)
+                ;
+                    MaybeCoveragePoints = no,
+                    
+                    % No static coverage data available.
+                    % XXX: Try to get dynamic coverage data.
+                    SolnsCoveragePointMap = map.init,
+                    BranchCoveragePointMap = map.init
+                ),
 
                 procrep_annotate_with_coverage(Own, CallSitesMap,
                     SolnsCoveragePointMap, BranchCoveragePointMap,
@@ -1200,10 +1212,11 @@ create_proc_static_dump_report(Deep, PSP
         % Should we dump some other fields?
         PS = proc_static(_ProcId, _DeclModule,
             UnQualRefinedName, QualRefinedName, RawName, FileName, LineNumber,
-            _InInterface, CallSites, CoveragePoints, _IsZeroed),
+            _InInterface, CallSites, CoveragePointInfos, _MaybeCoveragePoints, 
+            _IsZeroed),
         array.max(CallSites, MaxCallSiteIdx),
         NumCallSites = MaxCallSiteIdx + 1,
-        array.max(CoveragePoints, MaxCoveragePointIdx),
+        array.max(CoveragePointInfos, MaxCoveragePointIdx),
         NumCoveragePoints = MaxCoveragePointIdx + 1,
         ProcStaticDumpInfo = proc_static_dump_info(PSPtr, RawName,
             UnQualRefinedName, QualRefinedName,
@@ -1219,16 +1232,25 @@ create_proc_static_dump_report(Deep, PSP
 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),
+        PD = proc_dynamic(PSPtr, CallSiteArray, MaybeCPCounts),
         deep_lookup_proc_statics(Deep, PSPtr, PS),
         RawName = PS ^ ps_raw_id,
         ModuleName = PS ^ ps_decl_module,
         UnQualRefinedName = PS ^ ps_uq_refined_id,
         QualRefinedName = PS ^ ps_q_refined_id,
         array.to_list(CallSiteArray, CallSites),
+        (
+            MaybeCPCounts = yes(CPCounts),
+            CPInfos = PS ^ ps_coverage_point_infos,
+            coverage_point_arrays_to_list(CPInfos, CPCounts, CPs),
+            MaybeCPs = yes(CPs)
+        ;
+            MaybeCPCounts = no,
+            MaybeCPs = no
+        ),
         ProcDynamicDumpInfo = proc_dynamic_dump_info(PDPtr, PSPtr,
             RawName, ModuleName, UnQualRefinedName, QualRefinedName,
-            CallSites),
+            CallSites, MaybeCPs),
         MaybeProcDynamicDumpInfo = ok(ProcDynamicDumpInfo)
     ;
         MaybeProcDynamicDumpInfo = error("invalid proc_dynamic index")
Index: deep_profiler/display_report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/display_report.m,v
retrieving revision 1.26
diff -u -p -b -r1.26 display_report.m
--- deep_profiler/display_report.m	30 Aug 2010 01:12:25 -0000	1.26
+++ deep_profiler/display_report.m	21 Sep 2010 00:30:09 -0000
@@ -2054,7 +2054,8 @@ display_report_proc_static_dump(ProcStat
 
 display_report_proc_dynamic_dump(_Deep, Prefs, ProcDynamicDumpInfo, Display) :-
     ProcDynamicDumpInfo = proc_dynamic_dump_info(PDPtr, PSPtr, RawName,
-        ModuleName, UnQualRefinedName, QualRefinedName, CallSites),
+        ModuleName, UnQualRefinedName, QualRefinedName, CallSites,
+        MaybeCoveragePoints),
     PDPtr = proc_dynamic_ptr(PDI),
     PSPtr = proc_static_ptr(PSI),
     string.format("Dump of proc_dynamic %d", [i(PDI)], Title),
@@ -2081,8 +2082,33 @@ display_report_proc_dynamic_dump(_Deep, 
     CallSitesTable = table(table_class_box_if_pref, 2, no, CallSitesRows),
     CallSitesTableItem = display_table(CallSitesTable),
 
+    (
+        MaybeCoveragePoints = yes(CoveragePoints),
+        CoveragePointsTitle = "Coverage points:",
+        CoveragePointsTitleItem = display_heading(CoveragePointsTitle),
+
+        list.map(format_coverage_point_row, CoveragePoints,
+            CoveragePointsRows),
+        CoveragePointsTableHeader = table_header([
+            table_header_group(table_header_group_single(td_s("Goal Path")), 
+                table_column_class_no_class, column_do_not_colour),
+            table_header_group(table_header_group_single(td_s("Type")),
+                table_column_class_no_class, column_do_not_colour),
+            table_header_group(table_header_group_single(td_s("Count")),
+                table_column_class_number, column_do_not_colour)]),
+        CoveragePointsTable = table(table_class_box_if_pref, 3,
+            yes(CoveragePointsTableHeader), CoveragePointsRows),
+        CoveragePointsTableItem = display_table(CoveragePointsTable),
+
+        CoveragePointsItems = [CoveragePointsTitleItem, CoveragePointsTableItem]
+    ;
+        MaybeCoveragePoints = no,
+        CoveragePointsItems = []
+    ),
+
     Display = display(yes(Title),
-        [MainTableItem, CallSitesTitleItem, CallSitesTableItem]).
+        [MainTableItem, CallSitesTitleItem, CallSitesTableItem] ++
+        CoveragePointsItems).
 
 :- pred dump_psd_call_site(preferences::in,
     call_site_array_slot::in, list(table_row)::out,
@@ -2130,6 +2156,16 @@ dump_psd_call_site_multi_entry(Prefs, CS
     EmptyCell = table_cell(td_s("")),
     Row = table_row([EmptyCell, CSDCell]).
 
+:- pred format_coverage_point_row(coverage_point::in, table_row::out) is det.
+
+format_coverage_point_row(CoveragePoint, Row) :-
+    CoveragePoint = coverage_point(Count, GoalPath, CPType),
+    GoalPathString = goal_path_to_string(GoalPath),
+    GoalPathCell = table_cell(td_s(GoalPathString)),
+    TypeCell = table_cell(td_s(string(CPType))),
+    CountCell = table_cell(td_i(Count)),
+    Row = table_row([GoalPathCell, TypeCell, CountCell]).
+
     % Create a display_report structure for a call_site_static_dump report.
     %
 :- pred display_report_call_site_static_dump(preferences::in,
Index: deep_profiler/dump.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/dump.m,v
retrieving revision 1.17
diff -u -p -b -r1.17 dump.m
--- deep_profiler/dump.m	8 Sep 2009 02:37:15 -0000	1.17
+++ deep_profiler/dump.m	21 Sep 2010 00:30:09 -0000
@@ -123,6 +123,7 @@
 
 :- implementation.
 
+:- import_module coverage.
 :- import_module array_util.
 :- import_module measurements.
 :- import_module mdbcomp.
@@ -274,7 +275,7 @@ get_static_ptrs_from_dynamic_procs(ProcD
 
 get_static_ptrs_from_dynamic_proc(ProcStatics, _, ProcDynamic, !PS_Ptrs,
         !CSS_Ptrs) :-
-    ProcDynamic = proc_dynamic(ProcStaticPtr, _PDSites),
+    ProcStaticPtr = ProcDynamic ^ pd_proc_static,
     svset.insert(ProcStaticPtr, !PS_Ptrs),
     lookup_proc_statics(ProcStatics, ProcStaticPtr, ProcStatic),
     CSSs = array.to_list(ProcStatic ^ ps_sites),
@@ -290,7 +291,7 @@ get_static_ptrs_from_dynamic_proc(ProcSt
 dump_init_profile_stats(Stats, !IO) :-
     Stats = profile_stats(ProgramName, MaxCSD, MaxCSS, MaxPD, MaxPS,
         TicksPerSec, InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize,
-        Canonical),
+        CoverageDataType, Canonical),
     io.write_string("SECTION PROFILING STATS:\n\n", !IO),
     io.write_string("\tprogram_name = " ++ ProgramName ++ "\n", !IO),
     io.format("\tmax_csd = %d\n", [i(MaxCSD)], !IO),
@@ -302,6 +303,8 @@ dump_init_profile_stats(Stats, !IO) :-
     io.format("\tuser_quanta = %d\n", [i(UserQuanta)], !IO),
     io.format("\tnum_callseqs = %d\n", [i(NumCallSeqs)], !IO),
     io.format("\tword_size   = %d\n", [i(WordSize)], !IO),
+    io.format("\tcoverage_data_type = %s\n", [s(string(CoverageDataType))], 
+        !IO),
     io.write_string("\tcanonical = ", !IO),
     (
         Canonical = yes,
@@ -435,7 +438,7 @@ dump_init_proc_dynamics(ProcDynamics, Pr
     io::di, io::uo) is det.
 
 dump_proc_dynamic(ProcStatics, Index, ProcDynamic, !IO) :-
-    ProcDynamic = proc_dynamic(PSPtr, Sites),
+    ProcDynamic = proc_dynamic(PSPtr, Sites, MaybeCPs),
     PSPtr = proc_static_ptr(PSI),
     lookup_proc_statics(ProcStatics, PSPtr, PS),
     ( PS ^ ps_q_refined_id = "" ->
@@ -447,6 +450,15 @@ dump_proc_dynamic(ProcStatics, Index, Pr
     io.format("\tpd_proc_static = %d (%s)\n",
         [i(PSI), s(QualRefinedPSId)], !IO),
     array_foldl_from_0(dump_call_site_array_slot, Sites, !IO),
+    (
+        MaybeCPs = yes(CPCounts),
+        CPInfos = PS ^ ps_coverage_point_infos,
+        coverage_point_arrays_to_list(CPInfos, CPCounts, CPs),
+        io.write_string("Coverage points:\n", !IO),
+        foldl2(dump_coverage_point, CPs, 0, _, !IO)
+    ;
+        MaybeCPs = no
+    ),
     io.nl(!IO).
 
 :- pred dump_call_site_array_slot(int::in, call_site_array_slot::in,
@@ -523,7 +535,8 @@ dump_proc_static(Restriction, Index, Pro
     ->
         ProcStatic = proc_static(Id, DeclModule,
             _UnQualRefinedId, QualRefinedId, RawId, FileName, LineNumber,
-            InInterface, Sites, CoveragePoints, IsZeroed),
+            InInterface, Sites, CoveragePointInfos, MaybeCoveragePoints, 
+            IsZeroed),
         IdStr = dump_proc_id(Id),
         io.format("ps%d:\n", [i(Index)], !IO),
         io.format("\tps_id\t\t= %s", [s(IdStr)], !IO),
@@ -559,7 +572,18 @@ dump_proc_static(Restriction, Index, Pro
         ),
         io.format("\t%s\n", [s(IsZeroStr)], !IO),
         array_foldl_from_0(dump_proc_static_call_sites, Sites, !IO),
-        array_foldl_from_0(dump_coverage_point, CoveragePoints, !IO),
+        (
+            MaybeCoveragePoints = yes(CoveragePointsArray),
+            coverage_point_arrays_to_list(CoveragePointInfos,
+                CoveragePointsArray, CoveragePoints),
+            list.foldl2(dump_coverage_point, CoveragePoints, 0, _, !IO)
+        ;
+            MaybeCoveragePoints = no,
+            io.write_string("\tCoverage counts not present in proc static\n",
+                !IO),
+            array_foldl_from_0(dump_coverage_point_info, CoveragePointInfos, 
+                !IO)
+        ),
         io.nl(!IO)
     ;
         true
@@ -572,14 +596,29 @@ dump_proc_static_call_sites(Slot, CSSPtr
     CSSPtr = call_site_static_ptr(CSSI),
     io.format("\tps_site[%d]: css%d\n", [i(Slot), i(CSSI)], !IO).
 
-:- pred dump_coverage_point(int::in, coverage_point::in, io::di, io::uo)
-    is det.
+:- pred dump_coverage_point(coverage_point::in, int::in, int::out,
+    io::di, io::uo) is det.
 
-dump_coverage_point(Num, CoveragePoint, !IO) :-
+dump_coverage_point(CoveragePoint, !Num, !IO) :-
     CoveragePoint = coverage_point(Count, Path, Type),
+    CPInfo = coverage_point_info(Path, Type),
+    format_cp_info(!.Num, CPInfo, CPInfoStr),
+    io.format("\t%s: %d\n", [s(CPInfoStr), i(Count)], !IO),
+    !:Num = !.Num + 1.
+
+:- pred dump_coverage_point_info(int::in, coverage_point_info::in, 
+    io::di, io::uo) is det.
+
+dump_coverage_point_info(Num, CoveragePointInfo, !IO) :-
+    format_cp_info(Num, CoveragePointInfo, CPInfoStr),
+    io.format("\t%s\n", [s(CPInfoStr)], !IO).
+
+:- pred format_cp_info(int::in, coverage_point_info::in, string::out) is det.
+
+format_cp_info(Num, coverage_point_info(Path, CPType), String) :-
     goal_path_to_string(Path) = PathString,
-    io.format("\tcoverage_point[%d]: %s, %s: %d\n",
-        [i(Num), s(string(Type)), s(PathString), i(Count)], !IO).
+    format("coverage_point[%d]: %s, %s", 
+        [i(Num), s(string(CPType)), s(PathString)], String).
 
 %----------------------------------------------------------------------------%
 
Index: deep_profiler/io_combinator.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/io_combinator.m,v
retrieving revision 1.9
diff -u -p -b -r1.9 io_combinator.m
--- deep_profiler/io_combinator.m	12 Aug 2008 02:51:07 -0000	1.9
+++ deep_profiler/io_combinator.m	21 Sep 2010 00:30:09 -0000
@@ -678,6 +678,41 @@
     pred(out, di, uo) is det,
     pred(in, in, in, in, in, in, in, in, in, in, in, in, out) is det,
     out, di, uo) is det.
+
+:- pred io_combinator.maybe_error_sequence_13(
+    pred(maybe_error(T1), io, io),
+    pred(maybe_error(T2), io, io),
+    pred(maybe_error(T3), io, io),
+    pred(maybe_error(T4), io, io),
+    pred(maybe_error(T5), io, io),
+    pred(maybe_error(T6), io, io),
+    pred(maybe_error(T7), io, io),
+    pred(maybe_error(T8), io, io),
+    pred(maybe_error(T9), io, io),
+    pred(maybe_error(T10), io, io),
+    pred(maybe_error(T11), io, io),
+    pred(maybe_error(T12), io, io),
+    pred(maybe_error(T13), io, io),
+    pred(T1, T2, T3, T4, T5, T6, T7, T8, T9, T10, T11, T12, T13, 
+        maybe_error(T)),
+    maybe_error(T), io, io).
+:- mode io_combinator.maybe_error_sequence_13(
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(out, di, uo) is det,
+    pred(in, in, in, in, in, in, in, in, in, in, in, in, in, out) is det,
+    out, di, uo) is det.
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
@@ -2457,6 +2492,104 @@ io_combinator.maybe_error_sequence_12(P1
         Res = error(Err)
     ).
 
+io_combinator.maybe_error_sequence_13(P1, P2, P3, P4, P5, P6, P7, P8, P9, P10,
+        P11, P12, P13, Combine, Res, !IO) :-
+    call(P1, Res1, !IO),
+    (
+        Res1 = ok(T1),
+        call(P2, Res2, !IO),
+        (
+            Res2 = ok(T2),
+            call(P3, Res3, !IO),
+            (
+                Res3 = ok(T3),
+                call(P4, Res4, !IO),
+                (
+                    Res4 = ok(T4),
+                    call(P5, Res5, !IO),
+                    (
+                        Res5 = ok(T5),
+                        call(P6, Res6, !IO),
+                        (
+                            Res6 = ok(T6),
+                            call(P7, Res7, !IO),
+                            (
+                                Res7 = ok(T7),
+                                call(P8, Res8, !IO),
+                                (
+                                    Res8 = ok(T8),
+                                    call(P9, Res9, !IO),
+                                    (
+                                        Res9 = ok(T9),
+                                        call(P10, Res10, !IO),
+                                        (
+                                            Res10 = ok(T10),
+                                            call(P11, Res11, !IO),
+                                            (
+                                                Res11 = ok(T11),
+                                                call(P12, Res12, !IO),
+                                                (
+                                                    Res12 = ok(T12),
+                                                    call(P13, Res13, !IO),
+                                                    (
+                                                        Res13 = ok(T13),
+                                                        call(Combine, T1, T2,
+                                                            T3, T4, T5, T6, T7,
+                                                            T8, T9, T10, T11,
+                                                            T12, T13, Res)
+                                                    ;
+                                                        Res13 = error(Err),
+                                                        Res = error(Err)
+                                                    )
+                                                ;
+                                                    Res12 = error(Err),
+                                                    Res = error(Err)
+                                                )
+                                            ;
+                                                Res11 = error(Err),
+                                                Res = error(Err)
+                                            )
+                                        ;
+                                            Res10 = error(Err),
+                                            Res = error(Err)
+                                        )
+                                    ;
+                                        Res9 = error(Err),
+                                        Res = error(Err)
+                                    )
+                                ;
+                                    Res8 = error(Err),
+                                    Res = error(Err)
+                                )
+                            ;
+                                Res7 = error(Err),
+                                Res = error(Err)
+                            )
+                        ;
+                            Res6 = error(Err),
+                            Res = error(Err)
+                        )
+                    ;
+                        Res5 = error(Err),
+                        Res = error(Err)
+                    )
+                ;
+                    Res4 = error(Err),
+                    Res = error(Err)
+                )
+            ;
+                Res3 = error(Err),
+                Res = error(Err)
+            )
+        ;
+            Res2 = error(Err),
+            Res = error(Err)
+        )
+    ;
+        Res1 = error(Err),
+        Res = error(Err)
+    ).
+
 %-----------------------------------------------------------------------------%
 :- end_module io_combinator.
 %-----------------------------------------------------------------------------%
Index: deep_profiler/profile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/profile.m,v
retrieving revision 1.29
diff -u -p -b -r1.29 profile.m
--- deep_profiler/profile.m	26 Aug 2010 06:29:27 -0000	1.29
+++ deep_profiler/profile.m	21 Sep 2010 00:51:57 -0000
@@ -48,6 +48,7 @@
                 user_quanta             :: int,
                 num_callseqs            :: int,
                 word_size               :: int,
+                coverage_data_type      :: coverage_data_type,
                 canonical               :: bool
             ).
 
@@ -175,21 +176,44 @@
 :- type proc_dynamic
     --->    proc_dynamic(
                 pd_proc_static  :: proc_static_ptr,
-                pd_sites        :: array(call_site_array_slot)
+                pd_sites                    :: array(call_site_array_slot),
+
+                % An array of coverage points. If present then coverage points
+                % for this procedure are dynamic and the corresponding static
+                % info can be found in the proc_static.  If no, then coverage
+                % points aren't available or are stored in the proc static.
+                pd_maybe_coverage_points    :: maybe(array(int))
             ).
 
 :- type proc_static
     --->    proc_static(
-                ps_id               :: string_proc_label, % procedure ID
-                ps_decl_module      :: string,      % declaring module
-                ps_uq_refined_id    :: string,      % unqualified refined id
-                ps_q_refined_id     :: string,      % qualied refined id
-                ps_raw_id           :: string,      % raw procedure id
-                ps_file_name        :: string,      % file name of proc
-                ps_line_number      :: int,         % line number of proc
-                ps_in_interface     :: bool,        % is in interface?
+                % procedure ID
+                ps_id                       :: string_proc_label,
+                
+                % declaring module
+                ps_decl_module              :: string,
+                
+                % unqualified refined id
+                ps_uq_refined_id            :: string,
+                
+                % qualified refined id
+                ps_q_refined_id             :: string,
+                
+                % raw procedure id
+                ps_raw_id                   :: string,
+                
+                % file name of proc
+                ps_file_name                :: string,
+                
+                % line number of proc
+                ps_line_number              :: int,
+                
+                % is in interface?
+                ps_in_interface             :: bool,
+                
                 ps_sites            :: array(call_site_static_ptr),
-                ps_coverage_points  :: array(coverage_point),
+                ps_coverage_point_infos     :: array(coverage_point_info),
+                ps_maybe_coverage_points    :: maybe(array(int)),
                 ps_is_zeroed        :: is_zeroed
             ).
 
@@ -261,25 +285,12 @@
                 call_site_static_ptr
             ).
 
-    % This is similar to the coverage_point type in
-    % mdbcomp/program_representation.m, however it includes an integer count
-    % of how often execution reached this point in the program.
+    % The type of coverage data available in a profile.
     %
-:- type coverage_point
-    --->    coverage_point(
-                % The number of times execution reached this point,
-                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.
-
-                goal_path,
-
-                % The type of this coverage point.
-                cp_type
-            ).
+:- type coverage_data_type
+    --->    no_coverage_data
+    ;       static_coverage_data
+    ;       dynamic_coverage_data.
 
 :- pred is_call_site_kind(int::in, call_site_kind::out) is semidet.
 
Index: deep_profiler/read_profile.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/read_profile.m,v
retrieving revision 1.28
diff -u -p -b -r1.28 read_profile.m
--- deep_profiler/read_profile.m	4 Aug 2010 02:25:02 -0000	1.28
+++ deep_profiler/read_profile.m	21 Sep 2010 00:30:09 -0000
@@ -38,11 +38,13 @@
 :- import_module mdbcomp.prim_data.
 :- import_module mdbcomp.program_representation.
 
+:- import_module assoc_list.
 :- import_module array.
 :- import_module bool.
 :- import_module char.
 :- import_module int.
 :- import_module list.
+:- import_module pair.
 :- import_module require.
 :- import_module string.
 
@@ -65,39 +67,19 @@ read_call_graph(FileName, MaybeInitDeep,
         read_deep_id_string(MaybeIdStr, !IO),
         (
             MaybeIdStr = ok(_),
-            io_combinator.maybe_error_sequence_12(
+            io_combinator.maybe_error_sequence_11(
                 read_string,
                 read_fixed_size_int,
                 read_fixed_size_int,
                 read_fixed_size_int,
                 read_fixed_size_int,
+                read_fixed_size_int,
                 read_num,
                 read_num,
                 read_num,
                 read_num,
-                read_deep_byte,
-                read_deep_byte,
                 read_ptr(pd),
-                (pred(ProgName::in,
-                        MaxCSD::in, MaxCSS::in,
-                        MaxPD::in, MaxPS::in,
-                        TicksPerSec::in,
-                        InstrumentQuanta::in,
-                        UserQuanta::in,
-                        NumCallSeqs::in,
-                        WordSize::in,
-                        CanonicalFlag::in,
-                        RootPDI::in,
-                        ResInitDeep::out) is det :-
-                    InitDeep0 = init_deep(basename(ProgName),
-                        MaxCSD, MaxCSS, MaxPD, MaxPS,
-                        TicksPerSec, InstrumentQuanta, UserQuanta,
-                        NumCallSeqs,
-                        WordSize, CanonicalFlag,
-                        RootPDI),
-                    ResInitDeep = ok(InitDeep0)
-                ),
-                MaybeInitDeepHeader, !IO),
+                maybe_init_deep, MaybeInitDeepHeader, !IO),
             (
                 MaybeInitDeepHeader = ok(InitDeep),
                 read_nodes(InitDeep, MaybeInitDeep, !IO),
@@ -141,7 +123,7 @@ read_deep_id_string(MaybeIdStr, !IO) :-
     %
 :- func deep_id_string = string.
 
-deep_id_string = deep_id_prefix ++ " 6\n".
+deep_id_string = deep_id_prefix ++ " 7\n".
 
     % Return the part of deep_id_string that is version independent.
     %
@@ -188,20 +170,19 @@ basename_chars([Char | Chars], MaybeChar
 path_separator('/').
 path_separator('\\').
 
-:- func init_deep(string, int, int, int, int, int, int, int, int, int, int,
-    int) = initial_deep.
-
-init_deep(ProgName, MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec,
-        InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize, CanonicalByte,
-        RootPDI) = InitDeep :-
-    ( CanonicalByte = 0 ->
-        CanonicalFlag = no
-    ;
-        CanonicalFlag = yes
-    ),
+:- pred maybe_init_deep(string::in, int::in, int::in, int::in, int::in,
+    int::in, int::in, int::in, int::in, int::in, int::in, 
+    maybe_error(initial_deep)::out) is det.
+
+maybe_init_deep(ProgName, FlagsInt, MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec,
+        InstrumentQuanta, UserQuanta, NumCallSeqs, RootPDI, MaybeInitDeep) :-
+    maybe_deep_flags(FlagsInt, MaybeFlags),
+    (
+        MaybeFlags = ok(Flags),
+        Flags = deep_flags(WordSize, CanonicalFlag, CoverageDataType),
     InitStats = profile_stats(ProgName, MaxCSD, MaxCSS, MaxPD, MaxPS,
         TicksPerSec, InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize,
-        CanonicalFlag),
+            CoverageDataType, CanonicalFlag),
     InitDeep = initial_deep(
         InitStats,
         make_pdptr(RootPDI),
@@ -211,7 +192,8 @@ init_deep(ProgName, MaxCSD, MaxCSS, MaxP
                 make_dummy_pdptr,
                 zero_own_prof_info
             )),
-        array.init(MaxPD + 1, proc_dynamic(make_dummy_psptr, array([]))),
+            array.init(MaxPD + 1, proc_dynamic(make_dummy_psptr, array([]),
+                no)),
         array.init(MaxCSS + 1,
             call_site_static(
                 make_dummy_psptr, -1,
@@ -219,9 +201,84 @@ init_deep(ProgName, MaxCSD, MaxCSS, MaxP
             )),
         array.init(MaxPS + 1,
             proc_static(dummy_proc_id, "", "", "", "", "", -1, no,
-                array([]), array([]), not_zeroed))
+                    array([]), array([]), no, not_zeroed))
+        ),
+        MaybeInitDeep = ok(InitDeep)
+    ;
+        MaybeFlags = error(Error),
+        MaybeInitDeep = error(Error)
+    ).
+
+:- type deep_flags
+    --->    deep_flags(
+                df_bytes_per_int        :: int,
+                df_canonical_flag       :: bool,
+                df_coverage_data_type   :: coverage_data_type
+            ).
+
+:- pred maybe_deep_flags(int::in, maybe_error(deep_flags)::out) is det.
+
+maybe_deep_flags(FlagsInt, MaybeFlags) :-
+    BytesPerInt = (FlagsInt /\ deep_flag_bytes_per_int_mask)
+        >> deep_flag_bytes_per_int_shift,
+    Canonical = (FlagsInt /\ deep_flag_canonical_mask)
+        >> deep_flag_canonical_shift,
+    Coverage = (FlagsInt /\ deep_flag_coverage_mask)
+        >> deep_flag_coverage_shift,
+    (
+        ( 
+            Coverage = 0, 
+            CoverageFlag = no_coverage_data
+        ; 
+            Coverage = 1, 
+            CoverageFlag = static_coverage_data
+        ; 
+            Coverage = 2, 
+            CoverageFlag = dynamic_coverage_data
+        ),
+        (
+            Canonical = 0,
+            CanonicalFlag = no
+        ;
+            Canonical = 1,
+            CanonicalFlag = yes
+        ),
+        0 = ((\ deep_flag_all_fields_mask) /\ FlagsInt)
+    ->
+        MaybeFlags = ok(deep_flags(BytesPerInt, CanonicalFlag, CoverageFlag))
+    ;
+        MaybeFlags = error(
+            format("Error parsing flags in file header, flags are 0x%x",
+                [i(FlagsInt)]))
     ).
 
+    % Flags masks and shifts.
+    % The following line provides a ruler to line up the hexadecimal values
+    % with.
+    % 
+    %                              48  32  16   0
+    %
+:- func deep_flag_bytes_per_int_mask = int.
+deep_flag_bytes_per_int_mask = 0x00000000000000FF.
+:- func deep_flag_bytes_per_int_shift = int.
+deep_flag_bytes_per_int_shift = 0.
+
+:- func deep_flag_canonical_mask = int.
+deep_flag_canonical_mask =     0x0000000000000100.
+:- func deep_flag_canonical_shift = int.
+deep_flag_canonical_shift = 8.
+
+:- func deep_flag_coverage_mask = int.
+deep_flag_coverage_mask =      0x0000000000000B00.
+:- func deep_flag_coverage_shift = int.
+deep_flag_coverage_shift = 10.
+
+:- func deep_flag_all_fields_mask = int.
+deep_flag_all_fields_mask = 
+    deep_flag_bytes_per_int_mask \/
+    deep_flag_canonical_mask \/
+    deep_flag_coverage_mask.
+
 :- pred read_nodes(initial_deep::in, maybe_error(initial_deep)::out,
     io::di, io::uo) is det.
 
@@ -264,6 +321,7 @@ read_nodes_2(Depth, !.InitDeep, MaybeIni
     io::di, io::uo) is det.
 
 read_nodes_3(Depth, !.InitDeep, MaybeInitDeep, !IO) :-
+    ProfileStats = !.InitDeep ^ init_profile_stats,
     read_byte(MaybeByte, !IO),
     (
         MaybeByte = ok(Byte),
@@ -283,7 +341,7 @@ read_nodes_3(Depth, !.InitDeep, MaybeIni
                 )
             ;
                 NextItem = deep_item_proc_dynamic,
-                read_proc_dynamic(MaybePD, !IO),
+                read_proc_dynamic(ProfileStats, MaybePD, !IO),
                 (
                     MaybePD = ok2(ProcDynamic, PDI),
                     PDs0 = !.InitDeep ^ init_proc_dynamics,
@@ -309,7 +367,7 @@ read_nodes_3(Depth, !.InitDeep, MaybeIni
                 )
             ;
                 NextItem = deep_item_proc_static,
-                read_proc_static(MaybePS, !IO),
+                read_proc_static(ProfileStats, MaybePS, !IO),
                 (
                     MaybePS = ok2(ProcStatic, PSI),
                     PSs0 = !.InitDeep ^ init_proc_statics,
@@ -372,34 +430,34 @@ read_call_site_static(MaybeCSS, !IO) :-
         MaybeCSS = error(_)
     ).
 
-:- pred read_proc_static(maybe_error2(proc_static, int)::out,
-    io::di, io::uo) is det.
+:- pred read_proc_static(profile_stats::in, 
+    maybe_error2(proc_static, int)::out, io::di, io::uo) is det.
 
-read_proc_static(MaybePS, !IO) :-
+read_proc_static(ProfileStats, MaybePS, !IO) :-
     trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
         io.write_string("reading proc_static.\n", !IO)
     ),
-    io_combinator.maybe_error_sequence_7(
+    io_combinator.maybe_error_sequence_6(
         read_ptr(ps),
         read_proc_id,
         read_string,
         read_num,
         read_deep_byte,
         read_num,
-        read_num,
         (pred(PSI0::in, Id0::in, F0::in, L0::in, I0::in,
-                NCS0::in, NCP0::in, ProcId::out) is det :-
-            ProcId = ok({PSI0, Id0, F0, L0, I0, NCS0, NCP0})
+                NCS0::in, ProcId::out) is det :-
+            ProcId = ok({PSI0, Id0, F0, L0, I0, NCS0})
         ),
         MaybeProcId, !IO),
     (
-        MaybeProcId = ok({PSI, Id, FileName, LineNumber, Interface, NCS, NCP}),
+        MaybeProcId = ok({PSI, Id, FileName, LineNumber, Interface, NCS}),
         read_n_things(NCS, read_ptr(css), MaybeCSSIs, !IO),
         (
             MaybeCSSIs = ok(CSSIs),
-            read_n_things(NCP, read_coverage_point, MaybeCoveragePoints, !IO),
+            maybe_read_ps_coverage_points(ProfileStats, MaybeCoveragePoints,
+                !IO),
             (
-                MaybeCoveragePoints = ok(CoveragePoints),
+                MaybeCoveragePoints = ok(CPInfos - MaybeCPs),
                 CSSPtrs = list.map(make_cssptr, CSSIs),
                 DeclModule = decl_module(Id),
                 create_refined_proc_ids(Id, UnQualRefinedStr, QualRefinedStr),
@@ -415,7 +473,7 @@ read_proc_static(MaybePS, !IO) :-
                 ProcStatic = proc_static(Id, DeclModule,
                     UnQualRefinedStr, QualRefinedStr, RawStr,
                     FileName, LineNumber, IsInInterface,
-                    array(CSSPtrs), array(CoveragePoints), not_zeroed),
+                    array(CSSPtrs), CPInfos, MaybeCPs, not_zeroed),
                 MaybePS = ok2(ProcStatic, PSI),
                 trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
                     io.write_string("read proc_static ", !IO),
@@ -437,6 +495,90 @@ read_proc_static(MaybePS, !IO) :-
         MaybePS = error2(Error)
     ).
 
+:- pred maybe_read_ps_coverage_points(profile_stats::in, 
+    maybe_error(pair(array(coverage_point_info), maybe(array(int))))::out,
+    io::di, io::uo) is det.
+
+maybe_read_ps_coverage_points(ProfileStats, MaybeCoveragePoints, !IO) :-
+    CoverageDataType = ProfileStats ^ coverage_data_type,
+    (
+        CoverageDataType = no_coverage_data,
+        MaybeCoveragePoints0 = ok([] - no)
+    ;
+        ( CoverageDataType = static_coverage_data
+        ; CoverageDataType = dynamic_coverage_data
+        ),
+        read_num(MaybeNCP, !IO),
+        (
+            MaybeNCP = ok(NCP),
+            (
+                CoverageDataType = static_coverage_data, 
+                read_n_things(NCP, read_coverage_point,
+                    MaybeCPPairs, !IO),
+                (
+                    MaybeCPPairs = ok(CPPairs),
+                    keys_and_values(CPPairs, CPInfos, CPs),
+                    MaybeCoveragePoints0 = ok(CPInfos - yes(CPs))
+                ;
+                    MaybeCPPairs = error(Error0),
+                    MaybeCoveragePoints0 = error(Error0)
+                )
+            ;
+                CoverageDataType = dynamic_coverage_data,
+                read_n_things(NCP, read_coverage_point_static,
+                    MaybeCPInfos, !IO),
+                (
+                    MaybeCPInfos = ok(CPInfos),
+                    MaybeCoveragePoints0 = ok(CPInfos - no)
+                ;
+                    MaybeCPInfos = error(Error0),
+                    MaybeCoveragePoints0 = error(Error0)
+                )
+            )
+        ;
+            MaybeNCP = error(Error0),
+            MaybeCoveragePoints0 = error(Error0)
+        )
+    ),
+    (
+        MaybeCoveragePoints0 = ok(CPInfosList - MaybeCPsList),
+        CPInfosArray = array(CPInfosList),
+        MaybeCPsArray = map_maybe(array, MaybeCPsList),
+        MaybeCoveragePoints = ok(CPInfosArray - MaybeCPsArray)
+    ;
+        MaybeCoveragePoints0 = error(Error),
+        MaybeCoveragePoints = error(Error)
+    ).
+
+:- pred maybe_read_pd_coverage_points(profile_stats::in,
+    maybe_error(maybe(array(int)))::out, io::di, io::uo) is det.
+
+maybe_read_pd_coverage_points(ProfileStats, MaybeCoveragePoints, !IO) :-
+    CoverageDataType = ProfileStats ^ coverage_data_type,
+    (
+        ( CoverageDataType = no_coverage_data
+        ; CoverageDataType = static_coverage_data
+        ),
+        MaybeCoveragePoints = ok(no)
+    ;
+        CoverageDataType = dynamic_coverage_data,
+        read_num(ResN, !IO),
+        (
+            ResN = ok(N),
+            read_n_things(N, read_num, MaybeCPs, !IO),
+            (
+                MaybeCPs = ok(CPsList),
+                MaybeCoveragePoints = ok(yes(array(CPsList)))
+            ;
+                MaybeCPs = error(Error),
+                MaybeCoveragePoints = error(Error)
+            )
+        ;
+            ResN = error(Error),
+            MaybeCoveragePoints = error(Error)
+        )
+    ).
+
 :- pred read_proc_id(maybe_error(string_proc_label)::out, io::di, io::uo)
     is det.
 
@@ -500,19 +642,39 @@ read_proc_id_user_defined(PredOrFunc, Ma
         ),
         MaybeProcLabel, !IO).
 
-:- pred read_coverage_point(maybe_error(coverage_point)::out, io::di, io::uo)
-    is det.
+    % Read a full coverage point.
+    %
+    % A full coverage point is that static data followed by a number indicating
+    % how many times that point was covered.  This is used when coverage data
+    % is per proc-static.
+    %
+:- pred read_coverage_point(maybe_error(pair(coverage_point_info, int))::out,
+    io::di, io::uo) is det.
 
-read_coverage_point(MaybeCoveragePoint, !IO) :-
-    io_combinator.maybe_error_sequence_3(
+read_coverage_point(MaybeCP, !IO) :-
+    io_combinator.maybe_error_sequence_2(
+        read_coverage_point_static,
+        read_num,
+        (pred(CPInfo::in, Count::in, ok(CPI)::out) is det :-
+            CPI = CPInfo - Count
+        ), MaybeCP, !IO).
+
+    % Read the static data for coverage points.
+    %
+    % This data is always present in the proc static even when dynamic coverage
+    % profiling is used. 
+    %
+:- pred read_coverage_point_static(maybe_error(coverage_point_info)::out, 
+    io::di, io::uo) is det.
+
+read_coverage_point_static(MaybeCP, !IO) :-
+    io_combinator.maybe_error_sequence_2(
         read_string,
         read_cp_type,
-        read_num,
-        (pred(GoalPathString::in, CPType::in, CPCount::in, CP::out) is det :-
+        (pred(GoalPathString::in, CPType::in, MaybeCPI::out) is det :-
             goal_path_from_string_det(GoalPathString, GoalPath),
-            CP = ok(coverage_point(CPCount, GoalPath, CPType))
-        ),
-        MaybeCoveragePoint, !IO).
+            MaybeCPI = ok(coverage_point_info(GoalPath, CPType))
+        ), MaybeCP, !IO).
 
 :- func raw_proc_id_to_string(string_proc_label) = string.
 
@@ -681,10 +843,10 @@ glue_lambda_name(Segments, PredName, Lin
         fail
     ).
 
-:- pred read_proc_dynamic(maybe_error2(proc_dynamic, int)::out,
-    io::di, io::uo) is det.
+:- pred read_proc_dynamic(profile_stats::in,
+    maybe_error2(proc_dynamic, int)::out, io::di, io::uo) is det.
 
-read_proc_dynamic(MaybePD, !IO) :-
+read_proc_dynamic(ProfileStats, MaybePD, !IO) :-
     trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
         io.write_string("reading proc_dynamic.\n", !IO)
     ),
@@ -698,11 +860,17 @@ read_proc_dynamic(MaybePD, !IO) :-
         MaybePDHeader, !IO),
     (
         MaybePDHeader = ok({PDI, PSI, N}),
-        read_n_things(N, read_call_site_slot, MaybeSlots, !IO),
+        io_combinator.maybe_error_sequence_2(
+            maybe_read_pd_coverage_points(ProfileStats),
+            read_n_things(N, read_call_site_slot),
+            (pred(MaybeCPs0::in, Slots0::in, CPsAndSlots0::out) is det :-
+                CPsAndSlots0 = ok({MaybeCPs0, Slots0})
+            ),
+            MaybeCPsAndSlots, !IO),
         (
-            MaybeSlots = ok(Refs),
+            MaybeCPsAndSlots = ok({MaybeCPs, Refs}),
             PSPtr = make_psptr(PSI),
-            ProcDynamic = proc_dynamic(PSPtr, array(Refs)),
+            ProcDynamic = proc_dynamic(PSPtr, array(Refs), MaybeCPs),
             MaybePD = ok2(ProcDynamic, PDI),
             trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
                 io.write_string("read proc_dynamic ", !IO),
@@ -712,7 +880,7 @@ read_proc_dynamic(MaybePD, !IO) :-
                 io.write_string("\n", !IO)
             )
         ;
-            MaybeSlots = error(Error),
+            MaybeCPsAndSlots = error(Error),
             MaybePD = error2(Error)
         )
     ;
@@ -1199,13 +1367,16 @@ read_num_acc(Num0, MaybeNum, !IO) :-
 % Must correspond to MR_FIXED_SIZE_INT_BYTES
 % in runtime/mercury_deep_profiling.c.
 
-fixed_size_int_bytes = 4.
+fixed_size_int_bytes = 8.
 
 :- pred read_fixed_size_int(maybe_error(int)::out,
     io::di, io::uo) is det.
 
-read_fixed_size_int(MaybeByte, !IO) :-
-    read_fixed_size_int_acc(fixed_size_int_bytes, 0, 0, MaybeByte, !IO).
+read_fixed_size_int(MaybeInt, !IO) :-
+    read_fixed_size_int_acc(fixed_size_int_bytes, 0, 0, MaybeInt, !IO),
+    trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
+        io.format("fixed size int %s\n", [s(string(MaybeInt))], !IO)
+    ).
 
 :- pred read_fixed_size_int_acc(int::in, int::in, int::in,
     maybe_error(int)::out, io::di, io::uo) is det.
@@ -1359,4 +1530,10 @@ make_dummy_psptr = proc_static_ptr(-1).
 ").
 
 %------------------------------------------------------------------------------%
+
+:- func this_file = string.
+
+this_file = "read_profile.m: ".
+
+%------------------------------------------------------------------------------%
 %------------------------------------------------------------------------------%
Index: deep_profiler/report.m
===================================================================
RCS file: /home/mercury1/repository/mercury/deep_profiler/report.m,v
retrieving revision 1.22
diff -u -p -b -r1.22 report.m
--- deep_profiler/report.m	26 Aug 2010 06:29:27 -0000	1.22
+++ deep_profiler/report.m	21 Sep 2010 00:30:09 -0000
@@ -463,7 +463,8 @@
                 pddi_ps_module_name         :: string,
                 pddi_ps_uq_refined_name     :: string,
                 pddi_ps_q_refined_name      :: string,
-                pddi_call_sites             :: list(call_site_array_slot)
+                pddi_call_sites             :: list(call_site_array_slot),
+                pddi_coverage_points        :: maybe(list(coverage_point))
             ).
 
 :- type call_site_static_dump_info
Index: library/profiling_builtin.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/profiling_builtin.m,v
retrieving revision 1.23
diff -u -p -b -r1.23 profiling_builtin.m
--- library/profiling_builtin.m	27 Sep 2008 11:56:20 -0000	1.23
+++ library/profiling_builtin.m	21 Sep 2010 00:30:09 -0000
@@ -107,7 +107,13 @@
 
 :- impure pred reset_activation_info_sr(proc_dynamic::in) is det.
 
-:- impure pred increment_coverage_point_count(proc_layout::in, int::in) is det.
+    /*
+    ** Increment a static coverage point.
+    */
+:- impure pred increment_static_coverage_point_count(proc_layout::in, int::in)
+    is det.
+
+:- impure pred increment_dynamic_coverage_point_count(int::in) is det.
 
 :- type call_site_nums_2
     --->    call_site_nums_2(int, int).
@@ -805,16 +811,16 @@
 }").
 
 %---------------------------------------------------------------------------%
-% instance of increment_coverage_point_counto
+% instance of increment_{static,dynamic}_coverage_point_count
 %---------------------------------------------------------------------------%
 
 :- pragma foreign_proc("C",
-    increment_coverage_point_count(ProcLayout::in, CPIndex::in),
+    increment_static_coverage_point_count(ProcLayout::in, CPIndex::in),
     [thread_safe, will_not_call_mercury],
     % The code of this predicate is duplicated bodily in deep_profiling.m
     % in the compiler directory, so any changes here should also be made there.
 "
-#ifdef MR_DEEP_PROFILING
+#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC
     const MR_ProcLayout *pl;
     MR_ProcStatic       *ps;
 
@@ -841,8 +847,64 @@
     MR_leave_instrumentation();
 #else
     MR_fatal_error(
-        ""increment_coverage_point_count: deep profiling not enabled"");
-#endif /* MR_DEEP_PROFILING */
+        ""increment_static_coverage_point_count:  ""
+            ""static coverage profiling not enabled"");
+#endif /* MR_DEEP_PROFILING_COVERAGE_STATIC */
+").
+
+:- pragma foreign_proc("C",
+    increment_dynamic_coverage_point_count(CPIndex::in),
+    [thread_safe, will_not_call_mercury],
+    % The code of this predicate is duplicated bodily in deep_profiling.m
+    % in the compiler directory, so any changes here should also be made there.
+"
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    const MR_CallSiteDynamic *csd;
+    const MR_ProcDynamic *pd;
+
+    MR_enter_instrumentation();
+
+  #ifdef MR_DEEP_PROFILING_LOWLEVEL_DEBUG
+    if (MR_calldebug && MR_lld_print_enabled) {
+        MR_print_deep_prof_vars(stdout, ""increment_coverage_point_count"");
+        printf("", CallSiteDynamic: 0x%x, CPIndex: %d\\n"", 
+            MR_current_call_site_dynamic, CPIndex);
+    }
+  #endif
+
+    csd = MR_current_call_site_dynamic;
+
+    MR_deep_assert(NULL, NULL, NULL, csd != NULL);
+    pd = csd->MR_csd_callee_ptr;
+
+    MR_deep_assert(csd, NULL, NULL, pd != NULL);
+
+#ifdef MR_DEEP_CHECKS
+    /*
+    ** Check that CPIndex is within bounds.
+    */
+    {
+        const MR_ProcLayout *pl;
+        const MR_ProcStatic *ps;
+
+        pl = pd->MR_pd_proc_layout;
+        MR_deep_assert(csd, NULL, NULL, pl != NULL);
+        ps = pl->MR_sle_proc_static;
+        MR_deep_assert(csd, pl, NULL, ps != NULL);
+        MR_deep_assert(csd, pl, ps, CPIndex >= ps->MR_ps_num_coverage_points);
+    }
+#endif
+
+    MR_deep_assert(csd, NULL, NULL, pd->MR_pd_coverage_points != NULL);
+
+    pd->MR_pd_coverage_points[CPIndex]++;
+
+    MR_leave_instrumentation();
+#else
+    MR_fatal_error(
+        ""increment_dynamic_coverage_point_count:  ""
+            ""dynamic deep profiling not enabled"");
+#endif /* MR_DEEP_PROFILING_COVERAGE_DYNAMIC */
 ").
 
 %---------------------------------------------------------------------------%
Index: runtime/mercury_conf_param.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_conf_param.h,v
retrieving revision 1.113
diff -u -p -b -r1.113 mercury_conf_param.h
--- runtime/mercury_conf_param.h	16 Feb 2010 22:55:39 -0000	1.113
+++ runtime/mercury_conf_param.h	21 Sep 2010 00:30:09 -0000
@@ -645,6 +645,20 @@
 **
 ** MR_DEEP_PROFILING_MEMORY.
 ** Enables deep profiling of memory usage.
+**
+** MR_DEEP_PROFILING_COVERAGE,
+** Enables deep profiling code coverage support. (required for
+** auto-parallelisation).
+**
+** MR_DEEP_PROFILING_COVERAGE_STATIC,
+** Enables the outmoded static coverage profiling code.  This disables the new
+** dynamic coverage profiling code.
+**
+** MR_DEEP_PROFILING_COVERAGE_DYNAMIC,
+** Enabled unless MR_DEEP_PROFILING_COVERAGE_STATIC is enabled.  This is the
+** normal option, coverage information is per procedure and it's context rather
+** than just per static procedure.
+** Don't specify this option directly, just specifiy the STATIC option.
 */
 
 #ifdef	MR_DEEP_PROFILING
@@ -654,12 +668,32 @@
     #define MR_DEEP_PROFILING_TIMING
     #define MR_DEEP_PROFILING_CALL_SEQ
     #define MR_DEEP_PROFILING_MEMORY
+    #define MR_DEEP_PROFILING_COVERAGE
+    #ifndef MR_DEEP_PROFILING_COVERAGE_STATIC
+      #define MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    #else
+      #undef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    #endif
+  #else
+    #ifdef MR_DEEP_PROFILING_COVERAGE
+      #ifndef MR_DEEP_PROFILING_COVERAGE_STATIC
+        #define MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+      #else
+        #undef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+      #endif
+    #else
+      #undef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+      #undef MR_DEEP_PROFILING_COVERAGE_STATIC
+    #endif
   #endif
 #else
   #undef  MR_DEEP_PROFILING_PORT_COUNTS
   #undef  MR_DEEP_PROFILING_TIMING
   #undef  MR_DEEP_PROFILING_CALL_SEQ
   #undef  MR_DEEP_PROFILING_MEMORY
+  #undef  MR_DEEP_PROFILING_COVERAGE
+  #undef  MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+  #undef  MR_DEEP_PROFILING_COVERAGE_STATIC
 #endif
 
 #if !defined(MR_DISABLE_CHECK_DU_EQ)
Index: runtime/mercury_deep_profiling.c
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_deep_profiling.c,v
retrieving revision 1.34
diff -u -p -b -r1.34 mercury_deep_profiling.c
--- runtime/mercury_deep_profiling.c	2 Oct 2008 05:22:38 -0000	1.34
+++ runtime/mercury_deep_profiling.c	21 Sep 2010 00:30:09 -0000
@@ -60,7 +60,7 @@ MR_ProcStatic   MR_main_parent_proc_stat
 
 MR_ProcLayoutUser MR_main_parent_proc_layout =
 {
-    { MR_do_not_reached, { MR_LONG_LVAL_TYPE_UNKNOWN }, -1, MR_DETISM_DET },
+    { MR_do_not_reached, MR_LONG_LVAL_TYPE_UNKNOWN, -1, MR_DETISM_DET },
     { MR_PREDICATE, "Mercury runtime", "Mercury runtime",
         "Mercury runtime", 0, 0 },
     NULL,
@@ -94,7 +94,10 @@ MR_CallSiteDynamic  MR_main_grandparent_
     0,
 #endif
 #ifdef MR_DEEP_PROFILING_MEMORY
-    0, 0
+    0, 0,
+#endif
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    NULL
 #endif
     },
     0
@@ -210,7 +213,7 @@ MR_setup_callback(void *entry)
 
     MR_new_call_site_dynamic(csd);
 
-    csd_list = MR_PROFILING_MALLOC(MR_CallSiteDynList);
+    csd_list = MR_PROFILING_NEW(MR_CallSiteDynList);
     csd_list->MR_csdlist_key = entry;
     csd_list->MR_csdlist_call_site = csd;
     csd_list->MR_csdlist_next = *MR_current_callback_site;
@@ -262,6 +265,7 @@ static  void    MR_write_out_profiling_t
 static  void    MR_write_out_deep_id_string(FILE *fp);
 static  void    MR_write_out_procrep_id_string(FILE *fp);
 static  void    MR_write_out_program_name(FILE *fp);
+static  void    MR_write_out_deep_flags(FILE *fp);
 
 static  void    MR_write_out_call_site_static(FILE *fp,
                     const MR_CallSiteStatic *css);
@@ -285,17 +289,20 @@ typedef enum node_kind {
 } MR_NodeKind;
 
 /* must correspond to fixed_size_int_bytes in deep_profiler/read_profile.m */
-#define MR_FIXED_SIZE_INT_BYTES 4
+#define MR_FIXED_SIZE_INT_BYTES 8
 
 static  void    MR_write_csd_ptr(FILE *fp, const MR_CallSiteDynamic *csd);
-static  void    MR_write_out_coverage_point(FILE *fp, 
-                    const MR_CoveragePointStatic *cp_static, 
-                    const MR_Unsigned *cp);
+#ifdef MR_DEEP_PROFILING_COVERAGE
+static  void    MR_write_out_coverage_points_static(FILE *fp, 
+                    const MR_ProcStatic *ps);
+static  void    MR_write_out_coverage_points_dynamic(FILE *fp,
+                    const MR_ProcDynamic *pd);
+#endif
 static  void    MR_write_ptr(FILE *fp, MR_NodeKind kind, const int node_id);
 static  void    MR_write_kind(FILE *fp, MR_CallSiteKind kind);
 static  void    MR_write_byte(FILE *fp, const char byte);
 static  void    MR_write_num(FILE *fp, unsigned long num);
-static  void    MR_write_fixed_size_int(FILE *fp, unsigned long num);
+static  void    MR_write_fixed_size_int(FILE *fp, MR_uint_least64_t num);
 static  void    MR_write_string(FILE *fp, const char *ptr);
 
 /*----------------------------------------------------------------------------*/
@@ -414,6 +421,8 @@ MR_write_out_profiling_tree(void)
     MR_write_out_deep_id_string(deep_fp);
     MR_write_out_program_name(deep_fp);
 
+    MR_write_out_deep_flags(deep_fp);
+
     /* We overwrite these zeros after seeking back to table_sizes_offset */
     table_sizes_offset = ftell(deep_fp);
     if (table_sizes_offset == -1) {
@@ -444,8 +453,6 @@ MR_write_out_profiling_tree(void)
     MR_write_num(deep_fp, MR_quanta_inside_deep_profiling_code);
     MR_write_num(deep_fp, MR_quanta_outside_deep_profiling_code);
     MR_write_num(deep_fp, num_call_seqs);
-    MR_write_byte(deep_fp, sizeof(MR_Word));
-    MR_write_byte(deep_fp, 0); /* the canonical flag is MR_FALSE = 0 */
 
     MR_call_site_dynamic_table = MR_create_hash_table(MR_hash_table_size);
     MR_call_site_static_table  = MR_create_hash_table(MR_hash_table_size);
@@ -693,7 +700,7 @@ static void
 MR_write_out_deep_id_string(FILE *fp)
 {
     /* Must be the same as deep_id_string in deep_profiler/read_profile.m */
-    const char  *id_string = "Mercury deep profiler data version 6\n";
+    const char  *id_string = "Mercury deep profiler data version 7\n";
 
     fputs(id_string, fp);
 }
@@ -704,6 +711,58 @@ MR_write_out_program_name(FILE *fp)
     MR_write_string(fp, MR_progname);
 }
 
+/*
+** Flags in the deep profiler data file's header.  Any bit without a meaning
+** here must be set to zero as it it may be used in the future.  The next
+** line marks 16 bit boundaries in the 64bit flags value:
+**
+**       48  32  16   0
+*/
+#define MR_DEEP_FLAG_WORDSIZE_MASK \
+    (0x00000000000000FF)
+#define MR_DEEP_FLAG_WORDSIZE_SHIFT \
+    (0)
+#define MR_DEEP_FLAG_CANONICAL_MASK \
+    (0x0000000000000100)
+#define MR_DEEP_FLAG_CANONICAL_SHIFT \
+    (8)
+/* This flag is not yet implemented */
+#define MR_DEEP_FLAG_COMPRESSION_MASK \
+    (0x0000000000000200)
+#define MR_DEEP_FLAG_COMPRESSION_SHIFT \
+    (9)
+/* This flag is two bits wide had has three valid values */
+#define MR_DEEP_FLAG_COVERAGE_DATA_TYPE_MASK \
+    (0x0000000000000B00)
+#define MR_DEEP_FLAG_COVERAGE_DATA_TYPE_SHIFT \
+    (10)
+
+#if !defined(MR_DEEP_PROFILING_COVERAGE)
+    #define MR_DEEP_FLAG_COVERAGE_DATA_TYPE_VALUE 0
+#elif defined(MR_DEEP_PROFILING_COVERAGE_STATIC)
+    #define MR_DEEP_FLAG_COVERAGE_DATA_TYPE_VALUE 1
+#elif defined(MR_DEEP_PROFILING_COVERAGE_DYNAMIC)
+    #define MR_DEEP_FLAG_COVERAGE_DATA_TYPE_VALUE 2
+#endif
+
+static void
+MR_write_out_deep_flags(FILE *fp)
+{
+    MR_uint_least64_t       flags = 0;
+
+    flags |= MR_DEEP_FLAG_WORDSIZE_MASK & 
+        (sizeof(MR_Word) << MR_DEEP_FLAG_WORDSIZE_SHIFT);
+
+    flags |= MR_DEEP_FLAG_CANONICAL_MASK & 
+        (1 << MR_DEEP_FLAG_CANONICAL_SHIFT);
+    
+    flags |= MR_DEEP_FLAG_COVERAGE_DATA_TYPE_MASK & 
+        (MR_DEEP_FLAG_COVERAGE_DATA_TYPE_VALUE <<
+            MR_DEEP_FLAG_COVERAGE_DATA_TYPE_SHIFT);
+
+    MR_write_fixed_size_int(fp, flags);
+} 
+
 static void
 MR_write_out_procrep_id_string(FILE *fp)
 {
@@ -914,7 +973,6 @@ MR_write_out_proc_static(FILE *deep_fp, 
     MR_write_num(deep_fp, ps->MR_ps_line_number);
     MR_write_byte(deep_fp, ps->MR_ps_is_in_interface);
     MR_write_num(deep_fp, ps->MR_ps_num_call_sites);
-    MR_write_num(deep_fp, ps->MR_ps_num_coverage_points);
 
     /*
     ** Write out pointers to Call Site Statics.  These are read in with the
@@ -937,24 +995,11 @@ MR_write_out_proc_static(FILE *deep_fp, 
 
     /*
     ** Write out coverage points.  This is read in as part of the proc static.
-    **/
-    /* TODO: Don't know if MR_Unsigned will work with MR_write_num() will work
-    ** on 64bit machines, depends on size of unsigned.
     */
-    for (i = 0; i < ps->MR_ps_num_coverage_points; i++)
-    {
-#ifdef MR_DEEP_PROFILING_DEBUG
-        if (debug_fp != NULL) {
-            fprintf(debug_fp, "in proc_static %p/%p/%d, coverage point %d\n",
-                proc_layout, ps, ps_id, i);
-        }
+#ifdef MR_DEEP_PROFILING_COVERAGE
+    MR_write_out_coverage_points_static(deep_fp, ps);
 #endif
         
-        MR_write_out_coverage_point(deep_fp, 
-            &ps->MR_ps_coverage_points_static[i], &ps->MR_ps_coverage_points[i]);
-    }
-    
-    
     /*
     ** Write out the actual call site statics,  These are read in after the
     ** proc static, not as part of it.
@@ -1290,6 +1335,10 @@ MR_write_out_proc_dynamic(FILE *fp, cons
     }
 #endif
 
+#ifdef MR_DEEP_PROFILING_COVERAGE
+    MR_write_out_coverage_points_dynamic(fp, pd);
+#endif
+
     for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
         MR_write_kind(fp, ps->MR_ps_call_sites[i].MR_css_kind);
         switch (ps->MR_ps_call_sites[i].MR_css_kind)
@@ -1377,23 +1426,66 @@ MR_write_csd_ptr(FILE *fp, const MR_Call
     MR_write_ptr(fp, kind_csd, csd_id);
 }
 
-
+#ifdef MR_DEEP_PROFILING_COVERAGE
 static void
-MR_write_out_coverage_point(FILE *fp, const MR_CoveragePointStatic *cp_static,
-    const MR_Unsigned *cp)
+MR_write_out_coverage_points_static(FILE *fp, const MR_ProcStatic *ps)
 {
+    const MR_CoveragePointStatic *cps_static;
+    cps_static = ps->MR_ps_coverage_points_static;
+#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC
+    const MR_Unsigned *cps;
+    cps = ps->MR_ps_coverage_points;
+#endif
+    unsigned int i;
+
+    MR_write_num(fp, ps->MR_ps_num_coverage_points);
+    for (i = 0; i < ps->MR_ps_num_coverage_points; i++) {
+
 #ifdef  MR_DEEP_PROFILING_DETAIL_DEBUG
     if (debug_fp != NULL) {
-        fprintf(debug_fp, "coverage point: %s,%d: %d\n", 
-            cp_static->MR_cp_goal_path, cp_static->MR_cp_type, *cp);
+            fprintf(debug_fp, "coverage point: %s,%d",
+                cps_static[i].MR_cp_goal_path, cps_static[i].MR_cp_type);
+#ifdef  MR_DEEP_PROFILING_COVERAGE_STATIC
+            fprintf(debug_fp, ": %d\n", cps[i]);
+#else
+            fprintf(debug_fp, "\n");
+#endif
     }
 #endif
 
-    MR_write_string(fp, cp_static->MR_cp_goal_path),
-    MR_write_num(fp, cp_static->MR_cp_type),
-    MR_write_num(fp, *cp);
+        MR_write_string(fp, cps_static[i].MR_cp_goal_path);
+        MR_write_num(fp, cps_static[i].MR_cp_type);
+#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC
+        MR_write_num(fp, cps[i]);
+#endif
+    }
 }
 
+static void
+MR_write_out_coverage_points_dynamic(FILE *fp, const MR_ProcDynamic *pd)
+{
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+    const MR_Unsigned *cps;
+    unsigned int i;
+    unsigned int ncps;
+
+    cps = pd->MR_pd_coverage_points;
+    ncps = pd->MR_pd_proc_layout->MR_sle_proc_static->
+        MR_ps_num_coverage_points;
+
+    MR_write_num(fp, ncps);
+    for (i = 0; i < ncps; i++) {
+#ifdef  MR_DEEP_PROFILING_DETAIL_DEBUG
+        if (debug_fp != NULL) {
+            fprintf(debug_fp, "coverage point: %d",
+                cps[i]);
+        }
+#endif
+        MR_write_num(fp, cps[i]);
+    }
+#endif
+};
+#endif
 
 static void
 MR_write_ptr(FILE *fp, MR_NodeKind kind, int node_id)
@@ -1470,7 +1562,7 @@ MR_write_num(FILE *fp, unsigned long num
 }
 
 static void
-MR_write_fixed_size_int(FILE *fp, unsigned long num)
+MR_write_fixed_size_int(FILE *fp, MR_uint_least64_t num)
 {
     int i;
 
@@ -1480,8 +1572,6 @@ MR_write_fixed_size_int(FILE *fp, unsign
     }
 #endif
 
-    MR_deep_assert(NULL, NULL, NULL, (MR_Integer) num >= 0);
-
     for (i = 0; i < MR_FIXED_SIZE_INT_BYTES; i++) {
         putc(num & ((1 << 8) - 1), fp);
         num = num >> 8;
Index: runtime/mercury_deep_profiling.h
===================================================================
RCS file: /home/mercury1/repository/mercury/runtime/mercury_deep_profiling.h,v
retrieving revision 1.21
diff -u -p -b -r1.21 mercury_deep_profiling.h
--- runtime/mercury_deep_profiling.h	20 Sep 2008 11:38:05 -0000	1.21
+++ runtime/mercury_deep_profiling.h	21 Sep 2010 00:54:40 -0000
@@ -48,9 +48,11 @@ struct MR_ProfilingMetrics_Struct {
 	unsigned				MR_own_allocs;
 	unsigned				MR_own_words;
 #endif
+
 	/* ANSI/ISO C requires non-empty structs */
 #if !defined(MR_DEEP_PROFILING_PORT_COUNTS) && \
-	!defined(MR_DEEP_PROFILING_TIMING) && !defined(MR_DEEP_PROFILING_MEMORY)
+	!defined(MR_DEEP_PROFILING_TIMING) && \
+	!defined(MR_DEEP_PROFILING_MEMORY)
 	unsigned				dummy;
 #endif
 };
@@ -93,6 +95,7 @@ struct MR_ProcStatic_Struct {
 	int					MR_ps_next_csd_stack_slot;
 	int					MR_ps_old_outermost_stack_slot;
 
+#ifdef MR_DEEP_PROFILING_COVERAGE
 	/*
 	** The number of coverage points in a procedure and static information
 	** about them are fixed at compile time, so they are associated with
@@ -101,12 +104,14 @@ struct MR_ProcStatic_Struct {
 	const MR_Unsigned			MR_ps_num_coverage_points;
 	const MR_CoveragePointStatic * const	MR_ps_coverage_points_static;
 	
+#ifdef MR_DEEP_PROFILING_COVERAGE_STATIC
 	/*
-	** Coverage data is kept in the ProcStatic structure initially, at a
-	** later stage more fine-grained coverage idata may be associated with
-	** ProcDynamic if performance is not affected too much.
+	** Coverage data is kept in the ProcStatic structure if we're
+	** collecting it statically.  See also MR_dyn_coverage_points
 	*/
 	MR_Unsigned * const			MR_ps_coverage_points;
+#endif
+#endif
 };
 
 struct MR_CallSiteDynamic_Struct {
@@ -118,6 +123,14 @@ struct MR_CallSiteDynamic_Struct {
 struct MR_ProcDynamic_Struct {
 	const MR_ProcLayout			*MR_pd_proc_layout;
 	MR_CallSiteDynamic			**MR_pd_call_site_ptr_ptrs;
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+	/*
+	** Coverage data is kept in the ProcStatic structure initially, at a
+	** later stage more fine-grained coverage data may be associated with
+	** ProcDynamic if performance is not affected too much.
+	*/
+	MR_Unsigned 				*MR_pd_coverage_points;
+#endif
 };
 
 struct MR_CallSiteDynList_Struct {
@@ -222,7 +235,7 @@ typedef enum {
 
 #define	MR_new_call_site_dynamic(newcsd)				\
 	do {								\
-		newcsd = MR_PROFILING_MALLOC(MR_CallSiteDynamic);	\
+		newcsd = MR_PROFILING_NEW(MR_CallSiteDynamic);		\
 									\
 		newcsd->MR_csd_callee_ptr = NULL;			\
 		MR_init_own_ports(newcsd);				\
@@ -232,21 +245,46 @@ typedef enum {
 		MR_init_depth_count(newcsd);				\
 	} while (0)
 
+#ifdef MR_DEEP_PROFILING_COVERAGE_DYNAMIC
+  #define MR_pd_init_coverage_points(pd, ps)				\
+  	do {								\
+		int	num_cps;					\
+		int	cp_i;						\
+									\
+		num_cps = (ps)->MR_ps_num_coverage_points;		\
+		if (num_cps) {						\
+			(pd)->MR_pd_coverage_points = 			\
+			  MR_PROFILING_NEW_ARRAY(MR_Unsigned, num_cps); \
+			for (cp_i = 0; cp_i < num_cps; cp_i++) {	\
+				(pd)->MR_pd_coverage_points[cp_i] = 0;	\
+			}						\
+		}							\
+	} while (0)
+#else
+  #define MR_pd_init_coverage_points(pd, ps)				\
+ 	((void) 0)
+#endif
+
+/*
+** TODO: Consider merging these mallocs into one, this should improve
+** efficiency.
+*/
 #define	MR_new_proc_dynamic(pd, pl)					\
 	do {								\
 		MR_ProcStatic	*psl;					\
 		int		npdi;					\
 									\
-		(pd) = MR_PROFILING_MALLOC(MR_ProcDynamic);		\
+		(pd) = MR_PROFILING_NEW(MR_ProcDynamic);		\
 		(pd)->MR_pd_proc_layout = (pl);				\
 		psl = (pl)->MR_sle_proc_static;				\
 		(pd)->MR_pd_call_site_ptr_ptrs =			\
-			MR_PROFILING_MALLOC_ARRAY(MR_CallSiteDynamic *,	\
+			MR_PROFILING_NEW_ARRAY(MR_CallSiteDynamic *,	\
 				psl->MR_ps_num_call_sites);		\
 									\
 		for (npdi = 0; npdi < psl->MR_ps_num_call_sites; npdi++) { \
 			(pd)->MR_pd_call_site_ptr_ptrs[npdi] = NULL;	\
 		}							\
+		MR_pd_init_coverage_points(pd, psl);			\
 	} while (0)
 
 #ifdef	MR_DEEP_PROFILING_STATISTICS
@@ -317,7 +355,7 @@ typedef enum {
 
 #define	MR_make_and_link_csdlist(csdlist, newcsd, pd, csn, void_key)	\
 	do {								\
-		(csdlist) = MR_PROFILING_MALLOC(MR_CallSiteDynList);	\
+		(csdlist) = MR_PROFILING_NEW(MR_CallSiteDynList);	\
 		(csdlist)->MR_csdlist_key = (void_key);			\
 		(csdlist)->MR_csdlist_call_site = (newcsd);		\
 		(csdlist)->MR_csdlist_next = (MR_CallSiteDynList *)	\
@@ -328,7 +366,7 @@ typedef enum {
 
 #define	MR_make_and_link_csdlist_callback(csdlist, newcsd, void_key)	\
 	do {								\
-		(csdlist) = MR_PROFILING_MALLOC(MR_CallSiteDynList);	\
+		(csdlist) = MR_PROFILING_NEW(MR_CallSiteDynList);	\
 		(csdlist)->MR_csdlist_key = (void_key);			\
 		(csdlist)->MR_csdlist_call_site = (newcsd);		\
 		(csdlist)->MR_csdlist_next = *MR_current_callback_site;	\
@@ -420,7 +458,8 @@ extern	void	MR_deep_prof_init(void);
 extern	void	MR_deep_prof_turn_on_time_profiling(void);
 extern	void	MR_deep_prof_turn_off_time_profiling(void);
 
-#define MR_PROFILING_MALLOC(type)		MR_NEW(type)
-#define MR_PROFILING_MALLOC_ARRAY(type, nelems) MR_NEW_ARRAY(type, nelems)
+#define MR_PROFILING_MALLOC(size)		MR_GC_malloc(size)
+#define MR_PROFILING_NEW(type)			MR_NEW(type)
+#define MR_PROFILING_NEW_ARRAY(type, nelems) 	MR_NEW_ARRAY(type, nelems)
 
 #endif	/* not MERCURY_DEEP_PROFILING_H */
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 489 bytes
Desc: Digital signature
URL: <http://lists.mercurylang.org/archives/reviews/attachments/20100921/dd8dd069/attachment.sig>


More information about the reviews mailing list