[m-rev.] For review: Deep Profiling and Program Representation file format changes.

Paul Bone pbone at csse.unimelb.edu.au
Mon Aug 11 14:08:00 AEST 2008


For review by Zoltan.

I've bootchecked these changes in the asm_fast.gc.profdeep grade, and
tested them using mdprof_cgi, mdprof_dump and mdprof_procrep.  I'm
waiting on a bootcheck in the asm_fast.gc.decldebug grade.

Estimated hours taken: 7.5 
Branches: main

Deep profiling and program representation file format changes.

Include a table of variable names in the program representation used by the
deep profiler (Deep.procrep).  The table shouldn't contain variables
introduced by the compiler.

Include the name of the program from which the deep profile was generated in
the header of the deep profiling data file (Deep.data).

compiler/prog_rep.m:
	Optionally create the variable table within the bytecode generated for
	each procedure, The actual variable names are stored in the string table
	for the module.

compiler/stack_layout.m:
	Enable the variable table only for deep profiling builds.	

mdbcomp/program_representation.m:
	Include variable table in each program representation structure.
	
	Create predicates to read in the variable table if it is present.
	
	Create predicates to lookup a variable name from a table or generate a
	name automatically.

	Incremented version number for the program representation file format.

runtime/mercury_deep_profiling.c:
	Write out program name in header of deep profiling data.

	Increment version numbers of deep profiling and program representation
	file formats.

browser/declarative_tree.m:
deep_profiler/canonical.m:
	Conform to changes in mdbcomp/program_representation.m

deep_profiler/mdprof_procrep.m:
	Lookup and display variable names when displaying program representation.

deep_profiler/profile.m:
	Make program name part of the profile_stats structure.

deep_profiler/read_profile.m:
deep_profiler/io_combinator.m:
	Read in program name from deep profiling data.

	Incremented version number for the deep profiling file format.

deep_profiler/report.m:
deep_profiler/create_report.m:
deep_profiler/display_report.m:
	Display program name with the statistics on the menu report.

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

Index: browser/declarative_tree.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/declarative_tree.m,v
retrieving revision 1.55
diff -u -p -r1.55 declarative_tree.m
--- browser/declarative_tree.m	30 Dec 2007 11:11:06 -0000	1.55
+++ browser/declarative_tree.m	11 Aug 2008 02:08:10 -0000
@@ -907,7 +907,7 @@ trace_dependency_in_proc_defn_rep(Store,
         StartLoc = cur_goal,
         Contour = Contour0
     ),
-    ProcDefnRep = proc_defn_rep(HeadVars, GoalRep),
+    ProcDefnRep = proc_defn_rep(HeadVars, GoalRep, _),
     is_traced_grade(AllTraced),
     MaybePrims = make_primitive_list(Store, [goal_and_path(GoalRep, empty)],
         Contour, StartPath, ArgNum, TotalArgs, HeadVars, AllTraced, []),
@@ -946,7 +946,7 @@ trace_dependency_in_proc_defn_rep(Store,
 proc_defn_rep_is_catch_impl(ProcDefnRep) :-
     ProcDefnRep = proc_defn_rep([A, B, C, D],
         atomic_goal_rep(_, "exception.m", _, [D],
-            plain_call_rep("exception", "builtin_catch", [A, B, C, D]))).
+            plain_call_rep("exception", "builtin_catch", [A, B, C, D])), _).
 
 :- pred find_chain_start(S::in, R::in, arg_pos::in, term_path::in,
     dependency_chain_start(R)::out) is det <= annotated_trace(S, R).
@@ -1575,7 +1575,7 @@ find_variable_in_args(Args, ArgNum, Tota
     subterm_origin(edt_node(R))::out) is det <= annotated_trace(S, R).
 
 traverse_primitives([], Var0, TermPath0, _, ProcDefnRep, Origin) :-
-    ProcDefnRep = proc_defn_rep(HeadVars, _),
+    ProcDefnRep = proc_defn_rep(HeadVars, _, _),
     ArgPos = find_arg_pos(HeadVars, Var0),
     Origin = origin_input(ArgPos, TermPath0).
 traverse_primitives([Prim | Prims], Var0, TermPath0, Store, ProcDefnRep,
Index: compiler/prog_rep.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_rep.m,v
retrieving revision 1.60
diff -u -p -r1.60 prog_rep.m
--- compiler/prog_rep.m	3 Apr 2008 05:26:45 -0000	1.60
+++ compiler/prog_rep.m	11 Aug 2008 02:08:10 -0000
@@ -44,8 +44,19 @@
     %
 :- type var_num_map == map(prog_var, pair(int, string)).
 
+    % Describe whether a variable name table should be included in the
+    % bytecode.  The variable name table actually adds the strings into the
+    % module's string table.
+    %
+:- type include_variable_table
+    --->    include_variable_table
+    ;       do_not_include_variable_table.
+
+    % Create the bytecodes for the given procedure.
+    %
 :- pred represent_proc_as_bytecodes(list(prog_var)::in, hlds_goal::in,
     instmap::in, vartypes::in, var_num_map::in, module_info::in,
+    include_variable_table::in, 
     stack_layout_info::in, stack_layout_info::out, list(int)::out) is det.
 
 %---------------------------------------------------------------------------%
@@ -82,37 +93,108 @@
             ).
 
 represent_proc_as_bytecodes(HeadVars, Goal, InstMap0, VarTypes, VarNumMap,
-        ModuleInfo, !StackInfo, ProcRepBytes) :-
+        ModuleInfo, IncludeVarTable, !StackInfo, ProcRepBytes) :-
     Goal = hlds_goal(_, GoalInfo),
     Context = goal_info_get_context(GoalInfo),
     term.context_file(Context, FileName),
-    MaxVarNum = map.foldl(max_var_num, VarNumMap, 0),
-    ( MaxVarNum =< 255 ->
-        VarNumRep = byte
-    ;
-        VarNumRep = short
-    ),
+    represent_var_table_as_bytecode(IncludeVarTable, VarNumMap, VarNumRep,
+        VarTableBytes, !StackInfo),
     Info = prog_rep_info(FileName, VarTypes, VarNumMap, VarNumRep, ModuleInfo),
-    var_num_rep_byte(VarNumRep, VarNumRepByte),
 
     string_to_byte_list(FileName, FileNameBytes, !StackInfo),
     goal_to_byte_list(Goal, InstMap0, Info, GoalBytes, !StackInfo),
-    ProcRepBytes0 = [VarNumRepByte] ++ FileNameBytes ++
+    ProcRepBytes0 = FileNameBytes ++ VarTableBytes ++
         vars_to_byte_list(Info, HeadVars) ++ GoalBytes,
     int32_to_byte_list(list.length(ProcRepBytes0) + 4, LimitBytes),
     ProcRepBytes = LimitBytes ++ ProcRepBytes0.
 
 %---------------------------------------------------------------------------%
 
+    % Create bytecodes for the variable table.
+    %
+    % If a variable table is not requested, an empty table is created.  The
+    % variable table also includes information about the representation of
+    % variable numbers within the bytecode.
+    %
+    % The representation of variables and the variable table restricts the
+    % number of possible variables in a procedure to 2^15.
+    %
+:- pred represent_var_table_as_bytecode(include_variable_table::in,
+    var_num_map::in, var_num_rep::out, list(int)::out, 
+    stack_layout_info::in, stack_layout_info::out) is det.
+
+represent_var_table_as_bytecode(IncludeVarTable, VarNumMap, VarNumRep,
+        ByteList, !StackInfo) :-
+    map.foldl(max_var_num, VarNumMap, 0) = MaxVarNum,
+    ( MaxVarNum =< 255 ->
+        VarNumRep = byte
+    ;
+        VarNumRep = short
+    ),
+    var_num_rep_byte(VarNumRep, VarNumRepByte),
+    (
+        IncludeVarTable = include_variable_table,
+        map.foldl3(var_table_entry_bytelist(VarNumRep), VarNumMap, 0, NumVars, 
+            [], VarTableEntriesBytes, !StackInfo)
+    ;
+        IncludeVarTable = do_not_include_variable_table,
+        NumVars = 0,
+        VarTableEntriesBytes = []
+    ),
+    short_to_byte_list(NumVars, NumVarsBytes),
+    ByteList = [VarNumRepByte] ++ NumVarsBytes ++ VarTableEntriesBytes.
+
 :- func max_var_num(prog_var, pair(int, string), int) = int.
 
 max_var_num(_, VarNum1 - _, VarNum2) = Max :-
-    ( VarNum1 > VarNum2 ->
-        Max = VarNum1
+    Max = max(VarNum1, VarNum2).
+
+:- pred var_table_entry_bytelist(var_num_rep::in, 
+    prog_var::in, pair(int, string)::in, int::in, int::out, 
+    list(int)::in, list(int)::out,
+    stack_layout_info::in, stack_layout_info::out) is det.
+
+var_table_entry_bytelist(VarNumRep, _ProgVar, VarNum - VarName, 
+        !NumVars, !VarTableBytes, !StackInfo) :-
+    (
+        % Some variables that the compiler creates are named automatically,
+        % these and unamed variables should not be included in the variable
+        % table.
+        compiler_introduced_varname(VarName)
+    ->
+        true
     ;
-        Max = VarNum2
+        !:NumVars = !.NumVars + 1,
+        (
+            VarNumRep = byte,
+            VarBytes = [VarNum]
+        ;
+            VarNumRep = short,
+            short_to_byte_list(VarNum, VarBytes)
+        ),
+        string_to_byte_list(VarName, VarNameBytes, !StackInfo),
+        !:VarTableBytes = VarBytes ++ VarNameBytes ++ !.VarTableBytes
     ).
 
+:- pred compiler_introduced_varname(string::in) is semidet.
+
+compiler_introduced_varname("").
+compiler_introduced_varname("ProcStaticLayout").
+compiler_introduced_varname("TopCSD").
+compiler_introduced_varname("MiddleCSD").
+compiler_introduced_varname("ActivationPtr").
+compiler_introduced_varname("SiteNum").
+compiler_introduced_varname("MethodNum").
+compiler_introduced_varname(VarName) :-
+    ( Prefix = "V_"
+    ; Prefix = "HeadVar__"
+    ; Prefix = "TypeClassInfo_for_"
+    ; Prefix = "TypeInfo_"
+    ; Prefix = "TypeCtorInfo_"
+    ; Prefix = "STATE_VARIABLE_"
+    ),
+    prefix(VarName, Prefix).
+
 %---------------------------------------------------------------------------%
 
 :- pred goal_to_byte_list(hlds_goal::in, instmap::in, prog_rep_info::in,
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.141
diff -u -p -r1.141 stack_layout.m
--- compiler/stack_layout.m	2 Jun 2008 02:27:29 -0000	1.141
+++ compiler/stack_layout.m	11 Aug 2008 02:08:10 -0000
@@ -565,8 +565,15 @@ construct_proc_layout(ProcLayoutInfo, In
             ; DeepProfiling = yes
             )
         ->
+            (
+                DeepProfiling = yes,
+                IncludeVarTable = include_variable_table
+            ;
+                DeepProfiling = no,
+                IncludeVarTable = do_not_include_variable_table
+            ),
             represent_proc_as_bytecodes(HeadVars, Goal, InstMap, VarTypes,
-                VarNumMap, ModuleInfo, !Info, ProcBytes)
+                VarNumMap, ModuleInfo, IncludeVarTable, !Info, ProcBytes)
         ;
             ProcBytes = []
         ),
Index: deep_profiler/canonical.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/canonical.m,v
retrieving revision 1.15
diff -u -p -r1.15 canonical.m
--- deep_profiler/canonical.m	23 Nov 2007 07:35:51 -0000	1.15
+++ deep_profiler/canonical.m	11 Aug 2008 02:08:10 -0000
@@ -848,7 +848,11 @@ do_merge_profiles(BaseInitDeep, OtherIni
     extract_num_callseqs(BaseInitDeep, BaseNumCallSeqs),
     list.map(extract_num_callseqs, OtherInitDeeps, OtherNumCallSeqs),
     list.foldl(int_add, OtherNumCallSeqs, BaseNumCallSeqs, ConcatNumCallSeqs),
-    ConcatProfileStats = profile_stats(
+    
+    % The program names are not checked.  The new profile is named after the
+    % base profile.
+    BaseProgramName = BaseInitDeep ^ init_profile_stats ^ program_name,
+    ConcatProfileStats = profile_stats(BaseProgramName,
         ConcatMaxCSD, BaseMaxCSS, ConcatMaxPD, BaseMaxPS, ConcatNumCallSeqs,
         BaseTicksPerSec, InstrumentQuanta, UserQuanta, WordSize, yes),
     % The root part is a temporary lie.
Index: deep_profiler/create_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/create_report.m,v
retrieving revision 1.4
diff -u -p -r1.4 create_report.m
--- deep_profiler/create_report.m	5 Aug 2008 00:54:18 -0000	1.4
+++ deep_profiler/create_report.m	11 Aug 2008 02:08:10 -0000
@@ -56,12 +56,14 @@ create_report(Cmd, Deep, Report) :-
         Report = report_message(MessageInfo)
     ;
         Cmd = deep_cmd_menu,
-        Deep ^ profile_stats = profile_stats(NumCSD, NumCSS, NumPD, NumPS,
+        Deep ^ profile_stats = profile_stats(ProgramName, 
+            NumCSD, NumCSS, NumPD, NumPS,
             QuantaPerSec, InstrumentationQuanta, UserQuanta, NumCallsequs,
             _, _),
         NumCliques = array.max(Deep ^ clique_members),
-        MenuInfo = menu_info(QuantaPerSec, UserQuanta, InstrumentationQuanta,
-            NumCallsequs, NumCSD, NumCSS, NumPD, NumPS, NumCliques),
+        MenuInfo = menu_info(ProgramName, QuantaPerSec, UserQuanta,
+            InstrumentationQuanta, NumCallsequs, NumCSD, NumCSS, NumPD, NumPS,
+            NumCliques),
         Report = report_menu(ok(MenuInfo))
     ;
         Cmd = deep_cmd_top_procs(Limit, CostKind, InclDesc, Scope),
Index: deep_profiler/display_report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/display_report.m,v
retrieving revision 1.7
diff -u -p -r1.7 display_report.m
--- deep_profiler/display_report.m	6 Aug 2008 08:15:03 -0000	1.7
+++ deep_profiler/display_report.m	11 Aug 2008 02:08:10 -0000
@@ -121,7 +121,7 @@ report_to_display(Deep, Prefs, Report) =
 :- pred display_report_menu(deep::in, menu_info::in, display::out) is det.
 
 display_report_menu(Deep, MenuInfo, Display) :-
-    MenuInfo = menu_info(QuantaPerSec, UserQuanta, InstQuanta,
+    MenuInfo = menu_info(ProgramName, QuantaPerSec, UserQuanta, InstQuanta,
         NumCallseqs, NumCSD, NumCSS, NumPD, NumPS, NumClique),
 
     ShouldDisplayTimes = should_display_times(Deep),
@@ -211,7 +211,8 @@ display_report_menu(Deep, MenuInfo, Disp
 
     % Display the table section of the report.
     ProfilingStatistics =
-        [("Quanta per second:"          - td_i(QuantaPerSec)),
+        [("Profile generated for:"      - td_s(ProgramName)),
+        ("Quanta per second:"           - td_i(QuantaPerSec)),
         ("Quanta in user code:"         - td_i(UserQuanta)),
         ("Quanta in instrumentation:"   - td_i(InstQuanta)),
         ("Call sequence numbers:"       - td_i(NumCallseqs)),
Index: deep_profiler/dump.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/dump.m,v
retrieving revision 1.15
diff -u -p -r1.15 dump.m
--- deep_profiler/dump.m	4 Aug 2008 03:17:45 -0000	1.15
+++ deep_profiler/dump.m	11 Aug 2008 02:08:10 -0000
@@ -288,9 +288,11 @@ get_static_ptrs_from_dynamic_proc(ProcSt
 :- pred dump_init_profile_stats(profile_stats::in, io::di, io::uo) is det.
 
 dump_init_profile_stats(Stats, !IO) :-
-    Stats = profile_stats(MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec,
-        InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize, Canonical),
+    Stats = profile_stats(ProgramName, MaxCSD, MaxCSS, MaxPD, MaxPS,
+        TicksPerSec, InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize,
+        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),
     io.format("\tmax_css = %d\n", [i(MaxCSS)], !IO),
     io.format("\tmax_pd  = %d\n", [i(MaxPD)],  !IO),
Index: deep_profiler/io_combinator.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/io_combinator.m,v
retrieving revision 1.8
diff -u -p -r1.8 io_combinator.m
--- deep_profiler/io_combinator.m	5 Oct 2006 04:37:50 -0000	1.8
+++ deep_profiler/io_combinator.m	11 Aug 2008 02:08:12 -0000
@@ -648,6 +648,36 @@
     pred(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_12(
+    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(T1, T2, T3, T4, T5, T6, T7, T8, T9, T10, T11, T12, maybe_error(T)),
+    maybe_error(T), io, io).
+:- mode io_combinator.maybe_error_sequence_12(
+    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, out) is det,
+    out, di, uo) is det.
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
@@ -2337,6 +2367,96 @@ io_combinator.maybe_error_sequence_11(P1
         Res = error(Err)
     ).
 
+io_combinator.maybe_error_sequence_12(P1, P2, P3, P4, P5, P6, P7, P8, P9, P10,
+        P11, P12, 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(Combine, T1, T2, T3,
+                                                        T4, T5, T6, T7, T8, T9,
+                                                        T10, T11, T12, Res)
+                                                ;
+                                                    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/mdprof_procrep.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/mdprof_procrep.m,v
retrieving revision 1.2
diff -u -p -r1.2 mdprof_procrep.m
--- deep_profiler/mdprof_procrep.m	30 Dec 2007 08:24:22 -0000	1.2
+++ deep_profiler/mdprof_procrep.m	11 Aug 2008 02:08:12 -0000
@@ -94,11 +94,11 @@ print_module(ModuleRep, !IO) :-
 
 print_proc(ProcRep, !IO) :-
     ProcRep = proc_rep(ProcLabel, ProcDefnRep),
-    ProcDefnRep = proc_defn_rep(ArgVarReps, GoalRep),
+    ProcDefnRep = proc_defn_rep(ArgVarReps, GoalRep, VarTable),
     print_proc_label(ProcLabel, !IO),
-    print_args(ArgVarReps, !IO),
+    print_args(VarTable, ArgVarReps, !IO),
     io.write_string(" :-\n", !IO),
-    print_goal(1, GoalRep, !IO),
+    print_goal(VarTable, 1, GoalRep, !IO),
     io.nl(!IO).
 
 :- pred print_proc_label(string_proc_label::in, io::di, io::uo) is det.
@@ -125,44 +125,46 @@ print_proc_label(ProcLabel, !IO) :-
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_goal(int::in, goal_rep::in, io::di, io::uo) is det.
+:- pred print_goal(var_table::in, int::in, goal_rep::in, io::di, io::uo) 
+    is det.
 
-print_goal(Indent, GoalRep, !IO) :-
+print_goal(VarTable, Indent, GoalRep, !IO) :-
     (
         GoalRep = conj_rep(ConjGoalReps),
-        print_conj(Indent, ConjGoalReps, !IO)
+        print_conj(VarTable, Indent, ConjGoalReps, !IO)
     ;
         GoalRep = disj_rep(DisjGoalReps),
         indent(Indent, !IO),
         io.write_string("(\n", !IO),
-        print_disj(Indent, DisjGoalReps, no, !IO),
+        print_disj(VarTable, Indent, DisjGoalReps, no, !IO),
         indent(Indent, !IO),
         io.write_string(")\n", !IO)
     ;
         GoalRep = switch_rep(SwitchVarRep, CasesRep),
         indent(Indent, !IO),
-        io.format("( switch on V%d\n", [i(SwitchVarRep)], !IO),
-        print_switch(Indent, CasesRep, no, !IO),
+        lookup_var_name(VarTable, SwitchVarRep, SwitchVarName),
+        io.format("( switch on %s\n", [s(SwitchVarName)], !IO),
+        print_switch(VarTable, Indent, CasesRep, no, !IO),
         indent(Indent, !IO),
         io.write_string(")\n", !IO)
     ;
         GoalRep = ite_rep(CondRep, ThenRep, ElseRep),
         indent(Indent, !IO),
         io.write_string("(\n", !IO),
-        print_goal(Indent + 1, CondRep, !IO),
+        print_goal(VarTable, Indent + 1, CondRep, !IO),
         indent(Indent, !IO),
         io.write_string("->\n", !IO),
-        print_goal(Indent + 1, ThenRep, !IO),
+        print_goal(VarTable, Indent + 1, ThenRep, !IO),
         indent(Indent, !IO),
         io.write_string(";\n", !IO),
-        print_goal(Indent + 1, ElseRep, !IO),
+        print_goal(VarTable, Indent + 1, ElseRep, !IO),
         indent(Indent, !IO),
         io.write_string(")\n", !IO)
     ;
         GoalRep = negation_rep(SubGoalRep),
         indent(Indent, !IO),
         io.write_string("not (\n", !IO),
-        print_goal(Indent + 1, SubGoalRep, !IO),
+        print_goal(VarTable, Indent + 1, SubGoalRep, !IO),
         indent(Indent, !IO),
         io.write_string(")\n", !IO)
     ;
@@ -176,44 +178,46 @@ print_goal(Indent, GoalRep, !IO) :-
             io.write_string(" cut", !IO)
         ),
         io.write_string(" (\n", !IO),
-        print_goal(Indent + 1, SubGoalRep, !IO),
+        print_goal(VarTable, Indent + 1, SubGoalRep, !IO),
         indent(Indent, !IO),
         io.write_string(")\n", !IO)
     ;
         GoalRep = atomic_goal_rep(_DetismRep, _FileName, _LineNumber,
             _BoundVars, AtomicGoalRep),
-        print_atomic_goal(Indent, AtomicGoalRep, !IO)
+        print_atomic_goal(VarTable, Indent, AtomicGoalRep, !IO)
     ).
 
-:- pred print_conj(int::in, list(goal_rep)::in, io::di, io::uo) is det.
+:- pred print_conj(var_table::in, int::in, list(goal_rep)::in, io::di, io::uo)
+    is det.
 
-print_conj(Indent, GoalReps, !IO) :-
+print_conj(VarTable, Indent, GoalReps, !IO) :-
     (
         GoalReps = [],
         indent(Indent, !IO),
         io.write_string("true\n", !IO)
     ;
         GoalReps = [_ | _],
-        print_conj_2(Indent, GoalReps, !IO)
+        print_conj_2(VarTable, Indent, GoalReps, !IO)
     ).
 
-:- pred print_conj_2(int::in, list(goal_rep)::in, io::di, io::uo) is det.
+:- pred print_conj_2(var_table::in, int::in, list(goal_rep)::in, 
+    io::di, io::uo) is det.
 
-print_conj_2(_Indent, [], !IO).
-print_conj_2(Indent, [GoalRep | GoalReps], !IO) :-
+print_conj_2(_, _Indent, [], !IO).
+print_conj_2(VarTable, Indent, [GoalRep | GoalReps], !IO) :-
     % We use the absence of a separator to denote conjunction.
     %
     % We could try to append the comma at the end of each goal that is
     % not last in a conjunction, but that would be significant work,
     % and (at least for now) there is no real need for it.
-    print_goal(Indent, GoalRep, !IO),
-    print_conj_2(Indent, GoalReps, !IO).
+    print_goal(VarTable, Indent, GoalRep, !IO),
+    print_conj_2(VarTable, Indent, GoalReps, !IO).
 
-:- pred print_disj(int::in, list(goal_rep)::in, bool::in, io::di, io::uo)
-    is det.
+:- pred print_disj(var_table::in, int::in, list(goal_rep)::in, bool::in, 
+    io::di, io::uo) is det.
 
-print_disj(_Indent, [], _PrintSemi, !IO).
-print_disj(Indent, [GoalRep | GoalReps], PrintSemi, !IO) :-
+print_disj(_, _Indent, [], _PrintSemi, !IO).
+print_disj(VarTable, Indent, [GoalRep | GoalReps], PrintSemi, !IO) :-
     (
         PrintSemi = no
     ;
@@ -221,14 +225,14 @@ print_disj(Indent, [GoalRep | GoalReps],
         indent(Indent, !IO),
         io.write_string(";\n", !IO)
     ),
-    print_goal(Indent + 1, GoalRep, !IO),
-    print_disj(Indent, GoalReps, yes, !IO).
+    print_goal(VarTable, Indent + 1, GoalRep, !IO),
+    print_disj(VarTable, Indent, GoalReps, yes, !IO).
 
-:- pred print_switch(int::in, list(case_rep)::in, bool::in, io::di, io::uo)
-    is det.
+:- pred print_switch(var_table::in, int::in, list(case_rep)::in, bool::in, 
+    io::di, io::uo) is det.
 
-print_switch(_Indent, [], _PrintSemi, !IO).
-print_switch(Indent, [CaseRep | CaseReps], PrintSemi, !IO) :-
+print_switch(_, _Indent, [], _PrintSemi, !IO).
+print_switch(VarTable, Indent, [CaseRep | CaseReps], PrintSemi, !IO) :-
     (
         PrintSemi = no
     ;
@@ -239,8 +243,8 @@ print_switch(Indent, [CaseRep | CaseReps
     CaseRep = case_rep(MainConsIdArityRep, OtherConsIdArityRep, GoalRep),
     print_cons_id_and_arity(Indent + 1, MainConsIdArityRep, !IO),
     list.foldl(print_cons_id_and_arity(Indent + 1), OtherConsIdArityRep, !IO),
-    print_goal(Indent + 1, GoalRep, !IO),
-    print_switch(Indent, CaseReps, yes, !IO).
+    print_goal(VarTable, Indent + 1, GoalRep, !IO),
+        print_switch(VarTable, Indent, CaseReps, yes, !IO).
 
 :- pred print_cons_id_and_arity(int::in, cons_id_arity_rep::in,
     io::di, io::uo) is det.
@@ -252,9 +256,10 @@ print_cons_id_and_arity(Indent, ConsIdAr
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_atomic_goal(int::in, atomic_goal_rep::in, io::di, io::uo) is det.
+:- pred print_atomic_goal(var_table::in, int::in, atomic_goal_rep::in, 
+    io::di, io::uo) is det.
 
-print_atomic_goal(Indent, AtomicGoalRep, !IO) :-
+print_atomic_goal(VarTable, Indent, AtomicGoalRep, !IO) :-
     indent(Indent, !IO),
     (
         (
@@ -264,8 +269,9 @@ print_atomic_goal(Indent, AtomicGoalRep,
             AtomicGoalRep = unify_deconstruct_rep(VarRep, ConsIdRep, ArgReps),
             UnifyOp = "=>"
         ),
-        io.format("V%d %s %s", [i(VarRep), s(UnifyOp), s(ConsIdRep)], !IO),
-        print_args(ArgReps, !IO)
+        lookup_var_name(VarTable, VarRep, VarName),
+        io.format("%s %s %s", [s(VarName), s(UnifyOp), s(ConsIdRep)], !IO),
+        print_args(VarTable, ArgReps, !IO)
     ;
         (
             AtomicGoalRep = partial_construct_rep(VarRep, ConsIdRep,
@@ -276,94 +282,107 @@ print_atomic_goal(Indent, AtomicGoalRep,
                 MaybeArgReps),
             UnifyOp = "=>"
         ),
-        io.format("V%d %s %s", [i(VarRep), s(UnifyOp), s(ConsIdRep)], !IO),
-        print_maybe_args(MaybeArgReps, !IO)
+        lookup_var_name(VarTable, VarRep, VarName),
+        io.format("%s %s %s", [s(VarName), s(UnifyOp), s(ConsIdRep)], !IO),
+        print_maybe_args(VarTable, MaybeArgReps, !IO)
     ;
         AtomicGoalRep = unify_assign_rep(TargetRep, SourceRep),
-        io.format("V%d := V%d", [i(TargetRep), i(SourceRep)], !IO)
+        lookup_var_name(VarTable, TargetRep, TargetName),
+        lookup_var_name(VarTable, SourceRep, SourceName),
+        io.format("%s := %s", [s(TargetName), s(SourceName)], !IO)
     ;
         AtomicGoalRep = cast_rep(TargetRep, SourceRep),
-        io.format("cast V%d to V%d", [i(SourceRep), i(TargetRep)], !IO)
+        lookup_var_name(VarTable, TargetRep, TargetName),
+        lookup_var_name(VarTable, SourceRep, SourceName),
+        io.format("cast %s to %s", [s(SourceName), s(TargetName)], !IO)
     ;
         AtomicGoalRep = unify_simple_test_rep(TargetRep, SourceRep),
-        io.format("V%d == V%d", [i(SourceRep), i(TargetRep)], !IO)
+        lookup_var_name(VarTable, TargetRep, TargetName),
+        lookup_var_name(VarTable, SourceRep, SourceName),
+        io.format("%s == %s", [s(SourceName), s(TargetName)], !IO)
     ;
         AtomicGoalRep = pragma_foreign_code_rep(Args),
         io.write_string("foreign_proc(", !IO),
-        print_args(Args, !IO),
+        print_args(VarTable, Args, !IO),
         io.write_string(")", !IO)
     ;
         AtomicGoalRep = higher_order_call_rep(HOVarRep, Args),
-        io.format("V%d(", [i(HOVarRep)], !IO),
-        print_args(Args, !IO),
+        lookup_var_name(VarTable, HOVarRep, HOVarName),
+        io.format("%s(", [s(HOVarName)], !IO),
+        print_args(VarTable, Args, !IO),
         io.write_string(")", !IO)
     ;
         AtomicGoalRep = method_call_rep(TCIVarRep, MethodNumber, Args),
-        io.format("method %d of V%d(", [i(MethodNumber), i(TCIVarRep)], !IO),
-        print_args(Args, !IO),
+        lookup_var_name(VarTable, TCIVarRep, TCIVarName),
+        io.format("method %d of %s(", [i(MethodNumber), s(TCIVarName)], !IO),
+        print_args(VarTable, Args, !IO),
         io.write_string(")", !IO)
     ;
         AtomicGoalRep = plain_call_rep(Module, Pred, Args),
         io.format("%s.%s", [s(Module), s(Pred)], !IO),
-        print_args(Args, !IO)
+        print_args(VarTable, Args, !IO)
     ;
         AtomicGoalRep = builtin_call_rep(Module, Pred, Args),
         io.format("builtin %s.%s", [s(Module), s(Pred)], !IO),
-        print_args(Args, !IO)
+        print_args(VarTable, Args, !IO)
     ;
         AtomicGoalRep = event_call_rep(Event, Args),
         io.format("event %s", [s(Event)], !IO),
-        print_args(Args, !IO)
+        print_args(VarTable, Args, !IO)
     ),
     io.nl(!IO).
 
 %-----------------------------------------------------------------------------%
 
-:- pred print_args(list(var_rep)::in, io::di, io::uo) is det.
+:- pred print_args(var_table::in, list(var_rep)::in, io::di, io::uo) is det.
 
-print_args(Args, !IO) :-
+print_args(VarTable, Args, !IO) :-
     (
         Args = []
     ;
         Args = [_ | _],
         io.write_string("(", !IO),
-        print_args_2(Args, "", !IO),
+        print_args_2(VarTable, Args, "", !IO),
         io.write_string(")", !IO)
     ).
 
-:- pred print_args_2(list(var_rep)::in, string::in, io::di, io::uo) is det.
+:- pred print_args_2(var_table::in, list(var_rep)::in, string::in, 
+    io::di, io::uo) is det.
 
-print_args_2([], _, !IO).
-print_args_2([VarRep | VarReps], Prefix, !IO) :-
-    io.format("%sV%d", [s(Prefix), i(VarRep)], !IO),
-    print_args_2(VarReps, ", ", !IO).
+print_args_2(_,        [],                 _,      !IO).
+print_args_2(VarTable, [VarRep | VarReps], Prefix, !IO) :-
+    lookup_var_name(VarTable, VarRep, VarName),
+    io.write_string(Prefix ++ VarName, !IO),
+    print_args_2(VarTable, VarReps, ", ", !IO).
 
-:- pred print_maybe_args(list(maybe(var_rep))::in, io::di, io::uo) is det.
+:- pred print_maybe_args(var_table::in, list(maybe(var_rep))::in, 
+    io::di, io::uo) is det.
 
-print_maybe_args(MaybeArgs, !IO) :-
+print_maybe_args(VarTable, MaybeArgs, !IO) :-
     (
         MaybeArgs = []
     ;
         MaybeArgs = [_ | _],
         io.write_string("(", !IO),
-        print_maybe_args_2(MaybeArgs, "", !IO),
+        print_maybe_args_2(VarTable, MaybeArgs, "", !IO),
         io.write_string(")", !IO)
     ).
 
-:- pred print_maybe_args_2(list(maybe(var_rep))::in, string::in,
+:- pred print_maybe_args_2(var_table::in, list(maybe(var_rep))::in, string::in,
     io::di, io::uo) is det.
 
-print_maybe_args_2([], _, !IO).
-print_maybe_args_2([MaybeVarRep | MaybeVarReps], Prefix, !IO) :-
+print_maybe_args_2(_, [], _, !IO).
+print_maybe_args_2(VarTable, [MaybeVarRep | MaybeVarReps], Prefix, !IO) :-
+    io.write_string(Prefix, !IO),
     (
         MaybeVarRep = no,
-        io.write_string(Prefix, !IO),
         io.write_string("_", !IO)
     ;
         MaybeVarRep = yes(VarRep),
-        io.format("%sV%d", [s(Prefix), i(VarRep)], !IO)
+        lookup_var_name(VarTable, VarRep, VarName),
+        io.write_string(VarName, !IO)
     ),
-    print_maybe_args_2(MaybeVarReps, ", ", !IO).
+    print_maybe_args_2(VarTable, MaybeVarReps, ", ", !IO).
 
 :- pred indent(int::in, io::di, io::uo) is det.
 
Index: deep_profiler/profile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/profile.m,v
retrieving revision 1.19
diff -u -p -r1.19 profile.m
--- deep_profiler/profile.m	29 Jul 2008 23:57:59 -0000	1.19
+++ deep_profiler/profile.m	11 Aug 2008 02:08:12 -0000
@@ -37,6 +37,7 @@
 
 :- type profile_stats
     --->    profile_stats(
+                program_name            :: string,
                 num_csd                 :: int,
                 num_css                 :: int,
                 num_pd                  :: int,
Index: deep_profiler/read_profile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/read_profile.m,v
retrieving revision 1.24
diff -u -p -r1.24 read_profile.m
--- deep_profiler/read_profile.m	4 Aug 2008 03:17:45 -0000	1.24
+++ deep_profiler/read_profile.m	11 Aug 2008 02:08:12 -0000
@@ -65,7 +65,8 @@ read_call_graph(FileName, Res, !IO) :-
         read_deep_id_string(Res1, !IO),
         (
             Res1 = ok(_),
-            io_combinator.maybe_error_sequence_11(
+            io_combinator.maybe_error_sequence_12(
+                read_string,
                 read_fixed_size_int,
                 read_fixed_size_int,
                 read_fixed_size_int,
@@ -77,7 +78,8 @@ read_call_graph(FileName, Res, !IO) :-
                 read_deep_byte,
                 read_deep_byte,
                 read_ptr(pd),
-                (pred(MaxCSD::in, MaxCSS::in,
+                (pred(ProgName::in, 
+                        MaxCSD::in, MaxCSS::in,
                         MaxPD::in, MaxPS::in,
                         TicksPerSec::in,
                         InstrumentQuanta::in,
@@ -87,8 +89,8 @@ read_call_graph(FileName, Res, !IO) :-
                         CanonicalFlag::in,
                         RootPDI::in,
                         ResInitDeep::out) is det :-
-                    InitDeep0 = init_deep(MaxCSD, MaxCSS,
-                        MaxPD, MaxPS,
+                    InitDeep0 = init_deep(basename(ProgName), 
+                        MaxCSD, MaxCSS, MaxPD, MaxPS,
                         TicksPerSec, InstrumentQuanta, UserQuanta,
                         NumCallSeqs,
                         WordSize, CanonicalFlag,
@@ -139,7 +141,7 @@ read_deep_id_string(Res, !IO) :-
     %
 :- func deep_id_string = string.
 
-deep_id_string = "Mercury deep profiler data version 5\n".
+deep_id_string = deep_id_prefix ++ " 6\n".
 
     % Return the part of deep_id_string that is version independent.
     %
@@ -147,19 +149,61 @@ deep_id_string = "Mercury deep profiler 
 
 deep_id_prefix = "Mercury deep profiler data version".
 
-:- func init_deep(int, int, int, int, int, int, int, int, int, int, int)
-    = initial_deep.
+    % Strip the directory paths off the given string.
+    %
+    % basename("/bin/ls") = "ls"
+    %
+:- func basename(string) = string.
+
+basename(Path) = Base :-
+    string.to_char_list(Path, PathChars),
+    basename_chars(PathChars, MaybeBaseChars),
+    (
+        MaybeBaseChars = no,
+        BaseChars = PathChars
+    ;
+        MaybeBaseChars = yes(BaseChars)
+    ),
+    string.from_char_list(BaseChars, Base).
+    
+:- pred basename_chars(list(char)::in, maybe(list(char))::out) is det.
+
+basename_chars([], no).
+basename_chars([Char | Chars], MaybeResult) :-
+    basename_chars(Chars, MaybeResult0),
+    (
+        MaybeResult0 = yes(_),
+        MaybeResult = MaybeResult0
+    ;
+        MaybeResult0 = no,
+        (
+            path_separator(Char)
+        ->
+            MaybeResult = yes(Chars)
+        ;
+            MaybeResult = no
+        )
+    ).
+
+:- pred path_separator(char::in) is semidet.
+
+path_separator('/').
+path_separator('\\').
+
+:- func init_deep(string, int, int, int, int, int, int, int, int, int, int,
+    int) = initial_deep.
 
-init_deep(MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec, InstrumentQuanta,
-        UserQuanta, NumCallSeqs, WordSize, CanonicalByte, RootPDI)
-        = InitDeep :-
+init_deep(ProgName, MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec,
+        InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize, CanonicalByte,
+        RootPDI) = InitDeep :-
     ( CanonicalByte = 0 ->
         CanonicalFlag = no
     ;
         CanonicalFlag = yes
     ),
-    InitStats = profile_stats(MaxCSD, MaxCSS, MaxPD, MaxPS, TicksPerSec,
-        InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize, CanonicalFlag),
+    InitStats = profile_stats(ProgName, MaxCSD, MaxCSS, MaxPD, MaxPS, 
+        TicksPerSec, InstrumentQuanta, UserQuanta, NumCallSeqs, WordSize,
+        CanonicalFlag),
     InitDeep = initial_deep(
         InitStats,
         make_pdptr(RootPDI),
Index: deep_profiler/report.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/report.m,v
retrieving revision 1.4
diff -u -p -r1.4 report.m
--- deep_profiler/report.m	5 Aug 2008 00:54:18 -0000	1.4
+++ deep_profiler/report.m	11 Aug 2008 02:08:12 -0000
@@ -59,6 +59,7 @@
                 % These statistics are displayed on the menu of the mdprof_cgi
                 % program.
 
+                program_name                :: string,
                 quanta_per_sec              :: int,
                 user_quanta                 :: int,
                 inst_quanta                 :: int,
Index: mdbcomp/program_representation.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/program_representation.m,v
retrieving revision 1.32
diff -u -p -r1.32 program_representation.m
--- mdbcomp/program_representation.m	29 Jul 2008 23:58:00 -0000	1.32
+++ mdbcomp/program_representation.m	11 Aug 2008 02:08:13 -0000
@@ -114,7 +114,10 @@
                 list(var_rep),
 
                 % The procedure body.
-                goal_rep
+                goal_rep,
+
+                % The variable table.
+                var_table
             ).
 
 :- type goal_rep
@@ -254,6 +257,19 @@
     ;       erroneous_rep
     ;       failure_rep.
 
+    % A table of var_rep to string mappings.
+    %
+    % This table may not contain all the variables in the procedure.  Variables
+    % created by the compiler are not included.  The table may be empty if it's
+    % not required, such as when used with the declarative debugger.
+    %
+:- type var_table.
+
+    % Lookup the name of a variable within the variable table.  If the variable
+    % is unknown a distinct name is automatically generated.
+    %
+:- pred lookup_var_name(var_table::in, var_rep::in, string::out) is det.
+
     % If the given atomic goal behaves like a call in the sense that it
     % generates events as ordinary calls do, then return the list of variables
     % that are passed as arguments.
@@ -528,8 +544,10 @@
 :- import_module char.
 :- import_module exception.
 :- import_module int.
+:- import_module map.
 :- import_module require.
 :- import_module string.
+:- import_module svmap.
 
 atomic_goal_generates_event_like_call(GoalRep) = Generates :-
     (
@@ -751,6 +769,16 @@ goal_type_byte(19, goal_event_call).
 var_num_rep_byte(byte, 0).
 var_num_rep_byte(short, 1).
 
+:- type var_table == map(var_rep, string).
+
+lookup_var_name(VarTable, VarRep, String) :-
+    ( map.search(VarTable, VarRep, StringPrime) ->
+        String = StringPrime
+    ;
+        % Generate an automatic name for the variable. 
+        String = string.format("V_%d", [i(VarRep)])
+    ).
+
 %-----------------------------------------------------------------------------%
 
 :- pred read_file_as_bytecode(string::in, io.res(bytecode)::out,
@@ -844,7 +872,7 @@ read_prog_rep_file(FileName, Result, !IO
             list.reverse(RevModuleReps, ModuleReps),
             Result = ok(prog_rep(ModuleReps))
         ;
-            Msg = FileName ++ "is not a valid program representation file",
+            Msg = FileName ++ ": is not a valid program representation file",
             Result = error(io.make_io_error(Msg))
         )
     ).
@@ -853,7 +881,7 @@ read_prog_rep_file(FileName, Result, !IO
     %
 :- func procrep_id_string = string.
 
-procrep_id_string = "Mercury deep profiler procrep version 1\n".
+procrep_id_string = "Mercury deep profiler procrep version 2\n".
 
 :- pred read_module_reps(bytecode::in,
     list(module_rep)::in, list(module_rep)::out,
@@ -903,12 +931,12 @@ read_proc_rep(ByteCode, StringTable, Pro
     read_string_proc_label(ByteCode, ProcLabel, !Pos),
     StartPos = !.Pos,
     read_int32(ByteCode, Size, !Pos),
-    read_var_num_rep(ByteCode, VarNumRep, !Pos),
     read_string_via_offset(ByteCode, StringTable, FileName, !Pos),
     Info = read_proc_rep_info(FileName),
+    read_var_table(ByteCode, StringTable, VarNumRep, VarTable, !Pos), 
     read_vars(VarNumRep, ByteCode, HeadVars, !Pos),
     read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos),
-    ProcDefnRep = proc_defn_rep(HeadVars, Goal),
+    ProcDefnRep = proc_defn_rep(HeadVars, Goal, VarTable),
     require(unify(!.Pos, StartPos + Size),
         "trace_read_proc_defn_rep: limit mismatch"),
     ProcRep = proc_rep(ProcLabel, ProcDefnRep).
@@ -948,6 +976,43 @@ read_string_proc_label(ByteCode, ProcLab
 
 %-----------------------------------------------------------------------------%
 
+    % Read the var table from the bytecode.  The var table names all the
+    % variables used in the procedure representation.
+    % 
+    % The representation of variables and the variable table restricts the
+    % number of possible variables in a procedure to 2^16.
+    %
+:- pred read_var_table(bytecode::in, string_table::in,  var_num_rep::out, 
+    map(var_rep, string)::out, int::in, int::out) is semidet.
+
+read_var_table(ByteCode, StringTable, VarNumRep, VarTable, !Pos) :-
+    read_var_num_rep(ByteCode, VarNumRep, !Pos),
+    read_short(ByteCode, NumVarsInTable, !Pos),
+    read_var_table_entries(NumVarsInTable, VarNumRep, ByteCode, StringTable,
+        map.init, VarTable, !Pos).
+
+    % Read entries from the symbol table until the number of entries left to
+    % read is zero.
+    %
+:- pred read_var_table_entries(var_rep::in, var_num_rep::in, bytecode::in,
+    string_table::in, map(var_rep, string)::in, map(var_rep, string)::out,
+    int::in, int::out) is semidet.
+
+read_var_table_entries(NumVarsInTable, VarNumRep, ByteCode, StringTable,
+        !VarTable, !Pos) :-
+    ( NumVarsInTable > 0 ->
+        read_var(VarNumRep, ByteCode, VarRep, !Pos),
+        read_string_via_offset(ByteCode, StringTable, VarName, !Pos),
+        svmap.insert(VarRep, VarName, !VarTable),
+        read_var_table_entries(NumVarsInTable - 1, VarNumRep, ByteCode, 
+            StringTable, !VarTable, !Pos)
+    ;
+        % No more variables to read.
+        true
+    ).
+
+%----------------------------------------------------------------------------%
+
 :- pragma foreign_export("C", trace_read_proc_defn_rep(in, in, out),
     "MR_MDBCOMP_trace_read_proc_defn_rep").
 
@@ -965,12 +1030,12 @@ trace_read_proc_defn_rep(Bytes, LabelLay
         DummyByteCode = bytecode(Bytes, 4),
         read_int32(DummyByteCode, Size, !Pos),
         ByteCode = bytecode(Bytes, Size),
-        read_var_num_rep(ByteCode, VarNumRep, !Pos),
         read_string_via_offset(ByteCode, StringTable, FileName, !Pos),
         Info = read_proc_rep_info(FileName),
+        read_var_table(ByteCode, StringTable, VarNumRep, VarTable, !Pos),
         read_vars(VarNumRep, ByteCode, HeadVars, !Pos),
         read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos),
-        ProcDefnRep = proc_defn_rep(HeadVars, Goal),
+        ProcDefnRep = proc_defn_rep(HeadVars, Goal, VarTable),
         require(unify(!.Pos, Size),
             "trace_read_proc_defn_rep: limit mismatch")
     ).
Index: runtime/mercury_deep_profiling.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_deep_profiling.c,v
retrieving revision 1.30
diff -u -p -r1.30 mercury_deep_profiling.c
--- runtime/mercury_deep_profiling.c	29 Jul 2008 23:58:01 -0000	1.30
+++ runtime/mercury_deep_profiling.c	11 Aug 2008 02:08:13 -0000
@@ -261,6 +261,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_call_site_static(FILE *fp,
                     const MR_CallSiteStatic *css);
@@ -384,6 +385,7 @@ MR_write_out_profiling_tree(void)
     FILE                    *check_fp;
     int                     ticks_per_sec;
     unsigned                num_call_seqs;
+    long                    table_sizes_offset;
 
     deep_fp = fopen(MR_MDPROF_DATA_FILENAME, "wb+");
     if (deep_fp == NULL) {
@@ -409,8 +411,15 @@ MR_write_out_profiling_tree(void)
     }
 #endif
 
-    /* We overwrite these zeros (and the id string) after the seek below. */
     MR_write_out_deep_id_string(deep_fp);
+    MR_write_out_program_name(deep_fp);
+
+    /* We overwrite these zeros after seeking back to table_sizes_offset */
+    table_sizes_offset = ftell(deep_fp);
+    if (table_sizes_offset == -1) {
+        MR_deep_data_output_error("ftell failed for ",
+            MR_MDPROF_DATA_FILENAME);
+    }
     MR_write_fixed_size_int(deep_fp, 0);
     MR_write_fixed_size_int(deep_fp, 0);
     MR_write_fixed_size_int(deep_fp, 0);
@@ -465,12 +474,11 @@ MR_write_out_profiling_tree(void)
         MR_address_of_write_out_proc_statics != NULL);
     (*MR_address_of_write_out_proc_statics)(deep_fp, procrep_fp);
 
-    if (fseek(deep_fp, 0L, SEEK_SET) != 0) {
-        MR_deep_data_output_error("cannot seek to start of",
+    if (fseek(deep_fp, table_sizes_offset, SEEK_SET) != 0) {
+        MR_deep_data_output_error("cannot seek to header of",
             MR_MDPROF_DATA_FILENAME);
     }
 
-    MR_write_out_deep_id_string(deep_fp);
     MR_write_fixed_size_int(deep_fp, MR_call_site_dynamic_table->last_id);
     MR_write_fixed_size_int(deep_fp, MR_call_site_static_table->last_id);
     MR_write_fixed_size_int(deep_fp, MR_proc_dynamic_table->last_id);
@@ -685,19 +693,25 @@ 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 5\n";
+    const char  *id_string = "Mercury deep profiler data version 6\n";
 
     fputs(id_string, fp);
 }
 
 static void
+MR_write_out_program_name(FILE *fp)
+{
+    MR_write_string(fp, MR_progname);
+}
+
+static void
 MR_write_out_procrep_id_string(FILE *fp)
 {
     /*
     ** Must be the same as procrep_id_string in
     ** mdbcomp/program_representation.m
     */
-    const char  *id_string = "Mercury deep profiler procrep version 1\n";
+    const char  *id_string = "Mercury deep profiler procrep version 2\n";
 
     fputs(id_string, fp);
 }

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


More information about the reviews mailing list