[m-rev.] for review: procedure representations for the deep profiler

Zoltan Somogyi zs at csse.unimelb.edu.au
Tue Sep 11 11:47:13 AEST 2007


For review by anyone.

Zoltan.

Make a representation of the program available to the deep profiler. We do
this by letting the user request, via the option "--deep-procrep-file"
in MERCURY_OPTIONS, that when the Deep.data file is written, a Deep.procrep
file should be written alongside it.

The intended use of this information is the discovery of profitable
parallelism. When a conjunction contains two expensive calls, e.g. p(...) and
q(...) connected by some shared variables, the potential gain from executing
them in parallel is limited by how early p produces those variables and how
late q consumes them, and knowing this requires access to the code of p and q.

Since the debugger and the deep profiler both need access to program
representations, put the relevant data structures and the operations on them
in mdbcomp. The data structures are significantly expanded, since the deep
profiler deals with the whole program, while the debugger was interested only
in one procedure at a time.

The layout structures have to changes as well. In a previous change, I changed
proc layout structures to make room for the procedure representation even in
non-debugging grades, but this isn't enough, since the procedure representation
refers to the module's string table. This diff therefore makes some parts of
the module layout structure, including of course the string table, also
available in non-debugging grades.

configure.in:
	Check whether the installed compiler can process switches on foreign
	enums correctly, since this diff depends on that.

runtime/mercury_stack_layout.[ch]:
runtime/mercury_types.h:
	Add a new structure, MR_ModuleCommonLayout, that holds the part of
	the module layout that is common to deep profiling and debugging.

runtime/mercury_deep_profiling.[ch]:
	The old "deep profiling token" enum type was error prone, since at
	each point in the data file, only a subset was applicable. This diff
	breaks up the this enum into several enums, each consisting of the
	choice applicable at a given point.

	This also allows some of the resulting enums to be used in procrep
	files.

	Rename some enums and functions to avoid ambiguities, and in one case
	to conform to our naming scheme.

	Make write_out_proc_statics take a second argument. This is a FILE *
	that (if not NULL) asks write_out_proc_statics to write the
	representation of the current module to specified stream.

	These module representations go into the middle part of the program
	representation file. Add functions to write out the prologue and
	epilogue of this file.

	Write out procedure representations if this is requested.

	Factor out some code that is now used in more than one place.

runtime/mercury_deep_profiling_hand.h:
	Conform to the changes to mercury_deep_profiling.h.

runtime/mercury_builtin_types.c:
	Pass the extra argument in the argument lists of invocations of
	write_out_proc_statics.

runtime/mercury_trace_base.[ch]:
	Conform to the name change from proc_rep to proc_defn_rep in mdbcomp.

runtime/mercury_grade.h:
	Due to the change to layout structures, increment the binary
	compatibility version numbers for both debug and deep profiling grades.

runtime/mercury_wrapper.[ch]:
	Provide two new MERCURY_OPTION options. The first --deep-procrep-file,
	allows the user to ask for the program representation to be generated.
	The second, --deep-random-write, allows tools/bootcheck to request that
	only a fraction of all program invocations should generate any deep
	profiling output.

	The first option will be documented once it is tested much more fully.
	The second option is deliberately not documented.

	Update the type of the variable that holds the address of the
	(mkinit-generated) write_out_proc_statics function to accept the second
	argument.

util/mkinit.c:
	Pass the extra argument in the argument list of write_out_proc_statics.

mdbcomp/program_representation.m:
	Extend the existing data structures for representing a procedure body
	to represent a procedure (complete with name), a module and a program.
	The name is implemented a string_proc_label, a form of proc_label that
	can be written out to files. This replaces the old proc_id type the
	deep profiler.

	Extend the representation of switches to record the identity of the
	variable being switched on, and the cons_ids of the arms. Without the
	former, we cannot be sure when a variable is first used, and the latter
	is needed for meaningful prettyprinting of procedure bodies.

	Add code for reading in files of bytecodes, and for making sense of the
	bytecodes themselves. (It is this code that uses foreign enums.)

mdbcomp/prim_data.m:
	Note the relationship of proc_label with string_proc_label.

mdbcomp/rtti_access.m:
	Add the access operations needed to find module string tables with the
	new organization of layout structures.

	Provide operations on bytecodes and string tables generally.

trace/mercury_trace_cmd_browsing.c:
	Conform to the change to mdbcomp/program_representation.m.

compiler/layout.m:
	Add support for a MR_ModuleCommonLayout.

	Rename some function symbols to avoid ambiguities.

compiler/layout_out.m:
	Handle the new structure.

compiler/stack_layout.m:
	Generate the new structure and the procedure representation bytecode
	in deep profiling grades.

compiler/llds_out.m:
	Generate the code required to write out the prologue and epilogue
	of program representation files.

	Pass the extra argument in the argument lists of invocations of
	write_out_proc_statics that tells those invocations to write out
	the module representations between the prologue and the epilogue.

compiler/prog_rep.m:
	When generating bytecodes, include the new information for switches.

compiler/continuation_info.m:
	Replace a bool with a more expressive type.

compiler/proc_rep.m:
	Conform to the change to continuation_info.m.

compiler/opt_debug.m:
	Conform to the change to layout.m.

deep_profiler/mdprof_procrep.m:
	A new test program to test the reading of program representations.

deep_profiler/DEEP_FLAGS.in:
deep_profiler/Mmakefile:
	Copy the contents of the mdbcomp module to this directory on demand,
	instead of linking to it. This is necessary now that the deep profiler
	depends directly on mdbcomp even if it is compiled in a non-debugging
	grade.

	The arrangements for doing is were copied from the slice directory,
	which has long done the same.

	Avoid a duplicate include of Mmake.deep.params.

	Add the new test program to the list of programs in this directory.

Mmakefile:
	Go through deep_profiler/Mmakefile when deciding whether to do "mmake
	depend" in the deep_profiler directory. The old actions won't work
	correctly now that we need to copy some files from mdbcomp before we
	can run "mmake depend".

deep_profiler/profile.m:
	Remove the code that was moved (in cleaned-up form) to mdbcomp.

deep_profiler/dump.m:
deep_profiler/profile.m:
	Conform to the changes above.

browser/declarative_execution.m:
browser/declarative_tree.m:
	Conform to the changes in mdbcomp.

doc/user_guide.texi:
	Add commented out documentation of the two new options.

slice/Mmakefile:
	Fix formatting, and a bug.

library/exception.m:
library/par_builtin.m:
library/thread.m:
library/thread.semaphore.m:
	Update all the handwritten modules to pass the extra argument now
	required by write_out_proc_statics.

tests/debugger/declarative/dependency.exp:
	Conform to the change from proc_rep to proc_defn_rep.

tools/bootcheck:
	Write out deep profiling data only from every 25th invocation, since
	otherwise the time for a bootcheck takes six times as long in deep
	profiling grades than in asm_fast.gc.

	However, do test the ability to write out program representations.

	Use the mkinit from the workspace, not the installed one.

	Don't disable line wrapping.

cvs diff: Diffing .
Index: Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/Mmakefile,v
retrieving revision 1.123
diff -u -b -r1.123 Mmakefile
--- Mmakefile	15 Jun 2007 13:38:43 -0000	1.123
+++ Mmakefile	29 Aug 2007 13:50:43 -0000
@@ -148,21 +148,12 @@
 dep_deep_profiler:
 endif
 
-deep_profiler/$(deps_subdir)mdprof_cgi.dep: \
-		library/$(deps_subdir)$(STD_LIB_NAME).dep
-	+cd deep_profiler && $(SUBDIR_MMAKE) mdprof_cgi.depend
-
-deep_profiler/$(deps_subdir)mdprof_test.dep: \
-		library/$(deps_subdir)$(STD_LIB_NAME).dep
-	+cd deep_profiler && $(SUBDIR_MMAKE) mdprof_test.depend
-
-deep_profiler/$(deps_subdir)mdprof_dump.dep: \
-		library/$(deps_subdir)$(STD_LIB_NAME).dep
-	+cd deep_profiler && $(SUBDIR_MMAKE) mdprof_dump.depend
-
+deep_profiler/$(deps_subdir)mdprof_cgi.dep \
+deep_profiler/$(deps_subdir)mdprof_test.dep \
+deep_profiler/$(deps_subdir)mdprof_dump.dep \
 deep_profiler/$(deps_subdir)mdprof_feedback.dep: \
 		library/$(deps_subdir)$(STD_LIB_NAME).dep
-	+cd deep_profiler && $(SUBDIR_MMAKE) mdprof_feedback.depend
+	+cd deep_profiler && $(SUBDIR_MMAKE) depend
 
 # depend_library MUST be done before depend_compiler and depend_profiler
 
Index: configure.in
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/configure.in,v
retrieving revision 1.499
diff -u -b -r1.499 configure.in
--- configure.in	13 Aug 2007 01:10:39 -0000	1.499
+++ configure.in	8 Sep 2007 01:39:56 -0000
@@ -275,7 +275,20 @@
 
 		:- pred return_rtti_version(int::out) is det.
 
-		:- pragma foreign_decl("C", local, "").
+		:- pragma foreign_decl("C", local, "
+		typedef enum {
+			enum1, enum2
+		} Enum;
+		").
+
+		:- type c_enum
+			--->	c_enum_1
+			;	c_enum_2.
+
+		:- pragma foreign_enum("C", c_enum/0, [[
+			c_enum_1 - "enum1",
+			c_enum_2 - "enum2"
+		]]).
 
 		:- type x ---> x.
 		:- pragma foreign_type("C", x, "MR_Integer",
@@ -324,6 +337,7 @@
 			--compound-compare-builtins-2007-07-09 \
 			--erlang-native-code \
 			--no-no-det-warning-compound-compare-2007-07-17 \
+			--foreign-enum-switch-fix \
 			</dev/null >&AC_FD_CC 2>&1 &&
 		test "`./conftest 2>&1 | tr -d '\015'`" = "Hello, world" &&
 		# Test for the --record-term-sizes-as-words option.
cvs diff: Diffing analysis
cvs diff: Diffing bindist
cvs diff: Diffing boehm_gc
cvs diff: Diffing boehm_gc/Mac_files
cvs diff: Diffing boehm_gc/cord
cvs diff: Diffing boehm_gc/cord/private
cvs diff: Diffing boehm_gc/doc
cvs diff: Diffing boehm_gc/include
cvs diff: Diffing boehm_gc/include/private
cvs diff: Diffing boehm_gc/libatomic_ops-1.2
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/doc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/gcc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/hpc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/ibmc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/icc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/msftc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/src/atomic_ops/sysdeps/sunc
cvs diff: Diffing boehm_gc/libatomic_ops-1.2/tests
cvs diff: Diffing boehm_gc/tests
cvs diff: Diffing boehm_gc/windows-untested
cvs diff: Diffing boehm_gc/windows-untested/vc60
cvs diff: Diffing boehm_gc/windows-untested/vc70
cvs diff: Diffing boehm_gc/windows-untested/vc71
cvs diff: Diffing browser
Index: browser/declarative_execution.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/declarative_execution.m,v
retrieving revision 1.60
diff -u -b -r1.60 declarative_execution.m
--- browser/declarative_execution.m	31 Jul 2007 05:48:17 -0000	1.60
+++ browser/declarative_execution.m	6 Sep 2007 11:02:27 -0000
@@ -297,8 +297,8 @@
 :- pred get_pred_attributes(proc_label::in, module_name::out, string::out,
     int::out, pred_or_func::out) is det.
 
-:- pred call_node_maybe_proc_rep(trace_node(R)::in(trace_node_call),
-    maybe(proc_rep)::out) is det.
+:- pred call_node_maybe_proc_defn_rep(trace_node(R)::in(trace_node_call),
+    maybe(proc_defn_rep)::out) is det.
 
 %-----------------------------------------------------------------------------%
 
@@ -490,21 +490,27 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pragma promise_pure(call_node_maybe_proc_rep/2).
-
-call_node_maybe_proc_rep(CallNode, MaybeProcRep) :-
+call_node_maybe_proc_defn_rep(CallNode, MaybeProcDefnRep) :-
     Label = CallNode ^ call_label,
     ( call_node_bytecode_layout(Label, ProcLayout) ->
-        ( semipure have_cached_proc_rep(ProcLayout, ProcRep) ->
-            MaybeProcRep = yes(ProcRep)
+        promise_pure (
+            ( semipure have_cached_proc_defn_rep(ProcLayout, ProcDefnRep) ->
+                MaybeProcDefnRep = yes(ProcDefnRep)
+            ;
+                ByteCodeBytes = proc_bytecode_bytes(ProcLayout),
+                (
+                    trace_read_proc_defn_rep(ByteCodeBytes, Label, ProcDefnRep)
+                ->
+                    impure cache_proc_defn_rep(ProcLayout, ProcDefnRep),
+                    MaybeProcDefnRep = yes(ProcDefnRep)
         ;
-            lookup_proc_bytecode(ProcLayout, ByteCode),
-            read_proc_rep(ByteCode, Label, ProcRep),
-            impure cache_proc_rep(ProcLayout, ProcRep),
-            MaybeProcRep = yes(ProcRep)
+                    throw(internal_error("call_node_maybe_proc_defn_rep",
+                        "cannot interpret proc bytecode"))
+                )
+            )
         )
     ;
-        MaybeProcRep = no
+        MaybeProcDefnRep = no
     ).
 
 :- pred call_node_bytecode_layout(label_layout::in, proc_layout::out)
@@ -532,61 +538,44 @@
     }
 ").
 
-:- pred lookup_proc_bytecode(proc_layout::in, bytecode::out) is det.
-
-    % Default version for non-C backends.
-lookup_proc_bytecode(_, dummy_bytecode).
-
-:- pragma foreign_proc("C",
-    lookup_proc_bytecode(ProcLayout::in, ByteCode::out),
-    [will_not_call_mercury, thread_safe, promise_pure],
-"
-    ByteCode = ProcLayout->MR_sle_body_bytes;
-#ifdef MR_DEBUG_PROC_REP
-    printf(""lookup_proc_bytecode: %p %p\\n"", ProcLayout, ByteCode);
-#endif
-").
-
-:- semipure pred have_cached_proc_rep(proc_layout::in, proc_rep::out)
+:- semipure pred have_cached_proc_defn_rep(proc_layout::in, proc_defn_rep::out)
     is semidet.
 
     % Default version for non-C backends.
-have_cached_proc_rep(_, _) :-
+have_cached_proc_defn_rep(_, _) :-
     semidet_fail.
 
 :- pragma foreign_proc("C",
-    have_cached_proc_rep(ProcLayout::in, ProcRep::out),
+    have_cached_proc_defn_rep(ProcLayout::in, ProcDefnRep::out),
     [will_not_call_mercury, thread_safe, promise_semipure],
 "
-    ProcRep = MR_lookup_proc_rep(ProcLayout);
-    if (ProcRep != 0) {
+    ProcDefnRep = MR_lookup_proc_defn_rep(ProcLayout);
+    if (ProcDefnRep != 0) {
 #ifdef MR_DEBUG_PROC_REP
-        printf(""have_cached_proc_rep: %p success\\n"",
-            ProcLayout);
+        printf(""have_cached_proc_defn_rep: %p success\\n"", ProcLayout);
 #endif
         SUCCESS_INDICATOR = MR_TRUE;
     } else {
 #ifdef MR_DEBUG_PROC_REP
-        printf(""have_cached_proc_rep: %p failure\\n"",
-            ProcLayout);
+        printf(""have_cached_proc_defn_rep: %p failure\\n"", ProcLayout);
 #endif
         SUCCESS_INDICATOR = MR_FALSE;
     }
 ").
 
-:- impure pred cache_proc_rep(proc_layout::in, proc_rep::in) is det.
+:- impure pred cache_proc_defn_rep(proc_layout::in, proc_defn_rep::in) is det.
 
     % Default version for non-C backends.
-cache_proc_rep(_, _).
+cache_proc_defn_rep(_, _).
 
 :- pragma foreign_proc("C",
-    cache_proc_rep(ProcLayout::in, ProcRep::in),
+    cache_proc_defn_rep(ProcLayout::in, ProcDefnRep::in),
     [will_not_call_mercury, thread_safe],
 "
 #ifdef MR_DEBUG_PROC_REP
-    printf(""cache_proc_rep: %p %x\\n"", ProcLayout, ProcRep);
+    printf(""cache_proc_defn_rep: %p %x\\n"", ProcLayout, ProcDefnRep);
 #endif
-    MR_insert_proc_rep(ProcLayout, ProcRep);
+    MR_insert_proc_defn_rep(ProcLayout, ProcDefnRep);
 ").
 
 %-----------------------------------------------------------------------------%
Index: browser/declarative_tree.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/browser/declarative_tree.m,v
retrieving revision 1.50
diff -u -b -r1.50 declarative_tree.m
--- browser/declarative_tree.m	19 Jan 2007 07:03:58 -0000	1.50
+++ browser/declarative_tree.m	10 Sep 2007 14:29:34 -0000
@@ -715,33 +715,28 @@
 
 :- type dependency_chain_start(R)
     --->    chain_start(
+                % The argument number of the selected position in the full list
+                % of arguments, including the compiler-generated ones.
                 start_loc(R),
-                        % The argument number of the selected
-                        % position in the full list of
-                        % arguments, including the
-                        % compiler-generated ones.
 
+                % The total number of arguments including the compiler
+                % generated ones.
                 int,
-                        % The total number of arguments
-                        % including the compiler generated
-                        % ones.
 
                 int,
-                R,      % The id of the node preceding the exit
-                        % node, if start_loc is cur_goal
-                        % and the id of the node preceding the
-                        % call node if start_loc is
-                        % parent_goal.
 
-                maybe(goal_path),
-                        % No if start_loc is cur_goal;
-                        % and yes wrapped around the goal path
-                        % of the call in the parent procedure
+                % The id of the node preceding the exit node if start_loc
+                % is cur_goal, and the id of the node preceding the call node
                         % if start_loc is parent_goal.
+                R,
+
+                % No if start_loc is cur_goal; and yes wrapped around the
+                % goal path of the call in the parent procedure if start_loc
+                % is parent_goal.
+                maybe(goal_path),
 
-                maybe(proc_rep)
-                        % The body of the procedure indicated
-                        % by start_loc.
+                % The body of the procedure indicated by start_loc.
+                maybe(proc_defn_rep)
             )
 
     ;       require_explicit_subtree.
@@ -791,21 +786,21 @@
     find_chain_start(Store, Ref, ArgPos, TermPath, ChainStart),
     (
         ChainStart = chain_start(StartLoc, ArgNum, TotalArgs, NodeId,
-            StartPath, MaybeProcRep),
+            StartPath, MaybeProcDefnRep),
         Mode = start_loc_to_subterm_mode(StartLoc),
         (
-            MaybeProcRep = no,
+            MaybeProcDefnRep = no,
             Origin = origin_not_found
         ;
-            MaybeProcRep = yes(ProcRep),
+            MaybeProcDefnRep = yes(ProcDefnRep),
             (
-                trace_dependency_special_case(Store, ProcRep, Ref,
+                trace_dependency_special_case(Store, ProcDefnRep, Ref,
                     StartLoc, ArgNum, TermPath, NodeId, Origin0)
             ->
                 Origin = Origin0
             ;
-                trace_dependency_in_proc_rep(Store, TermPath, StartLoc, ArgNum,
-                    TotalArgs, NodeId, StartPath, ProcRep, Origin)
+                trace_dependency_in_proc_defn_rep(Store, TermPath, StartLoc,
+                    ArgNum, TotalArgs, NodeId, StartPath, ProcDefnRep, Origin)
             )
         )
     ;
@@ -819,16 +814,16 @@
     % by the usual subterm dependency tracking algorithm. At the moment
     % it handles tracking of subterms through catch_impl.
     %
-:- pred trace_dependency_special_case(S::in, proc_rep::in, R::in,
+:- pred trace_dependency_special_case(S::in, proc_defn_rep::in, R::in,
     start_loc(R)::in, int::in, term_path::in, R::in,
     subterm_origin(edt_node(R))::out) is semidet <= annotated_trace(S, R).
 
-trace_dependency_special_case(Store, ProcRep, Ref, StartLoc, ArgNum, TermPath,
-        NodeId, Origin) :-
+trace_dependency_special_case(Store, ProcDefnRep, Ref, StartLoc,
+        ArgNum, TermPath, NodeId, Origin) :-
     % Catch_impl's body is a single call to builtin_catch. Builtin_catch
     % doesn't generate any events, so we need to handle catch_impl specially.
 
-    proc_rep_is_catch_impl(ProcRep),
+    proc_defn_rep_is_catch_impl(ProcDefnRep),
     (
         StartLoc = parent_goal(_, _),
         % The subterm being tracked is an input to builtin_catch so we know
@@ -862,12 +857,13 @@
         )
     ).
 
-:- pred trace_dependency_in_proc_rep(S::in, term_path::in, start_loc(R)::in,
-    int::in, int::in, R::in, maybe(goal_path)::in, proc_rep::in,
-    subterm_origin(edt_node(R))::out) is det <= annotated_trace(S, R).
+:- pred trace_dependency_in_proc_defn_rep(S::in, term_path::in,
+    start_loc(R)::in, int::in, int::in, R::in, maybe(goal_path)::in,
+    proc_defn_rep::in, subterm_origin(edt_node(R))::out) is det
+    <= annotated_trace(S, R).
 
-trace_dependency_in_proc_rep(Store, TermPath, StartLoc, ArgNum,
-        TotalArgs, NodeId, StartPath, ProcRep, Origin) :-
+trace_dependency_in_proc_defn_rep(Store, TermPath, StartLoc, ArgNum,
+        TotalArgs, NodeId, StartPath, ProcDefnRep, Origin) :-
     det_trace_node_from_id(Store, NodeId, Node),
     materialize_contour(Store, NodeId, Node, [], Contour0),
     (
@@ -877,7 +873,7 @@
         StartLoc = cur_goal,
         Contour = Contour0
     ),
-    ProcRep = proc_rep(HeadVars, GoalRep),
+    ProcDefnRep = proc_defn_rep(HeadVars, GoalRep),
     is_traced_grade(AllTraced),
     MaybePrims = make_primitive_list(Store, [goal_and_path(GoalRep, [])],
         Contour, StartPath, ArgNum, TotalArgs, HeadVars, AllTraced, []),
@@ -899,22 +895,24 @@
             MaybeClosure = no,
             AdjustedTermPath = TermPath
         ),
-        traverse_primitives(Primitives, Var, AdjustedTermPath, Store, ProcRep,
-            Origin)
+        traverse_primitives(Primitives, Var, AdjustedTermPath, Store,
+            ProcDefnRep, Origin)
     ;
         MaybePrims = no,
         Origin = origin_not_found
     ).
 
-    % proc_rep_is_catch_impl(ProcRep) is true if ProcRep is a representation
-    % of exception.catch_impl (the converse is true assuming
-    % exception.builtin_catch is only called from exception.catch_impl).
+    % proc_defn_rep_is_catch_impl(ProcDefnRep) is true if ProcDefnRep
+    % is a representation of exception.catch_impl (the converse is true
+    % assuming exception.builtin_catch is only called from
+    % exception.catch_impl).
     %
-:- pred proc_rep_is_catch_impl(proc_rep::in) is semidet.
+:- pred proc_defn_rep_is_catch_impl(proc_defn_rep::in) is semidet.
 
-proc_rep_is_catch_impl(ProcRep) :-
-    ProcRep = proc_rep([A, B, C, D], atomic_goal_rep(_, "exception.m", _,
-        [D], plain_call_rep("exception", "builtin_catch", [A, B, C, D]))).
+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]))).
 
 :- 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).
@@ -954,9 +952,9 @@
         Node = node_excp(_, CallId, _, _, _, _, _),
         call_node_from_id(Store, CallId, CallNode),
         CallAtom = get_trace_call_atom(CallNode),
-        %
+
         % XXX We don't yet handle tracking of the exception value.
-        %
+
         ( trace_atom_subterm_is_ground(CallAtom, ArgPos, TermPath) ->
             find_chain_start_inside(Store, CallId, CallNode,
                 ArgPos, ChainStart)
@@ -980,7 +978,7 @@
     TotalArgs = length(CallAtom ^ atom_args),
     StartId = CallPrecId,
     StartPath = yes(CallPath),
-    parent_proc_rep(Store, CallId, StartRep),
+    parent_proc_defn_rep(Store, CallId, StartRep),
     ChainStart = chain_start(StartLoc, ArgNum, TotalArgs, StartId,
         StartPath, StartRep).
 
@@ -995,20 +993,20 @@
     TotalArgs = length(ExitAtom ^ atom_args),
     StartId = ExitNode ^ exit_preceding,
     StartPath = no,
-    call_node_maybe_proc_rep(CallNode, StartRep),
+    call_node_maybe_proc_defn_rep(CallNode, StartRep),
     ChainStart = chain_start(StartLoc, ArgNum, TotalArgs, StartId,
         StartPath, StartRep).
 
-:- pred parent_proc_rep(S::in, R::in, maybe(proc_rep)::out)
+:- pred parent_proc_defn_rep(S::in, R::in, maybe(proc_defn_rep)::out)
     is det <= annotated_trace(S, R).
 
-parent_proc_rep(Store, CallId, ProcRep) :-
+parent_proc_defn_rep(Store, CallId, ProcDefnRep) :-
     call_node_from_id(Store, CallId, Call),
     CallPrecId = Call ^ call_preceding,
     ( step_left_to_call(Store, CallPrecId, ParentCallNode) ->
-        call_node_maybe_proc_rep(ParentCallNode, ProcRep)
+        call_node_maybe_proc_defn_rep(ParentCallNode, ProcDefnRep)
     ;
-        ProcRep = no
+        ProcDefnRep = no
     ).
 
     % Finds the call node of the parent of the given node.  Fails if
@@ -1257,7 +1255,7 @@
                 "mismatch on disj"))
         )
     ;
-        Goal = switch_rep(Arms),
+        Goal = switch_rep(_SwitchVar, Cases),
         (
             Contour = [_ - ContourHeadNode | ContourTail],
             ContourHeadNode = node_switch(_, Label),
@@ -1266,7 +1264,8 @@
             list.append(Path, PathTail, ArmPath),
             PathTail = [step_switch(N, _)]
         ->
-            list.index1_det(Arms, N, Arm),
+            list.index1_det(Cases, N, Case),
+            Case = case_rep(_ConsId, _ConsIdArity, Arm),
             ArmAndPath = goal_and_path(Arm, ArmPath),
             MaybePrims = make_primitive_list(Store, [ArmAndPath | GoalPaths],
                 ContourTail, MaybeEnd, ArgNum, TotalArgs, HeadVars, AllTraced,
@@ -1526,14 +1525,15 @@
     ).
 
 :- pred traverse_primitives(list(annotated_primitive(R))::in,
-    var_rep::in, term_path::in, S::in, proc_rep::in,
+    var_rep::in, term_path::in, S::in, proc_defn_rep::in,
     subterm_origin(edt_node(R))::out) is det <= annotated_trace(S, R).
 
-traverse_primitives([], Var0, TermPath0, _, ProcRep, Origin) :-
-    ProcRep = proc_rep(HeadVars, _),
+traverse_primitives([], Var0, TermPath0, _, ProcDefnRep, Origin) :-
+    ProcDefnRep = proc_defn_rep(HeadVars, _),
     ArgPos = find_arg_pos(HeadVars, Var0),
     Origin = origin_input(ArgPos, TermPath0).
-traverse_primitives([Prim | Prims], Var0, TermPath0, Store, ProcRep, Origin) :-
+traverse_primitives([Prim | Prims], Var0, TermPath0, Store, ProcDefnRep,
+        Origin) :-
     Prim = primitive(File, Line, BoundVars, AtomicGoal, _GoalPath,
         MaybeNodeId),
     (
@@ -1545,23 +1545,25 @@
             ;
                 TermPath0 = [TermPathStep0 | TermPath],
                 list.index1_det(FieldVars, TermPathStep0, Var),
-                traverse_primitives(Prims, Var, TermPath, Store, ProcRep,
+                traverse_primitives(Prims, Var, TermPath, Store, ProcDefnRep,
                     Origin)
             )
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = unify_deconstruct_rep(CellVar, _Cons, FieldVars),
         ( list.member(Var0, BoundVars) ->
             ( list.nth_member_search(FieldVars, Var0, Pos) ->
                 traverse_primitives(Prims, CellVar, [Pos | TermPath0],
-                    Store, ProcRep, Origin)
+                    Store, ProcDefnRep, Origin)
             ;
                 throw(internal_error("traverse_primitives", "bad deconstruct"))
             )
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = partial_deconstruct_rep(_, _, MaybeFieldVars),
@@ -1574,17 +1576,18 @@
                 MaybeVar = yes(Var),
                 % This partial deconstruction bound the TermPathStep0'th
                 % argument of Var0.
-                traverse_primitives(Prims, Var, TermPath, Store, ProcRep,
+                traverse_primitives(Prims, Var, TermPath, Store, ProcDefnRep,
                     Origin)
             ;
                 MaybeVar = no,
                 % This partial deconstruction did not bind the TermPathStep0'th
                 % argument, so continue looking for the unification which did.
-                traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep,
+                traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
                     Origin)
             )
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = partial_construct_rep(_, _, MaybeFieldVars),
@@ -1601,8 +1604,8 @@
                     MaybeVar = yes(Var),
                     % The partial construction bound the TermPathStep0'th
                     % argument of Var0.
-                    traverse_primitives(Prims, Var, TermPath, Store, ProcRep,
-                        Origin)
+                    traverse_primitives(Prims, Var, TermPath, Store,
+                        ProcDefnRep, Origin)
                 ;
                     MaybeVar = no,
                     % We got to the construction which bound the outermost
@@ -1614,7 +1617,8 @@
                 )
             )
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = unify_assign_rep(ToVar, FromVar),
@@ -1622,10 +1626,11 @@
         ( list.member(Var0, BoundVars) ->
             decl_require(unify(Var0, ToVar), "traverse_primitives",
                 "bad assign"),
-            traverse_primitives(Prims, FromVar, TermPath0, Store, ProcRep,
+            traverse_primitives(Prims, FromVar, TermPath0, Store, ProcDefnRep,
                 Origin)
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = cast_rep(ToVar, FromVar),
@@ -1633,58 +1638,63 @@
         ( list.member(Var0, BoundVars) ->
             decl_require(unify(Var0, ToVar), "traverse_primitives",
                 "bad unsafe_cast"),
-            traverse_primitives(Prims, FromVar, TermPath0, Store, ProcRep,
+            traverse_primitives(Prims, FromVar, TermPath0, Store, ProcDefnRep,
                 Origin)
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = pragma_foreign_code_rep(_Args),
         ( list.member(Var0, BoundVars) ->
             Origin = origin_primitive_op(File, Line, primop_foreign_proc)
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = unify_simple_test_rep(_LVar, _RVar),
         ( list.member(Var0, BoundVars) ->
             throw(internal_error("traverse_primitives", "bad test"))
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = higher_order_call_rep(_, Args),
         traverse_call(BoundVars, File, Line, Args, MaybeNodeId, Prims,
-            Var0, TermPath0, Store, ProcRep, Origin)
+            Var0, TermPath0, Store, ProcDefnRep, Origin)
     ;
         AtomicGoal = method_call_rep(_, _, Args),
         traverse_call(BoundVars, File, Line, Args, MaybeNodeId, Prims,
-            Var0, TermPath0, Store, ProcRep, Origin)
+            Var0, TermPath0, Store, ProcDefnRep, Origin)
     ;
         AtomicGoal = plain_call_rep(Module, Name, Args),
         (
             list.member(Var0, BoundVars),
             plain_call_is_special_case(Module, Name, Args, NewVar)
         ->
-            traverse_primitives(Prims, NewVar, TermPath0, Store, ProcRep,
+            traverse_primitives(Prims, NewVar, TermPath0, Store, ProcDefnRep,
                 Origin)
         ;
             traverse_call(BoundVars, File, Line, Args, MaybeNodeId,
-                Prims, Var0, TermPath0, Store, ProcRep, Origin)
+                Prims, Var0, TermPath0, Store, ProcDefnRep, Origin)
         )
     ;
         AtomicGoal = builtin_call_rep(_, _, _),
         ( list.member(Var0, BoundVars) ->
             Origin = origin_primitive_op(File, Line, primop_builtin_call)
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ;
         AtomicGoal = event_call_rep(_, _),
         ( list.member(Var0, BoundVars) ->
             throw(internal_error("traverse_primitives", "bad event"))
         ;
-            traverse_primitives(Prims, Var0, TermPath0, Store, ProcRep, Origin)
+            traverse_primitives(Prims, Var0, TermPath0, Store, ProcDefnRep,
+                Origin)
         )
     ).
 
@@ -1713,11 +1723,11 @@
 
 :- pred traverse_call(list(var_rep)::in, string::in, int::in,
     list(var_rep)::in, maybe(R)::in, list(annotated_primitive(R))::in,
-    var_rep::in, term_path::in, S::in, proc_rep::in,
+    var_rep::in, term_path::in, S::in, proc_defn_rep::in,
     subterm_origin(edt_node(R))::out) is det <= annotated_trace(S, R).
 
 traverse_call(BoundVars, File, Line, Args, MaybeNodeId,
-        Prims, Var, TermPath, Store, ProcRep, Origin) :-
+        Prims, Var, TermPath, Store, ProcDefnRep, Origin) :-
     ( list.member(Var, BoundVars) ->
         Pos = find_arg_pos(Args, Var),
         (
@@ -1728,7 +1738,7 @@
             Origin = origin_primitive_op(File, Line, primop_untraced_call)
         )
     ;
-        traverse_primitives(Prims, Var, TermPath, Store, ProcRep, Origin)
+        traverse_primitives(Prims, Var, TermPath, Store, ProcDefnRep, Origin)
     ).
 
 %-----------------------------------------------------------------------------%
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.90
diff -u -b -r1.90 continuation_info.m
--- compiler/continuation_info.m	13 Aug 2007 03:01:38 -0000	1.90
+++ compiler/continuation_info.m	10 Sep 2007 07:12:58 -0000
@@ -122,9 +122,12 @@
                 pli_proc_body           :: hlds_goal,
                 % The body of the procedure.
 
-                pli_needs_body_rep      :: bool,
-                % Do we need to include a representation of the procedure body
-                % in the exec trace layout?
+                pli_trace_body_rep      :: trace_needs_body_rep,
+                % Does the level of execution tracing of this procedure require
+                % a representation of the procedure body in the layout
+                % structures? Note that even if this field is set to
+                % trace_does_not_need_body_rep, other options (such as deep
+                % profiling) may still ask for the body to be included.
 
                 pli_initial_instmap     :: instmap,
                 % The instmap at the start of the procedure body.
@@ -160,6 +163,10 @@
                 proc_table_struct_info
             ).
 
+:- type trace_needs_body_rep
+    --->    trace_needs_body_rep
+    ;       trace_does_not_need_body_rep.
+
     % Information about the labels internal to a procedure.
     %
 :- type proc_label_layout_info == map(int, internal_layout_info).
Index: compiler/layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout.m,v
retrieving revision 1.36
diff -u -b -r1.36 layout.m
--- compiler/layout.m	12 Jun 2007 06:06:28 -0000	1.36
+++ compiler/layout.m	4 Sep 2007 13:05:19 -0000
@@ -80,10 +80,14 @@
                 proc_layout_trav        :: proc_layout_stack_traversal,
                 proc_layout_more        :: maybe_proc_id_and_more
             )
+    ;       module_layout_common_data(  % defines MR_ModuleCommonLayout
+                module_common_name      :: module_name,
+                string_table_size       :: int,
+                string_table            :: string_with_0s
+            )
     ;       module_layout_data(         % defines MR_ModuleLayout
                 module_name             :: module_name,
-                string_table_size       :: int,
-                string_table            :: string_with_0s,
+                module_common           :: layout_name,
                 proc_layout_names       :: list(layout_name),
                 file_layouts            :: list(file_layout_data),
                 trace_level             :: trace_level,
@@ -159,13 +163,16 @@
             ).
 
 :- type maybe_proc_id_and_more
-    --->    no_proc_id
-    ;       proc_id(
+    --->    no_proc_id_and_more
+    ;       proc_id_and_more(
                 maybe_proc_static       :: maybe(proc_layout_proc_static),
                 maybe_exec_trace        :: maybe(proc_layout_exec_trace),
-                proc_body_bytes         :: list(int)
+                proc_body_bytes         :: list(int),
                                         % The procedure body represented as
                                         % a list of bytecodes.
+                proc_module_common      :: layout_name
+                                        % The name of the module_common_layout
+                                        % structure.
             ).
 
 :- type proc_layout_exec_trace          % defines MR_ExecTrace
@@ -243,6 +250,7 @@
     ;       module_layout_event_synth_attr_order(module_name, int, int)
     ;       module_layout_event_synth_order(module_name, int)
     ;       module_layout_event_specs(module_name)
+    ;       module_common_layout(module_name)
     ;       module_layout(module_name)
     ;       proc_static(rtti_proc_label)
     ;       proc_static_call_sites(rtti_proc_label).
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.92
diff -u -b -r1.92 layout_out.m
--- compiler/layout_out.m	12 Jun 2007 06:06:29 -0000	1.92
+++ compiler/layout_out.m	5 Sep 2007 16:19:19 -0000
@@ -146,11 +146,16 @@
             ModuleName, FileName, LineNumber, PredOrigin, GoalPath,
             !DeclSet, !IO)
     ;
-        Data = module_layout_data(ModuleName, StringTableSize,
-            StringTable, ProcLayoutNames, FileLayouts, TraceLevel,
+        Data = module_layout_common_data(ModuleName,
+            StringTableSize, StringTable),
+        output_module_common_layout_data_defn(ModuleName, StringTableSize,
+            StringTable, !DeclSet, !IO)
+    ;
+        Data = module_layout_data(ModuleName, ModuleCommonLayoutName,
+            ProcLayoutNames, FileLayouts, TraceLevel,
             SuppressedEvents, NumLabels, MaybeEventSet),
-        output_module_layout_data_defn(ModuleName, StringTableSize,
-            StringTable, ProcLayoutNames, FileLayouts, TraceLevel,
+        output_module_layout_data_defn(ModuleName, ModuleCommonLayoutName,
+            ProcLayoutNames, FileLayouts, TraceLevel,
             SuppressedEvents, NumLabels, MaybeEventSet, !DeclSet, !IO)
     ;
         Data = table_io_decl_data(RttiProcLabel, Kind, NumPTIs,
@@ -201,7 +206,10 @@
             _, _, _, _, _),
         LayoutName = closure_proc_id(CallerProcLabel, SeqNo, ClosureProcLabel)
     ;
-        Data = module_layout_data(ModuleName, _, _, _, _, _, _, _, _),
+        Data = module_layout_common_data(ModuleName, _, _),
+        LayoutName = module_common_layout(ModuleName)
+    ;
+        Data = module_layout_data(ModuleName, _, _, _, _, _, _, _),
         LayoutName = module_layout(ModuleName)
     ;
         Data = table_io_decl_data(RttiProcLabel, _, _, _, _),
@@ -406,6 +414,12 @@
         ModuleNameStr = sym_name_mangle(ModuleName),
         io.write_string(ModuleNameStr, !IO)
     ;
+        Data = module_common_layout(ModuleName),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_common_layout__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO)
+    ;
         Data = module_layout(ModuleName),
         io.write_string(mercury_data_prefix, !IO),
         io.write_string("_module_layout__", !IO),
@@ -580,6 +594,10 @@
         output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
+        Name = module_common_layout(_ModuleName),
+        io.write_string("static const MR_ModuleCommonLayout ", !IO),
+        output_layout_name(Name, !IO)
+    ;
         Name = module_layout(_ModuleName),
         io.write_string("static const MR_ModuleLayout ", !IO),
         output_layout_name(Name, !IO)
@@ -627,6 +645,7 @@
 layout_name_would_include_code_addr(module_layout_event_synth_order(_, _))
     = no.
 layout_name_would_include_code_addr(module_layout_event_specs(_)) = no.
+layout_name_would_include_code_addr(module_common_layout(_)) = no.
 layout_name_would_include_code_addr(module_layout(_)) = no.
 layout_name_would_include_code_addr(proc_static(_)) = no.
 layout_name_would_include_code_addr(proc_static_call_sites(_)) = no.
@@ -861,13 +880,14 @@
     ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
     Kind = maybe_proc_layout_and_more_kind(MaybeRest, ProcLabel),
     (
-        MaybeRest = no_proc_id,
+        MaybeRest = no_proc_id_and_more,
         output_proc_layout_data_defn_start(RttiProcLabel, Kind, Traversal,
             !IO),
         output_layout_no_proc_id_group(!IO),
         output_proc_layout_data_defn_end(!IO)
     ;
-        MaybeRest = proc_id(MaybeProcStatic, MaybeExecTrace, ProcBodyBytes),
+        MaybeRest = proc_id_and_more(MaybeProcStatic, MaybeExecTrace,
+            ProcBodyBytes, ModuleCommonLayout),
         (
             MaybeProcStatic = yes(ProcStatic),
             output_proc_static_data_defn(RttiProcLabel, ProcStatic, !DeclSet,
@@ -902,6 +922,8 @@
             io.write_string("};\n\n", !IO)
         ),
 
+        output_layout_decl(ModuleCommonLayout, !DeclSet, !IO),
+
         output_proc_layout_data_defn_start(RttiProcLabel, Kind, Traversal,
             !IO),
         Origin = RttiProcLabel ^ pred_info_origin,
@@ -926,12 +948,14 @@
         ),
         (
             ProcBodyBytes = [],
-            io.write_string("NULL\n", !IO)
+            io.write_string("NULL,\n", !IO)
         ;
             ProcBodyBytes = [_ | _],
             output_layout_name(proc_layout_body_bytecode(RttiProcLabel), !IO),
-            io.write_string("\n", !IO)
+            io.write_string(",\n", !IO)
         ),
+        io.write_string("&", !IO),
+        output_layout_name(ModuleCommonLayout, !IO),
         output_proc_layout_data_defn_end(!IO)
     ),
     DeclId = decl_data_addr(layout_addr(proc_layout(RttiProcLabel, Kind))),
@@ -942,10 +966,10 @@
 
 maybe_proc_layout_and_more_kind(MaybeRest, ProcLabel) = Kind :-
     (
-        MaybeRest = no_proc_id,
+        MaybeRest = no_proc_id_and_more,
         Kind = proc_layout_traversal
     ;
-        MaybeRest = proc_id(_, _, _),
+        MaybeRest = proc_id_and_more(_, _, _, _),
         Kind = proc_layout_proc_id(proc_label_user_or_uci(ProcLabel))
     ).
 
@@ -1460,18 +1484,42 @@
     %
 :- func layout_version_number = int.
 
-layout_version_number = 3.
+layout_version_number = 4.
 
-:- pred output_module_layout_data_defn(module_name::in, int::in,
-    string_with_0s::in, list(layout_name)::in, list(file_layout_data)::in,
+:- pred output_module_common_layout_data_defn(module_name::in, int::in,
+    string_with_0s::in, decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_module_common_layout_data_defn(ModuleName, StringTableSize, StringTable,
+        !DeclSet, !IO) :-
+    output_module_string_table(ModuleName, StringTableSize, StringTable,
+        !DeclSet, !IO),
+
+    ModuleCommonLayoutName = module_common_layout(ModuleName),
+    io.write_string("\n", !IO),
+    output_layout_name_storage_type_name(ModuleCommonLayoutName, yes, !IO),
+    io.write_string(" = {\n", !IO),
+    io.write_int(layout_version_number, !IO),
+    io.write_string(",\n", !IO),
+    quote_and_write_string(sym_name_to_string(ModuleName), !IO),
+    io.write_string(",\n", !IO),
+    io.write_int(StringTableSize, !IO),
+    io.write_string(",\n", !IO),
+    ModuleStringTableName = module_layout_string_table(ModuleName),
+    output_layout_name(ModuleStringTableName, !IO),
+    io.write_string("\n};\n", !IO),
+
+    decl_set_insert(decl_data_addr(layout_addr(ModuleCommonLayoutName)),
+        !DeclSet).
+
+:- pred output_module_layout_data_defn(module_name::in, layout_name::in,
+    list(layout_name)::in, list(file_layout_data)::in,
     trace_level::in, int::in, int::in, maybe(event_set_layout_data)::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_module_layout_data_defn(ModuleName, StringTableSize, StringTable,
+output_module_layout_data_defn(ModuleName, ModuleCommonLayoutName,
         ProcLayoutNames, FileLayouts, TraceLevel, SuppressedEvents,
         NumLabels, MaybeEventSetLayout, !DeclSet, !IO) :-
-    output_module_string_table(ModuleName, StringTableSize, StringTable,
-        !DeclSet, !IO),
+    output_layout_decl(module_common_layout(ModuleName), !DeclSet, !IO),
     output_module_layout_proc_vector_defn(ModuleName, ProcLayoutNames,
         ProcVectorName, !DeclSet, !IO),
     output_file_layout_data_defns(ModuleName, 0, FileLayouts,
@@ -1503,14 +1551,8 @@
     io.write_string("\n", !IO),
     output_layout_name_storage_type_name(ModuleLayoutName, yes, !IO),
     io.write_string(" = {\n", !IO),
-    io.write_int(layout_version_number, !IO),
-    io.write_string(",\n", !IO),
-    quote_and_write_string(sym_name_to_string(ModuleName), !IO),
-    io.write_string(",\n", !IO),
-    io.write_int(StringTableSize, !IO),
-    io.write_string(",\n", !IO),
-    ModuleStringTableName = module_layout_string_table(ModuleName),
-    output_layout_name(ModuleStringTableName, !IO),
+    io.write_string("&", !IO),
+    output_layout_name(ModuleCommonLayoutName, !IO),
     io.write_string(",\n", !IO),
     list.length(ProcLayoutNames, ProcLayoutVectorLength),
     io.write_int(ProcLayoutVectorLength, !IO),
@@ -2114,7 +2156,7 @@
     (
         CallSiteStatic = normal_call(Callee, TypeSubst, FileName, LineNumber,
             GoalPath),
-        io.write_string("MR_normal_call, (MR_ProcLayout *)\n&", !IO),
+        io.write_string("MR_callsite_normal_call, (MR_ProcLayout *)\n&", !IO),
         CalleeProcLabel = make_proc_label_from_rtti(Callee),
         CalleeUserOrUci = proc_label_user_or_uci(CalleeProcLabel),
         output_layout_name(proc_layout(Callee,
@@ -2128,16 +2170,16 @@
         )
     ;
         CallSiteStatic = special_call(FileName, LineNumber, GoalPath),
-        io.write_string("MR_special_call, NULL, NULL, ", !IO)
+        io.write_string("MR_callsite_special_call, NULL, NULL, ", !IO)
     ;
         CallSiteStatic = higher_order_call(FileName, LineNumber, GoalPath),
-        io.write_string("MR_higher_order_call, NULL, NULL, ", !IO)
+        io.write_string("MR_callsite_higher_order_call, NULL, NULL, ", !IO)
     ;
         CallSiteStatic = method_call(FileName, LineNumber, GoalPath),
-        io.write_string("MR_method_call, NULL, NULL, ", !IO)
+        io.write_string("MR_callsite_method_call, NULL, NULL, ", !IO)
     ;
         CallSiteStatic = callback(FileName, LineNumber, GoalPath),
-        io.write_string("MR_callback, NULL, NULL, ", !IO)
+        io.write_string("MR_callsite_callback, NULL, NULL, ", !IO)
     ),
     io.write_string("""", !IO),
     io.write_string(FileName, !IO),
Index: compiler/llds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/llds_out.m,v
retrieving revision 1.316
diff -u -b -r1.316 llds_out.m
--- compiler/llds_out.m	20 Aug 2007 03:35:57 -0000	1.316
+++ compiler/llds_out.m	4 Sep 2007 14:35:09 -0000
@@ -410,7 +410,8 @@
     io.write_string("#ifdef MR_DEEP_PROFILING\n", !IO),
     io.write_string("void ", !IO),
     output_init_name(ModuleName, !IO),
-    io.write_string("write_out_proc_statics(FILE *fp);\n", !IO),
+    io.write_string(
+        "write_out_proc_statics(FILE *deep_fp, FILE *procrep_fp);\n", !IO),
     io.write_string("#endif\n", !IO),
 
     io.write_string("#ifdef MR_RECORD_TERM_SIZES\n", !IO),
@@ -500,9 +501,15 @@
     output_write_proc_static_list_decls(LayoutDatas, !DeclSet, !IO),
     io.write_string("\nvoid ", !IO),
     output_init_name(ModuleName, !IO),
-    io.write_string("write_out_proc_statics(FILE *fp)\n", !IO),
+    io.write_string(
+        "write_out_proc_statics(FILE *deep_fp, FILE *procrep_fp)\n", !IO),
     io.write_string("{\n", !IO),
+    ModuleCommonLayoutName = module_common_layout(ModuleName),
+    io.write_string("\tMR_write_out_module_proc_reps_start(procrep_fp, &", !IO),
+    output_layout_name(ModuleCommonLayoutName, !IO),
+    io.write_string(");\n", !IO),
     output_write_proc_static_list(LayoutDatas, !IO),
+    io.write_string("\tMR_write_out_module_proc_reps_end(procrep_fp);\n", !IO),
     io.write_string("}\n", !IO),
     io.write_string("\n#endif\n\n", !IO),
 
@@ -625,7 +632,7 @@
 
 output_debugger_init_list_decls([], !DeclSet, !IO).
 output_debugger_init_list_decls([Data | Datas], !DeclSet, !IO) :-
-    ( Data = module_layout_data(ModuleName, _, _, _, _, _, _, _, _) ->
+    ( Data = module_layout_data(ModuleName, _, _, _, _, _, _, _) ->
         output_data_addr_decls(layout_addr(module_layout(ModuleName)),
             !DeclSet, !IO)
     ;
@@ -642,7 +649,7 @@
 
 output_debugger_init_list([], !IO).
 output_debugger_init_list([Data | Datas], !IO) :-
-    ( Data = module_layout_data(ModuleName, _, _, _, _, _, _, _, _) ->
+    ( Data = module_layout_data(ModuleName, _, _, _, _, _, _, _) ->
         io.write_string("\tif (MR_register_module_layout != NULL) {\n", !IO),
         io.write_string("\t\t(*MR_register_module_layout)(", !IO),
         io.write_string("\n\t\t\t&", !IO),
@@ -660,7 +667,7 @@
 output_write_proc_static_list_decls([Data | Datas], !DeclSet, !IO) :-
     (
         Data = proc_layout_data(_, _, MaybeRest),
-        MaybeRest = proc_id(yes(_), _, _)
+        MaybeRest = proc_id_and_more(yes(_), _, _, _)
     ->
         output_maybe_layout_data_decl(Data, !DeclSet, !IO)
     ;
@@ -675,17 +682,21 @@
 output_write_proc_static_list([Data | Datas], !IO) :-
     (
         Data = proc_layout_data(RttiProcLabel, _, MaybeRest),
-        MaybeRest = proc_id(yes(_), _, _)
+        MaybeRest = proc_id_and_more(yes(_), _, _, _)
     ->
         ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
         UserOrUCI = proc_label_user_or_uci(ProcLabel),
         Kind = proc_layout_proc_id(UserOrUCI),
         (
             UserOrUCI = user,
-            io.write_string("\tMR_write_out_user_proc_static(fp,\n\t\t&", !IO)
+            io.write_string(
+                "\tMR_write_out_user_proc_static(deep_fp, procrep_fp,\n\t\t&",
+                !IO)
         ;
             UserOrUCI = uci,
-            io.write_string("\tMR_write_out_uci_proc_static(fp,\n\t\t&", !IO)
+            io.write_string(
+                "\tMR_write_out_uci_proc_static(deep_fp, procrep_fp,\n\t\t&",
+                !IO)
         ),
         output_layout_name(proc_layout(RttiProcLabel, Kind), !IO),
         io.write_string(");\n", !IO)
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.197
diff -u -b -r1.197 opt_debug.m
--- compiler/opt_debug.m	20 Aug 2007 03:36:03 -0000	1.197
+++ compiler/opt_debug.m	4 Sep 2007 12:58:34 -0000
@@ -513,6 +513,8 @@
 dump_layout_name(module_layout_event_synth_order(ModuleName, EventNum)) =
     "module_layout_event_synth_order(" ++ sym_name_mangle(ModuleName) ++
         ", " ++ int_to_string(EventNum) ++ ")".
+dump_layout_name(module_common_layout(ModuleName)) =
+    "module_common_layout(" ++ sym_name_mangle(ModuleName) ++ ")".
 dump_layout_name(module_layout(ModuleName)) =
     "module_layout(" ++ sym_name_mangle(ModuleName) ++ ")".
 dump_layout_name(proc_static(RttiProcLabel)) =
Index: compiler/proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/proc_gen.m,v
retrieving revision 1.22
diff -u -b -r1.22 proc_gen.m
--- compiler/proc_gen.m	13 Aug 2007 03:01:43 -0000	1.22
+++ compiler/proc_gen.m	10 Sep 2007 23:47:12 -0000
@@ -411,9 +411,9 @@
             eff_trace_needs_proc_body_reps(ModuleInfo, PredInfo, ProcInfo,
                 TraceLevel, TraceSuppress) = yes
         ->
-            NeedGoalRep = yes
+            NeedGoalRep = trace_needs_body_rep
         ;
-            NeedGoalRep = no
+            NeedGoalRep = trace_does_not_need_body_rep
         ),
         NeedsAllNames = eff_trace_needs_all_var_names(ModuleInfo, PredInfo,
             ProcInfo, TraceLevel, TraceSuppress),
@@ -421,8 +421,7 @@
             MaybeHLDSDeepInfo),
         (
             MaybeHLDSDeepInfo = yes(HLDSDeepInfo),
-            DeepProfInfo = generate_deep_prof_info(ProcInfo,
-                HLDSDeepInfo),
+            DeepProfInfo = generate_deep_prof_info(ProcInfo, HLDSDeepInfo),
             MaybeDeepProfInfo = yes(DeepProfInfo)
         ;
             MaybeHLDSDeepInfo = no,
Index: compiler/prog_rep.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_rep.m,v
retrieving revision 1.54
diff -u -b -r1.54 prog_rep.m
--- compiler/prog_rep.m	7 Aug 2007 07:10:03 -0000	1.54
+++ compiler/prog_rep.m	10 Sep 2007 14:53:17 -0000
@@ -62,6 +62,7 @@
 :- import_module mdbcomp.
 :- import_module mdbcomp.prim_data.
 :- import_module mdbcomp.program_representation.
+:- import_module parse_tree.prog_util.
 
 :- import_module int.
 :- import_module maybe.
@@ -205,10 +206,11 @@
         Uni = complicated_unify(_, _, _),
         unexpected(this_file, "goal_expr_to_byte_list: complicated_unify")
     ).
-goal_expr_to_byte_list(switch(_, _, Cases), _, InstMap0, Info, !StackInfo, 
-        Bytes) :-
+goal_expr_to_byte_list(switch(SwitchVar, _, Cases), _, InstMap0, Info,
+        !StackInfo, Bytes) :-
     cases_to_byte_list(Cases, InstMap0, Info, !StackInfo, CasesBytes),
     Bytes = [goal_type_to_byte(goal_switch)] ++
+        var_to_byte_list(Info, SwitchVar) ++
         length_to_byte_list(Cases) ++ CasesBytes.
 goal_expr_to_byte_list(scope(_, Goal), GoalInfo, InstMap0, Info, !StackInfo, 
         Bytes) :-
@@ -406,14 +408,20 @@
     stack_layout_info::in, stack_layout_info::out, list(int)::out) is det.
 
 cases_to_byte_list([], _, _, !StackInfo, []).
-cases_to_byte_list([case(_ConsId, Goal) | Cases], InstMap0, Info, !StackInfo,
+cases_to_byte_list([case(ConsId, Goal) | Cases], InstMap0, Info, !StackInfo,
         Bytes) :-
+    cons_id_to_byte_list(ConsId, !StackInfo, ConsIdBytes),
+    MaybeArity = cons_id_maybe_arity(ConsId),
+    (
+        MaybeArity = yes(Arity)
+    ;
+        MaybeArity = no,
+        Arity = 0
+    ),
+    short_to_byte_list(Arity, ArityBytes),
     goal_to_byte_list(Goal, InstMap0, Info, !StackInfo, GoalBytes),
-    cases_to_byte_list(Cases, InstMap0, Info, !StackInfo, GoalsBytes),
-    % XXX
-    % Bytes = cons_id_and_arity_to_byte_list(ConsId)
-    %   ++ GoalBytes ++ GoalsBytes.
-    Bytes = GoalBytes ++ GoalsBytes.
+    cases_to_byte_list(Cases, InstMap0, Info, !StackInfo, CasesBytes),
+    Bytes = ConsIdBytes ++ ArityBytes ++ GoalBytes ++ CasesBytes.
 
 %---------------------------------------------------------------------------%
 
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.137
diff -u -b -r1.137 stack_layout.m
--- compiler/stack_layout.m	13 Aug 2007 03:01:44 -0000	1.137
+++ compiler/stack_layout.m	10 Sep 2007 07:16:52 -0000
@@ -119,8 +119,8 @@
     module_info_get_globals(ModuleInfo, Globals),
     globals.lookup_bool_option(Globals, agc_stack_layout, AgcLayout),
     globals.lookup_bool_option(Globals, trace_stack_layout, TraceLayout),
-    globals.lookup_bool_option(Globals, procid_stack_layout,
-        ProcIdLayout),
+    globals.lookup_bool_option(Globals, procid_stack_layout, ProcIdLayout),
+    globals.lookup_bool_option(Globals, profile_deep, DeepProfiling),
     globals.get_trace_level(Globals, TraceLevel),
     globals.get_trace_suppress(Globals, TraceSuppress),
     globals.have_static_code_addresses(Globals, StaticCodeAddr),
@@ -138,7 +138,8 @@
     lookup_string_in_table("", _, LayoutInfo0, LayoutInfo1),
     lookup_string_in_table("<too many variables>", _,
         LayoutInfo1, LayoutInfo2),
-    list.foldl(construct_layouts, ProcLayoutList, LayoutInfo2, LayoutInfo),
+    list.foldl(construct_layouts(DeepProfiling), ProcLayoutList,
+        LayoutInfo2, LayoutInfo),
     LabelsCounter = LayoutInfo ^ label_counter,
     counter.allocate(NumLabels, LabelsCounter, _),
     TableIoDecls = LayoutInfo ^ table_infos,
@@ -184,12 +185,24 @@
                 EventArgTypeInfoMap),
             MaybeEventSet = yes(EventSetLayoutData)
         ),
+        ModuleCommonLayout = module_layout_common_data(ModuleName,
+            StringOffset, ConcatStrings),
+        ModuleCommonLayoutName = module_common_layout(ModuleName),
         ModuleLayout = module_layout_data(ModuleName,
-            StringOffset, ConcatStrings, ProcLayoutNames, SourceFileLayouts,
+            ModuleCommonLayoutName, ProcLayoutNames, SourceFileLayouts,
             TraceLevel, SuppressedEvents, NumLabels, MaybeEventSet),
-        Layouts = [ModuleLayout | Layouts0]
+        Layouts = [ModuleCommonLayout, ModuleLayout | Layouts0]
     ;
         TraceLayout = no,
+        DeepProfiling = yes,
+        module_info_get_name(ModuleInfo, ModuleName),
+        ModuleCommonLayout = module_layout_common_data(ModuleName,
+            StringOffset, ConcatStrings),
+        Layouts = [ModuleCommonLayout | Layouts0],
+        StaticCellInfo = StaticCellInfo1
+    ;
+        TraceLayout = no,
+        DeepProfiling = no,
         Layouts = Layouts0,
         StaticCellInfo = StaticCellInfo1
     ),
@@ -280,10 +293,10 @@
     % layout and the layouts of the labels inside that procedure. Also update
     % the module-wide label table with the labels defined in this procedure.
     %
-:- pred construct_layouts(proc_layout_info::in,
+:- pred construct_layouts(bool::in, proc_layout_info::in,
     stack_layout_info::in, stack_layout_info::out) is det.
 
-construct_layouts(ProcLayoutInfo, !Info) :-
+construct_layouts(DeepProfiling, ProcLayoutInfo, !Info) :-
     ProcLayoutInfo = proc_layout_info(RttiProcLabel,
         EntryLabel,
         _Detism,
@@ -339,7 +352,7 @@
         LabelTables0, LabelTables),
     set_label_tables(LabelTables, !Info),
     construct_proc_layout(ProcLayoutInfo, InternalLabelInfos, Kind, VarNumMap,
-        !Info).
+        DeepProfiling, !Info).
 
 %---------------------------------------------------------------------------%
 
@@ -491,10 +504,10 @@
     %
 :- pred construct_proc_layout(proc_layout_info::in,
     list(internal_label_info)::in, proc_layout_kind::in, var_num_map::in,
-    stack_layout_info::in, stack_layout_info::out) is det.
+    bool::in, stack_layout_info::in, stack_layout_info::out) is det.
 
 construct_proc_layout(ProcLayoutInfo, InternalLabelInfos, Kind, VarNumMap,
-        !Info) :-
+        DeepProfiling, !Info) :-
     ProcLayoutInfo = proc_layout_info(RttiProcLabel,
         EntryLabel,
         Detism,
@@ -521,7 +534,7 @@
         SuccipLoc, Traversal, !Info),
     (
         Kind = proc_layout_traversal,
-        More = no_proc_id
+        More = no_proc_id_and_more
     ;
         Kind = proc_layout_proc_id(_),
         get_trace_stack_layout(!.Info, TraceStackLayout),
@@ -538,16 +551,21 @@
         ;
             MaybeExecTrace = no
         ),
-        (
-            NeedGoalRep = no,
-            ProcBytes = []
-        ;
-            NeedGoalRep = yes,
             ModuleInfo = !.Info ^ module_info,
+        (
+            ( NeedGoalRep = trace_needs_body_rep
+            ; DeepProfiling = yes
+            )
+        ->
             represent_proc_as_bytecodes(HeadVars, Goal, InstMap, VarTypes,
                 VarNumMap, ModuleInfo, !Info, ProcBytes)
+        ;
+            ProcBytes = []
         ),
-        More = proc_id(MaybeProcStatic, MaybeExecTrace, ProcBytes)
+        module_info_get_name(ModuleInfo, ModuleName),
+        ModuleCommonLayout = module_common_layout(ModuleName),
+        More = proc_id_and_more(MaybeProcStatic, MaybeExecTrace,
+            ProcBytes, ModuleCommonLayout)
     ),
     ProcLayout = proc_layout_data(RttiProcLabel, Traversal, More),
     LayoutName = proc_layout(RttiProcLabel, Kind),
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing debian/patches
cvs diff: Diffing deep_profiler
Index: deep_profiler/DEEP_FLAGS.in
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/DEEP_FLAGS.in,v
retrieving revision 1.4
diff -u -b -r1.4 DEEP_FLAGS.in
--- deep_profiler/DEEP_FLAGS.in	8 Nov 2006 08:06:42 -0000	1.4
+++ deep_profiler/DEEP_FLAGS.in	3 Aug 2007 08:35:35 -0000
@@ -5,14 +5,11 @@
 --no-mercury-stdlib-dir
 -I../library
 -I../browser
--I../mdbcomp
 --c-include-directory ../boehm_gc
 --c-include-directory ../boehm_gc/include
 --c-include-directory ../runtime
 --c-include-directory ../library
 --c-include-directory ../library/Mercury/mihs
---c-include-directory ../mdbcomp
---c-include-directory ../mdbcomp/Mercury/mihs
 --c-include-directory ../browser
 --c-include-directory ../browser/Mercury/mihs
 --c-include-directory ../trace
Index: deep_profiler/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/Mmakefile,v
retrieving revision 1.22
diff -u -b -r1.22 Mmakefile
--- deep_profiler/Mmakefile	8 Aug 2007 01:49:39 -0000	1.22
+++ deep_profiler/Mmakefile	10 Sep 2007 13:33:25 -0000
@@ -4,12 +4,24 @@
 # Public Licence - see the file COPYING in the Mercury distribution.
 #-----------------------------------------------------------------------------#
 
-# Mmake - this is Mmake file for building the Mercury deep profiler
+# This is the Mmakefile for building the Mercury deep profiler.
 
 MERCURY_DIR=..
 LINK_STATIC=yes
 include $(MERCURY_DIR)/Mmake.common
 
+#----------------------------------------------------------------------------#
+
+# Override some settings from ../Mmake.workspace so that in debugging grades
+# we do not include mer_mdbcomp.init when creating the _init.c files in
+# this directory. We copy the mdbcomp modules into this directory so if we
+# do include mer_mdbcomp.init we will end up with duplicate entries in the
+# _init.c files.
+
+C2INITFLAGS = --trace-init-file $(BROWSER_DIR)/$(BROWSER_LIB_NAME).init
+
+#----------------------------------------------------------------------------#
+
 -include Mmake.deep.params
 
 # Override the default rule in `mmake --use-mmc-make' that asks `mmc' to
@@ -20,7 +32,14 @@
 # can be found by `mmc --make'.
 include Mercury.options
 
-ALL_DEEP_MODULES=mdprof_cgi mdprof_test mdprof_dump mdprof_feedback
+MAIN_TARGET = all
+
+ALL_DEEP_MODULES = \
+	mdprof_cgi \
+	mdprof_test \
+	mdprof_dump \
+	mdprof_feedback \
+	mdprof_procrep
 
 ifeq ("$(ENABLE_DEEP_PROFILER)","yes")
 	MAIN_TARGET=all
@@ -38,8 +57,19 @@
 	INSTALL=nothing
 endif
 
-# Avoid trying to make this file with `mmc --make' if it doesn't exist.
-Mmake.deep.params: ;
+VPATH = $(LIBRARY_DIR)
+
+#-----------------------------------------------------------------------------#
+
+MDBCOMP_MODULES = \
+	mdbcomp.m \
+	prim_data.m \
+	program_representation.m \
+	rtti_access.m \
+	slice_and_dice.m \
+	trace_counts.m
+
+MDBCOMP_ORIG_MODULES = $(patsubst %,$(MDBCOMP_DIR)/%,$(MDBCOMP_MODULES))
 
 #-----------------------------------------------------------------------------#
 
@@ -52,12 +82,24 @@
 nothing:
 
 .PHONY: depend
-depend:	$(DEPEND)
+depend:	$(MDBCOMP_MODULES) $(DEPEND)
 
 $(DEPEND): DEEP_FLAGS 
 
 .PHONY: all
-all:	$(ALL_DEEP_MODULES) $(TAGS_FILE_EXISTS)
+all:	$(MDBCOMP_MODULES) $(ALL_DEEP_MODULES) $(TAGS_FILE_EXISTS)
+
+# We need to start by turning write permission on for each copied file
+# in case some exist, but we need to ignore errors in case some don't exist.
+# The exit 0 is to prevent make itself from printing a message about the
+# (ignored) failure of an action.
+#
+# We could modify the action here to copy only the changed files.
+
+$(MDBCOMP_MODULES): $(MDBCOMP_ORIG_MODULES)
+	- at chmod a+w $(MDBCOMP_MODULES) > /dev/null 2>&1; exit 0
+	cp $(MDBCOMP_ORIG_MODULES) .
+	@chmod a-w $(MDBCOMP_MODULES)
 
 #-----------------------------------------------------------------------------#
 
@@ -92,25 +134,29 @@
 
 #-----------------------------------------------------------------------------#
 
-# We need the shenanigans with .deep.tags to avoid situations in which an
+# We need the shenanigans with .deep_tags to avoid situations in which an
 # "mmake tags" in this directory does nothing even in the absence of a tags
 # file in this directory, because mmake uses VPATH to find ../library/tags
 # and believes it to be the tags file we are asking for.
 
 .PHONY: tags
-tags:	.deep.tags
-
-DEEP_MS = $(mdprof_cgi.ms) $(mdprof_test.ms) $(mdprof_dump.ms) $(mdprof_feedback.ms)
+tags:	.deep_tags
 
-.deep.tags: $(MTAGS) $(DEEP_MS) $(LIBRARY_DIR)/*.m
-	$(MTAGS) $(DEEP_MS) $(LIBRARY_DIR)/*.m
-	touch .deep.tags
+DEEP_MS = \
+	$(mdprof_cgi.ms) \
+	$(mdprof_test.ms) \
+	$(mdprof_dump.ms) \
+	$(mdprof_feedback.ms)
+
+.deep_tags: $(MTAGS) $(DEEP_MS) $(MDBCOMP_DIR)/*.m $(LIBRARY_DIR)/*.m
+	$(MTAGS) $(DEEP_MS) $(MDBCOMP_DIR)/*.m $(LIBRARY_DIR)/*.m
+	touch .deep_tags
 
 .PHONY: tags_file_exists
 tags_file_exists:
 	@if test ! -f tags; then echo making tags; \
-	$(MTAGS) $(DEEP_MS) $(LIBRARY_DIR)/*.m; \
-	touch .deep.tags; fi
+	$(MTAGS) $(DEEP_MS) $(MDBCOMP_DIR)/*.m $(LIBRARY_DIR)/*.m; \
+	touch .deep_tags; fi
 
 #-----------------------------------------------------------------------------#
 
@@ -134,7 +180,8 @@
 #-----------------------------------------------------------------------------#
 
 realclean_local:
-	rm -f tags DEEP_FLAGS DEEP_FLAGS.date
+	rm -f .deep_tags tags DEEP_FLAGS DEEP_FLAGS.date \
+		$(MDBCOMP_MODULES) mdbcomp.*.err
 
 #-----------------------------------------------------------------------------#
 
Index: deep_profiler/dump.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/dump.m,v
retrieving revision 1.10
diff -u -b -r1.10 dump.m
--- deep_profiler/dump.m	13 Jan 2007 12:23:15 -0000	1.10
+++ deep_profiler/dump.m	6 Sep 2007 02:07:01 -0000
@@ -53,6 +53,9 @@
 
 :- import_module array_util.
 :- import_module measurements.
+:- import_module mdbcomp.
+:- import_module mdbcomp.prim_data.
+:- import_module mdbcomp.program_representation.
 
 :- import_module array.
 :- import_module bool.
@@ -414,22 +417,23 @@
 
 %----------------------------------------------------------------------------%
 
-:- func dump_proc_id(proc_id) = string.
+:- func dump_proc_id(string_proc_label) = string.
 
 dump_proc_id(Proc) = Str :-
-    Proc = user_defined(PredOrFunc, _DeclModule, _DefnModule, Name,
+    Proc = str_ordinary_proc_label(PredOrFunc, _DeclModule, _DefnModule, Name,
         Arity, Mode),
     (
-        PredOrFunc = predicate,
+        PredOrFunc = pf_predicate,
         Suffix = ""
     ;
-        PredOrFunc = function,
+        PredOrFunc = pf_function,
         Suffix = "+1"
     ),
     string.format("%s/%d-%d%s", [s(Name), i(Arity), i(Mode), s(Suffix)],
         Str).
 dump_proc_id(Proc) = Str :-
-    Proc = uci_pred(Type, _TypeModule, _DefModule, Name, _Arity, _Mode),
+    Proc = str_special_proc_label(Type, _TypeModule, _DefModule, Name,
+        _Arity, _Mode),
     string.format("%s predicate for type `%s'", [s(Name), s(Type)], Str).
 
 %----------------------------------------------------------------------------%
Index: deep_profiler/mdprof_procrep.m
===================================================================
RCS file: deep_profiler/mdprof_procrep.m
diff -N deep_profiler/mdprof_procrep.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ deep_profiler/mdprof_procrep.m	10 Sep 2007 14:58:39 -0000
@@ -0,0 +1,370 @@
+%-----------------------------------------------------------------------------%
+% vim: ft=mercury ts=4 sw=4 et
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2007 The University of Melbourne.
+% This file may only be copied under the terms of the GNU General
+% Public License - see the file COPYING in the Mercury distribution.
+%-----------------------------------------------------------------------------%
+%
+% File: mdprof_procrep.m.
+% Author: zs.
+%
+%-----------------------------------------------------------------------------%
+
+:- module mdprof_procrep.
+:- interface.
+
+:- import_module io.
+
+%-----------------------------------------------------------------------------%
+
+:- pred main(io::di, io::uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module mdbcomp.
+:- import_module mdbcomp.prim_data.
+:- import_module mdbcomp.program_representation.
+:- import_module mdbcomp.rtti_access.
+
+:- import_module bool.
+:- import_module char.
+:- import_module int.
+:- import_module list.
+:- import_module maybe.
+:- import_module require.
+:- import_module string.
+
+%-----------------------------------------------------------------------------%
+
+main(!IO) :-
+    io.command_line_arguments(Args, !IO),
+    (
+        Args = [],
+        MaybeModules = no
+    ;
+        Args = [_ | _],
+        MaybeModules = yes(Args)
+    ),
+    read_prog_rep_file("Deep.procrep", ProgRepRes, !IO),
+    (
+        ProgRepRes = ok(ProgRep),
+        ProgRep = prog_rep(ModuleReps),
+        print_selected_modules(ModuleReps, MaybeModules, !IO)
+    ;
+        ProgRepRes = error(Error),
+        io.error_message(Error, Msg),
+        io.format("mdprof_procrep: %s\n", [s(Msg)], !IO)
+    ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred print_selected_modules(list(module_rep)::in, maybe(list(string))::in,
+    io::di, io::uo) is det.
+
+print_selected_modules([], _, !IO).
+print_selected_modules([ModuleRep | ModuleReps], MaybeModules, !IO) :-
+    ModuleRep = module_rep(ModuleName, _StringTable, _ProcReps),
+    (
+        MaybeModules = no,
+        print_module(ModuleRep, !IO)
+    ;
+        MaybeModules = yes(Modules),
+        ( list.member(ModuleName, Modules) ->
+            print_module(ModuleRep, !IO)
+        ;
+            true
+        )
+    ),
+    print_selected_modules(ModuleReps, MaybeModules, !IO).
+
+:- pred print_module(module_rep::in, io::di, io::uo) is det.
+
+print_module(ModuleRep, !IO) :-
+    ModuleRep = module_rep(ModuleName, _StringTable, ProcReps),
+    io.format("Module %s\n", [s(ModuleName)], !IO),
+    list.foldl(print_proc, ProcReps, !IO).
+
+:- pred print_proc(proc_rep::in, io::di, io::uo) is det.
+
+print_proc(ProcRep, !IO) :-
+    ProcRep = proc_rep(ProcLabel, ProcDefnRep),
+    ProcDefnRep = proc_defn_rep(ArgVarReps, GoalRep),
+    print_proc_label(ProcLabel, !IO),
+    print_args(ArgVarReps, !IO),
+    io.write_string(" :-\n", !IO),
+    print_goal(1, GoalRep, !IO),
+    io.nl(!IO).
+
+:- pred print_proc_label(string_proc_label::in, io::di, io::uo) is det.
+
+print_proc_label(ProcLabel, !IO) :-
+    (
+        ProcLabel = str_ordinary_proc_label(PredFunc, DeclModule, _DefModule,
+            Name, Arity, Mode),
+        (
+            PredFunc = pf_predicate,
+            PF = "pred"
+        ;
+            PredFunc = pf_function,
+            PF = "func"
+        ),
+        io.format("%s %s.%s/%d-%d",
+            [s(PF), s(DeclModule), s(Name), i(Arity), i(Mode)], !IO)
+    ;
+        ProcLabel = str_special_proc_label(TypeName, TypeModule, _DefModule,
+            Name, Arity, Mode),
+        io.format("%s for %s.%s/%d-%d",
+            [s(Name), s(TypeModule), s(TypeName), i(Arity), i(Mode)], !IO)
+    ).
+
+%-----------------------------------------------------------------------------%
+
+:- pred print_goal(int::in, goal_rep::in, io::di, io::uo) is det.
+
+print_goal(Indent, GoalRep, !IO) :-
+    (
+        GoalRep = conj_rep(ConjGoalReps),
+        print_conj(Indent, ConjGoalReps, !IO)
+    ;
+        GoalRep = disj_rep(DisjGoalReps),
+        indent(Indent, !IO),
+        io.write_string("(\n", !IO),
+        print_disj(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),
+        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),
+        indent(Indent, !IO),
+        io.write_string("->\n", !IO),
+        print_goal(Indent + 1, ThenRep, !IO),
+        indent(Indent, !IO),
+        io.write_string(";\n", !IO),
+        print_goal(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),
+        indent(Indent, !IO),
+        io.write_string(")\n", !IO)
+    ;
+        GoalRep = scope_rep(SubGoalRep, MaybeCut),
+        indent(Indent, !IO),
+        io.write_string("scope", !IO),
+        (
+            MaybeCut = scope_is_cut
+        ;
+            MaybeCut = scope_is_no_cut,
+            io.write_string(" cut", !IO)
+        ),
+        io.write_string(" (\n", !IO),
+        print_goal(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)
+    ).
+
+:- pred print_conj(int::in, list(goal_rep)::in, io::di, io::uo) is det.
+
+print_conj(Indent, GoalReps, !IO) :-
+    (
+        GoalReps = [],
+        indent(Indent, !IO),
+        io.write_string("true\n", !IO)
+    ;
+        GoalReps = [_ | _],
+        print_conj_2(Indent, GoalReps, !IO)
+    ).
+
+:- pred print_conj_2(int::in, list(goal_rep)::in, io::di, io::uo) is det.
+
+print_conj_2(_Indent, [], !IO).
+print_conj_2(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).
+
+:- pred print_disj(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) :-
+    (
+        PrintSemi = no
+    ;
+        PrintSemi = yes,
+        indent(Indent, !IO),
+        io.write_string(";\n", !IO)
+    ),
+    print_goal(Indent + 1, GoalRep, !IO),
+    print_disj(Indent, GoalReps, yes, !IO).
+
+:- pred print_switch(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) :-
+    (
+        PrintSemi = no
+    ;
+        PrintSemi = yes,
+        indent(Indent, !IO),
+        io.write_string(";\n", !IO)
+    ),
+    CaseRep = case_rep(ConsIdRep, Arity, GoalRep),
+    indent(Indent + 1, !IO),
+    io.format("%% case %s/%d\n", [s(ConsIdRep), i(Arity)], !IO),
+    print_goal(Indent + 1, GoalRep, !IO),
+    print_switch(Indent, CaseReps, yes, !IO).
+
+%-----------------------------------------------------------------------------%
+
+:- pred print_atomic_goal(int::in, atomic_goal_rep::in, io::di, io::uo) is det.
+
+print_atomic_goal(Indent, AtomicGoalRep, !IO) :-
+    indent(Indent, !IO),
+    (
+        (
+            AtomicGoalRep = unify_construct_rep(VarRep, ConsIdRep, ArgReps),
+            UnifyOp = "<="
+        ;
+            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)
+    ;
+        (
+            AtomicGoalRep = partial_construct_rep(VarRep, ConsIdRep,
+                MaybeArgReps),
+            UnifyOp = "<="
+        ;
+            AtomicGoalRep = partial_deconstruct_rep(VarRep, ConsIdRep,
+                MaybeArgReps),
+            UnifyOp = "=>"
+        ),
+        io.format("V%d %s %s", [i(VarRep), s(UnifyOp), s(ConsIdRep)], !IO),
+        print_maybe_args(MaybeArgReps, !IO)
+    ;
+        AtomicGoalRep = unify_assign_rep(TargetRep, SourceRep),
+        io.format("V%d := V%d", [i(TargetRep), i(SourceRep)], !IO)
+    ;
+        AtomicGoalRep = cast_rep(TargetRep, SourceRep),
+        io.format("cast V%d to V%d", [i(SourceRep), i(TargetRep)], !IO)
+    ;
+        AtomicGoalRep = unify_simple_test_rep(TargetRep, SourceRep),
+        io.format("V%d == V%d", [i(SourceRep), i(TargetRep)], !IO)
+    ;
+        AtomicGoalRep = pragma_foreign_code_rep(Args),
+        io.write_string("foreign_proc(", !IO),
+        print_args(Args, !IO),
+        io.write_string(")", !IO)
+    ;
+        AtomicGoalRep = higher_order_call_rep(HOVarRep, Args),
+        io.format("V%d(", [i(HOVarRep)], !IO),
+        print_args(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),
+        io.write_string(")", !IO)
+    ;
+        AtomicGoalRep = plain_call_rep(Module, Pred, Args),
+        io.format("%s.%s", [s(Module), s(Pred)], !IO),
+        print_args(Args, !IO)
+    ;
+        AtomicGoalRep = builtin_call_rep(Module, Pred, Args),
+        io.format("builtin %s.%s", [s(Module), s(Pred)], !IO),
+        print_args(Args, !IO)
+    ;
+        AtomicGoalRep = event_call_rep(Event, Args),
+        io.format("event %s", [s(Event)], !IO),
+        print_args(Args, !IO)
+    ),
+    io.nl(!IO).
+
+%-----------------------------------------------------------------------------%
+
+:- pred print_args(list(var_rep)::in, io::di, io::uo) is det.
+
+print_args(Args, !IO) :-
+    (
+        Args = []
+    ;
+        Args = [_ | _],
+        io.write_string("(", !IO),
+        print_args_2(Args, "", !IO),
+        io.write_string(")", !IO)
+    ).
+
+:- pred print_args_2(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).
+
+:- pred print_maybe_args(list(maybe(var_rep))::in, io::di, io::uo) is det.
+
+print_maybe_args(MaybeArgs, !IO) :-
+    (
+        MaybeArgs = []
+    ;
+        MaybeArgs = [_ | _],
+        io.write_string("(", !IO),
+        print_maybe_args_2(MaybeArgs, "", !IO),
+        io.write_string(")", !IO)
+    ).
+
+:- pred print_maybe_args_2(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) :-
+    (
+        MaybeVarRep = no,
+        io.write_string(Prefix, !IO),
+        io.write_string("_", !IO)
+    ;
+        MaybeVarRep = yes(VarRep),
+        io.format("%sV%d", [s(Prefix), i(VarRep)], !IO)
+    ),
+    print_maybe_args_2(MaybeVarReps, ", ", !IO).
+
+:- pred indent(int::in, io::di, io::uo) is det.
+
+indent(N, !IO) :-
+    ( N =< 0 ->
+        true
+    ;
+        io.write_string("  ", !IO),
+        indent(N - 1, !IO)
+    ).
+
+%-----------------------------------------------------------------------------%
+:- end_module mdprof_procrep.
+%-----------------------------------------------------------------------------%
Index: deep_profiler/profile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/profile.m,v
retrieving revision 1.16
diff -u -b -r1.16 profile.m
--- deep_profiler/profile.m	2 Apr 2007 02:42:33 -0000	1.16
+++ deep_profiler/profile.m	6 Sep 2007 02:07:45 -0000
@@ -17,12 +17,15 @@
 % at index 0; their first real element is at index 1. The arrays in
 % proc_static and proc_dynamic structures, being reflections of arrays created
 % in C code, start at index 0.
+%
 %-----------------------------------------------------------------------------%
 
 :- module profile.
 :- interface.
 
 :- import_module measurements.
+:- import_module mdbcomp.
+:- import_module mdbcomp.program_representation.
 
 :- import_module array.
 :- import_module bool.
@@ -159,7 +162,7 @@
 
 :- type proc_static
     --->    proc_static(
-                ps_id           :: proc_id,     % procedure ID
+                ps_id           :: string_proc_label, % procedure ID
                 ps_decl_module  :: string,      % declaring module
                 ps_refined_id   :: string,      % refined procedure id
                 ps_raw_id       :: string,      % raw procedure id
@@ -190,28 +193,6 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type pred_or_func
-    --->    predicate
-    ;       function.
-
-:- type proc_id
-    --->    user_defined(
-                user_pred_or_func :: pred_or_func,
-                user_decl_module  :: string,
-                user_def_module   :: string,
-                user_name         :: string,
-                user_arity        :: int,
-                user_mode         :: int
-            )
-    ;       uci_pred(
-                uci_type_name   :: string,
-                uci_type_module :: string,
-                uci_def_module  :: string,
-                uci_pred_name   :: string,
-                uci_arity       :: int,
-                uci_mode        :: int
-            ).
-
 :- type call_site_array_slot
     --->    slot_normal(call_site_dynamic_ptr)
     ;       slot_multi(is_zeroed, array(call_site_dynamic_ptr)).
@@ -244,12 +225,14 @@
                 call_site_static_ptr
             ).
 
+:- pred is_call_site_kind(int::in, call_site_kind::out) is semidet.
+
 %-----------------------------------------------------------------------------%
 
-:- func decl_module(proc_id) = string.
+:- func decl_module(string_proc_label) = string.
 
-:- func dummy_proc_id = proc_id.
-:- func main_parent_proc_id = proc_id.
+:- func dummy_proc_id = string_proc_label.
+:- func main_parent_proc_id = string_proc_label.
 
 :- func dummy_proc_dynamic_ptr = proc_dynamic_ptr.
 :- func dummy_proc_static_ptr = proc_static_ptr.
@@ -448,6 +431,7 @@
 
 :- implementation.
 
+:- import_module mdbcomp.prim_data.
 :- import_module array_util.
 
 :- import_module int.
@@ -455,17 +439,50 @@
 
 %-----------------------------------------------------------------------------%
 
+:- pragma foreign_decl("C", "#include ""mercury_deep_profiling.h""").
+
+:- pragma foreign_enum("C", call_site_kind/0, [
+    normal_call         - "MR_callsite_normal_call",
+    special_call        - "MR_callsite_special_call",
+    higher_order_call   - "MR_callsite_higher_order_call",
+    method_call         - "MR_callsite_method_call",
+    callback            - "MR_callsite_callback"
+]).
+
+:- pragma foreign_proc("C",
+    is_call_site_kind(Int::in, CallSite::out),
+    [promise_pure, will_not_call_mercury, thread_safe],
+"
+    CallSite = (MR_CallSiteKind) Int;
+
+    switch (CallSite) {
+        case MR_callsite_normal_call:
+        case MR_callsite_special_call:
+        case MR_callsite_higher_order_call:
+        case MR_callsite_method_call:
+        case MR_callsite_callback:
+            SUCCESS_INDICATOR = MR_TRUE;
+            break;
+
+        default:
+            SUCCESS_INDICATOR = MR_FALSE;
+            break;
+    }
+").
+
+%-----------------------------------------------------------------------------%
+
 decl_module(ProcId) = DeclModule :-
     (
-        ProcId = user_defined(_, DeclModule, _, _, _, _)
+        ProcId = str_ordinary_proc_label(_, DeclModule, _, _, _, _)
     ;
-        ProcId = uci_pred(_, DeclModule, _, _, _, _)
+        ProcId = str_special_proc_label(_, DeclModule, _, _, _, _)
     ).
 
-dummy_proc_id =
-    user_defined(predicate, "unknown", "unknown", "unknown", -1, -1).
+dummy_proc_id = str_ordinary_proc_label(pf_predicate, "unknown",
+    "unknown", "unknown", -1, -1).
 
-main_parent_proc_id = user_defined(predicate, "mercury_runtime",
+main_parent_proc_id = str_ordinary_proc_label(pf_predicate, "mercury_runtime",
     "mercury_runtime", "main_parent", 0, 0).
 
 %-----------------------------------------------------------------------------%
Index: deep_profiler/read_profile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/deep_profiler/read_profile.m,v
retrieving revision 1.19
diff -u -b -r1.19 read_profile.m
--- deep_profiler/read_profile.m	12 Oct 2006 06:30:23 -0000	1.19
+++ deep_profiler/read_profile.m	6 Sep 2007 02:08:36 -0000
@@ -33,6 +33,9 @@
 :- import_module array_util.
 :- import_module io_combinator.
 :- import_module measurements.
+:- import_module mdbcomp.
+:- import_module mdbcomp.prim_data.
+:- import_module mdbcomp.program_representation.
 
 :- import_module array.
 :- import_module bool.
@@ -58,7 +61,7 @@
     io.see_binary(FileName, Res0, !IO),
     (
         Res0 = ok,
-        read_id_string(Res1, !IO),
+        read_deep_id_string(Res1, !IO),
         (
             Res1 = ok(_),
             io_combinator.maybe_error_sequence_11(
@@ -110,15 +113,15 @@
         Res = error(Msg)
     ).
 
-:- pred read_id_string(maybe_error(string)::out,
+:- pred read_deep_id_string(maybe_error(string)::out,
     io::di, io::uo) is det.
 
-read_id_string(Res, !IO) :-
-    read_n_byte_string(string.length(id_string), Res0, !IO),
+read_deep_id_string(Res, !IO) :-
+    read_n_byte_string(string.length(deep_id_string), Res0, !IO),
     (
         Res0 = ok(String),
-        ( String = id_string ->
-            Res = ok(id_string)
+        ( String = deep_id_string ->
+            Res = ok(deep_id_string)
         ;
             Res = error("not a deep profiling data file")
         )
@@ -127,12 +130,12 @@
         Res = error(Err)
     ).
 
-:- func id_string = string.
+:- func deep_id_string = string.
 
-% This must the same string as the one written by MR_write_out_id_string
+% This must the same string as the one written by MR_write_out_deep_id_string
 % in runtime/mercury_deep_profiling.c.
 
-id_string = "Mercury deep profiler data version 3\n".
+deep_id_string = "Mercury deep profiler data version 4\n".
 
 :- func init_deep(int, int, int, int, int, int, int, int, int, int, int)
     = initial_deep.
@@ -174,7 +177,9 @@
     read_byte(Res0, !IO),
     (
         Res0 = ok(Byte),
-        ( Byte = token_call_site_dynamic ->
+        ( is_next_item_token(Byte, NextItem) ->
+            (
+                NextItem = deep_item_call_site_dynamic,
             read_call_site_dynamic(Res1, !IO),
             (
                 Res1 = ok2(CallSiteDynamic, CSDI),
@@ -186,7 +191,8 @@
                 Res1 = error2(Err),
                 Res = error(Err)
             )
-        ; Byte = token_proc_dynamic ->
+            ;
+                NextItem = deep_item_proc_dynamic,
             read_proc_dynamic(Res1, !IO),
             (
                 Res1 = ok2(ProcDynamic, PDI),
@@ -198,7 +204,8 @@
                 Res1 = error2(Err),
                 Res = error(Err)
             )
-        ; Byte = token_call_site_static ->
+            ;
+                NextItem = deep_item_call_site_static,
             read_call_site_static(Res1, !IO),
             (
                 Res1 = ok2(CallSiteStatic, CSSI),
@@ -210,7 +217,8 @@
                 Res1 = error2(Err),
                 Res = error(Err)
             )
-        ; Byte = token_proc_static ->
+            ;
+                NextItem = deep_item_proc_static,
             read_proc_static(Res1, !IO),
             (
                 Res1 = ok2(ProcStatic, PSI),
@@ -223,6 +231,10 @@
                 Res = error(Err)
             )
         ;
+                NextItem = deep_item_end,
+                Res = ok(InitDeep0)
+            )
+        ;
             format("unexpected token %d", [i(Byte)], Msg),
             Res = error(Msg)
         )
@@ -271,7 +283,6 @@
         Res = error2(Err)
     ).
 
-
 :- pred read_proc_static(maybe_error2(proc_static, int)::out,
     io::di, io::uo) is det.
 
@@ -300,15 +311,14 @@
             DeclModule = decl_module(Id),
             RefinedStr = refined_proc_id_to_string(Id),
             RawStr = raw_proc_id_to_string(Id),
-            % The `not_zeroed' for whether the procedure's
-            % proc_static is ever zeroed is the default. The
-            % startup phase will set it to `zeroed' in the
-            % proc_statics which are ever zeroed.
             ( Interface = 0 ->
                 IsInInterface = no
             ;
                 IsInInterface = yes
             ),
+            % The `not_zeroed' for whether the procedure's proc_static
+            % is ever zeroed is the default. The startup phase will set it
+            % to `zeroed' in the proc_statics which are ever zeroed.
             ProcStatic = proc_static(Id, DeclModule,
                 RefinedStr, RawStr, FileName, LineNumber,
                 IsInInterface, array(CSSPtrs), not_zeroed),
@@ -329,20 +339,26 @@
         Res = error2(Err)
     ).
 
-:- pred read_proc_id(maybe_error(proc_id)::out, io::di, io::uo) is det.
+:- pred read_proc_id(maybe_error(string_proc_label)::out, io::di, io::uo)
+    is det.
 
 read_proc_id(Res, !IO) :-
     read_deep_byte(Res0, !IO),
     (
         Res0 = ok(Byte),
-        ( Byte = token_isa_uci_pred ->
+        ( is_proclabel_kind(Byte, ProcLabelKind) ->
+            (
+                ProcLabelKind = proclabel_special,
             read_proc_id_uci_pred(Res, !IO)
-        ; Byte = token_isa_predicate ->
-            read_proc_id_user_defined(predicate, Res, !IO)
-        ; Byte = token_isa_function ->
-            read_proc_id_user_defined(function, Res, !IO)
         ;
-            format("unexpected proc_id_kind %d", [i(Byte)], Msg),
+                ProcLabelKind = proclabel_user_predicate,
+                read_proc_id_user_defined(pf_predicate, Res, !IO)
+            ;
+                ProcLabelKind = proclabel_user_function,
+                read_proc_id_user_defined(pf_function, Res, !IO)
+            )
+        ;
+            format("unexpected proclabel_kind %d", [i(Byte)], Msg),
             Res = error(Msg)
         )
     ;
@@ -350,8 +366,8 @@
         Res = error(Err)
     ).
 
-:- pred read_proc_id_uci_pred(maybe_error(proc_id)::out, io::di, io::uo)
-    is det.
+:- pred read_proc_id_uci_pred(maybe_error(string_proc_label)::out,
+    io::di, io::uo) is det.
 
 read_proc_id_uci_pred(Res, !IO) :-
     io_combinator.maybe_error_sequence_6(
@@ -364,13 +380,13 @@
         (pred(TypeName::in, TypeModule::in, DefModule::in,
                 PredName::in, Arity::in, Mode::in, ProcId::out)
                 is det :-
-            ProcId = ok(uci_pred(TypeName, TypeModule,
+            ProcId = ok(str_special_proc_label(TypeName, TypeModule,
                 DefModule, PredName, Arity, Mode))
         ),
         Res, !IO).
 
-:- pred read_proc_id_user_defined(pred_or_func::in, maybe_error(proc_id)::out,
-    io::di, io::uo) is det.
+:- pred read_proc_id_user_defined(pred_or_func::in,
+    maybe_error(string_proc_label)::out, io::di, io::uo) is det.
 
 read_proc_id_user_defined(PredOrFunc, Res, !IO) :-
     io_combinator.maybe_error_sequence_5(
@@ -380,32 +396,31 @@
         read_num,
         read_num,
         (pred(DeclModule::in, DefModule::in, Name::in,
-                Arity::in, Mode::in, ProcId::out)
-                is det :-
-            ProcId = ok(user_defined(PredOrFunc, DeclModule,
+                Arity::in, Mode::in, ProcId::out) is det :-
+            ProcId = ok(str_ordinary_proc_label(PredOrFunc, DeclModule,
                 DefModule, Name, Arity, Mode))
         ),
         Res, !IO).
 
-:- func raw_proc_id_to_string(proc_id) = string.
+:- func raw_proc_id_to_string(string_proc_label) = string.
 
-raw_proc_id_to_string(uci_pred(TypeName, TypeModule, _DefModule,
+raw_proc_id_to_string(str_special_proc_label(TypeName, TypeModule, _DefModule,
         PredName, Arity, Mode)) =
     string.append_list(
         [PredName, " for ", TypeModule, ".", TypeName,
         "/", string.int_to_string(Arity),
         " mode ", string.int_to_string(Mode)]).
-raw_proc_id_to_string(user_defined(PredOrFunc, DeclModule, _DefModule,
-        Name, Arity, Mode)) =
+raw_proc_id_to_string(str_ordinary_proc_label(PredOrFunc, DeclModule,
+        _DefModule, Name, Arity, Mode)) =
     string.append_list([DeclModule, ".", Name,
         "/", string.int_to_string(Arity),
-        ( PredOrFunc = function -> "+1" ; "" ),
+        ( PredOrFunc = pf_function -> "+1" ; "" ),
         "-", string.int_to_string(Mode)]).
 
-:- func refined_proc_id_to_string(proc_id) = string.
+:- func refined_proc_id_to_string(string_proc_label) = string.
 
-refined_proc_id_to_string(uci_pred(TypeName, TypeModule, _DefModule,
-        RawPredName, Arity, Mode)) = Name :-
+refined_proc_id_to_string(str_special_proc_label(TypeName, TypeModule,
+        _DefModule, RawPredName, Arity, Mode)) = Name :-
     ( RawPredName = "__Unify__" ->
         PredName = "Unify"
     ; RawPredName = "__Compare__" ->
@@ -427,8 +442,8 @@
     ;
         Name = string.append_list([Name0, " mode ", int_to_string(Mode)])
     ).
-refined_proc_id_to_string(user_defined(PredOrFunc, DeclModule, _DefModule,
-        ProcName, Arity, Mode)) = Name :-
+refined_proc_id_to_string(str_ordinary_proc_label(PredOrFunc, DeclModule,
+        _DefModule, ProcName, Arity, Mode)) = Name :-
     (
         string.append("TypeSpecOf__", ProcName1, ProcName),
         ( string.append("pred__", ProcName2A, ProcName1) ->
@@ -446,7 +461,7 @@
         RefinedProcName = string.from_char_list(ProcNameChars),
         Name = string.append_list([DeclModule, ".", RefinedProcName,
             "/", string.int_to_string(Arity),
-            ( PredOrFunc = function -> "+1" ; "" ),
+            ( PredOrFunc = pf_function -> "+1" ; "" ),
             "-", string.int_to_string(Mode),
             " [", SpecInfo, "]"])
     ;
@@ -468,11 +483,11 @@
         Name = string.append_list([DeclModule, ".", ContainingName,
             " lambda line ", LineNumber,
             "/", string.int_to_string(Arity),
-            ( PredOrFunc = function -> "+1" ; "" )])
+            ( PredOrFunc = pf_function -> "+1" ; "" )])
     ;
         Name = string.append_list([DeclModule, ".", ProcName,
             "/", string.int_to_string(Arity),
-            ( PredOrFunc = function -> "+1" ; "" ),
+            ( PredOrFunc = pf_function -> "+1" ; "" ),
             "-", string.int_to_string(Mode)])
     ).
 
@@ -786,19 +801,10 @@
     read_deep_byte(Res0, !IO),
     (
         Res0 = ok(Byte),
-        ( Byte = token_normal_call ->
-            Res = ok(normal_call)
-        ; Byte = token_special_call ->
-            Res = ok(special_call)
-        ; Byte = token_higher_order_call ->
-            Res = ok(higher_order_call)
-        ; Byte = token_method_call ->
-            Res = ok(method_call)
-        ; Byte = token_callback ->
-            Res = ok(callback)
+        ( is_call_site_kind(Byte, CallSiteKind) ->
+            Res = ok(CallSiteKind)
         ;
-            format("unexpected call_site_kind %d",
-                [i(Byte)], Msg),
+            format("unexpected call_site_kind %d", [i(Byte)], Msg),
             Res = error(Msg)
         ),
         trace [compile_time(flag("debug_read_profdeep")), io(!IO)] (
@@ -819,7 +825,9 @@
     read_deep_byte(Res0, !IO),
     (
         Res0 = ok(Byte),
-        ( Byte = token_normal_call ->
+        ( is_call_site_kind(Byte, CallSiteKind) ->
+            (
+                CallSiteKind = normal_call,
             read_num(Res1, !IO),
             (
                 Res1 = ok(CalleeProcStatic),
@@ -836,14 +844,19 @@
                 Res1 = error(Err),
                 Res = error(Err)
             )
-        ; Byte = token_special_call ->
+            ;
+                CallSiteKind = special_call,
             Res = ok(special_call_and_no_callee)
-        ; Byte = token_higher_order_call ->
+            ;
+                CallSiteKind = higher_order_call,
             Res = ok(higher_order_call_and_no_callee)
-        ; Byte = token_method_call ->
+            ;
+                CallSiteKind = method_call,
             Res = ok(method_call_and_no_callee)
-        ; Byte = token_callback ->
+            ;
+                CallSiteKind = callback,
             Res = ok(callback_and_no_callee)
+            )
         ;
             format("unexpected call_site_kind %d", [i(Byte)], Msg),
             Res = error(Msg)
@@ -1105,100 +1118,42 @@
 
 :- pragma foreign_decl("C", "#include ""mercury_deep_profiling.h""").
 
-:- func token_call_site_static = int.
-:- pragma foreign_proc("C",
-    token_call_site_static = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_call_site_static;
-").
-
-:- func token_call_site_dynamic = int.
-:- pragma foreign_proc("C",
-    token_call_site_dynamic = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_call_site_dynamic;
-").
-
-:- func token_proc_static = int.
-:- pragma foreign_proc("C",
-    token_proc_static = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_proc_static;
-").
-
-:- func token_proc_dynamic = int.
-:- pragma foreign_proc("C",
-    token_proc_dynamic = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_proc_dynamic;
-").
-
-:- func token_normal_call = int.
-:- pragma foreign_proc("C",
-    token_normal_call = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_normal_call;
-").
-
-:- func token_special_call = int.
-:- pragma foreign_proc("C",
-    token_special_call = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_special_call;
-").
-
-:- func token_higher_order_call = int.
-:- pragma foreign_proc("C",
-    token_higher_order_call = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_higher_order_call;
-").
-
-:- func token_method_call = int.
-:- pragma foreign_proc("C",
-    token_method_call = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_method_call;
-").
+:- type next_deep_item
+    --->    deep_item_end
+    ;       deep_item_call_site_static
+    ;       deep_item_call_site_dynamic
+    ;       deep_item_proc_static
+    ;       deep_item_proc_dynamic.
+
+:- pragma foreign_enum("C", next_deep_item/0, [
+    deep_item_end                - "MR_deep_item_end",
+    deep_item_call_site_static   - "MR_deep_item_call_site_static",
+    deep_item_call_site_dynamic  - "MR_deep_item_call_site_dynamic",
+    deep_item_proc_static        - "MR_deep_item_proc_static",
+    deep_item_proc_dynamic       - "MR_deep_item_proc_dynamic"
+]).
 
-:- func token_callback = int.
-:- pragma foreign_proc("C",
-    token_callback = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_callback;
-").
+:- pred is_next_item_token(int::in, next_deep_item::out) is semidet.
 
-:- func token_isa_predicate = int.
 :- pragma foreign_proc("C",
-    token_isa_predicate = (X::out),
+    is_next_item_token(Int::in, NextItem::out),
     [promise_pure, will_not_call_mercury, thread_safe],
 "
-    X = MR_deep_token_isa_predicate;
-").
+    NextItem = (MR_DeepProfNextItem) Int;
 
-:- func token_isa_function = int.
-:- pragma foreign_proc("C",
-    token_isa_function = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_isa_function;
-").
-
-:- func token_isa_uci_pred = int.
-:- pragma foreign_proc("C",
-    token_isa_uci_pred = (X::out),
-    [promise_pure, will_not_call_mercury, thread_safe],
-"
-    X = MR_deep_token_isa_uci_pred;
+    switch (NextItem) {
+        case MR_deep_item_end:
+        case MR_deep_item_call_site_static:
+        case MR_deep_item_call_site_dynamic:
+        case MR_deep_item_proc_static:
+        case MR_deep_item_proc_dynamic:
+            SUCCESS_INDICATOR = MR_TRUE;
+            break;
+
+        default:
+            SUCCESS_INDICATOR = MR_FALSE;
+            break;
+    }
 ").
 
 %------------------------------------------------------------------------------%
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
Index: doc/user_guide.texi
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/doc/user_guide.texi,v
retrieving revision 1.543
diff -u -b -r1.543 user_guide.texi
--- doc/user_guide.texi	6 Sep 2007 12:45:25 -0000	1.543
+++ doc/user_guide.texi	10 Sep 2007 05:23:38 -0000
@@ -9699,6 +9699,26 @@
 @c The intended use is to override the installed version of mtc_union
 @c with the version in a specific workspace, which may be more recent.
 
+ at c @sp 1
+ at c @item --deep-procrep-file
+ at c #findex --deep-procrep-file
+ at c This option, which is meaningful only in deep profiling grades,
+ at c asks that every Deep.data file being generated should be accompanied by
+ at c a Deep.procrep file that contains a representation of the program that
+ at c generated it.
+ at c This documentation is commented out
+ at c because procedure representations are not yet used.
+
+ at c @sp 1
+ at c @item --deep-random-write=@var{N}
+ at c #findex --deep-random-write=@var{N}
+ at c This option, which is meaningful only in deep profiling grades,
+ at c asks that Deep.data files (and Deep.procrep files) should be generated
+ at c only if by processes whose process id is evenly divisible by @var{N}.
+ at c This documentation is commented out because it is only for use by the
+ at c bootcheck script (to reduce the time taken for a bootcheck while still
+ at c testing the code writing out deep profiling data).
+
 @end table
 
 @sp 1
cvs diff: Diffing extras
cvs diff: Diffing extras/base64
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/fixed
cvs diff: Diffing extras/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_allegro
cvs diff: Diffing extras/graphics/mercury_allegro/examples
cvs diff: Diffing extras/graphics/mercury_allegro/samples
cvs diff: Diffing extras/graphics/mercury_allegro/samples/demo
cvs diff: Diffing extras/graphics/mercury_allegro/samples/mandel
cvs diff: Diffing extras/graphics/mercury_allegro/samples/pendulum2
cvs diff: Diffing extras/graphics/mercury_allegro/samples/speed
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/log4m
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/mopenssl
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/net
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/posix/samples
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
Index: library/exception.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/exception.m,v
retrieving revision 1.130
diff -u -b -r1.130 exception.m
--- library/exception.m	22 Aug 2007 06:40:58 -0000	1.130
+++ library/exception.m	6 Sep 2007 05:39:16 -0000
@@ -1657,7 +1657,8 @@
 void mercury_sys_init_exceptions_init(void);
 void mercury_sys_init_exceptions_init_type_tables(void);
 #ifdef  MR_DEEP_PROFILING
-void mercury_sys_init_exceptions_write_out_proc_statics(FILE *fp);
+void mercury_sys_init_exceptions_write_out_proc_statics(FILE *deep_fp,
+    FILE *procrep_fp);
 #endif
 
 #ifndef MR_HIGHLEVEL_CODE
@@ -2615,21 +2616,22 @@
 
 #ifdef  MR_DEEP_PROFILING
 void
-mercury_sys_init_exceptions_write_out_proc_statics(FILE *fp)
+mercury_sys_init_exceptions_write_out_proc_statics(FILE *deep_fp,
+    FILE *procrep_fp)
 {
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 0));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 1));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 2));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 3));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 4));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_catch, 3, 5));
-    MR_write_out_user_proc_static(fp,
+    MR_write_out_user_proc_static(deep_fp, procrep_fp,
         &MR_proc_layout_user_name(exception, builtin_throw, 1, 0));
 }
 #endif
Index: library/par_builtin.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/par_builtin.m,v
retrieving revision 1.12
diff -u -b -r1.12 par_builtin.m
--- library/par_builtin.m	17 Jul 2007 05:36:08 -0000	1.12
+++ library/par_builtin.m	6 Sep 2007 05:44:01 -0000
@@ -239,7 +239,8 @@
     void mercury_sys_init_par_builtin_modules_init(void);
     void mercury_sys_init_par_builtin_modules_init_type_tables(void);
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_par_builtin_modules_write_out_proc_statics(FILE *fp);
+    void mercury_sys_init_par_builtin_modules_write_out_proc_statics(
+        FILE *deep_fp, FILE *procrep_fp);
     #endif
 
     void mercury_sys_init_par_builtin_modules_init(void)
@@ -255,7 +256,8 @@
     }
 
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_par_builtin_modules_write_out_proc_statics(FILE *fp)
+    void mercury_sys_init_par_builtin_modules_write_out_proc_statics(
+        FILE *deep_fp, FILE *procrep_fp)
     {
         /* no proc_statics to write out */
     }
Index: library/thread.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/thread.m,v
retrieving revision 1.11
diff -u -b -r1.11 thread.m
--- library/thread.m	17 Jul 2007 05:36:08 -0000	1.11
+++ library/thread.m	6 Sep 2007 05:40:01 -0000
@@ -212,7 +212,8 @@
     void mercury_sys_init_thread_modules_init(void);
     void mercury_sys_init_thread_modules_init_type_tables(void);
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_thread_modules_write_out_proc_statics(FILE *fp);
+    void mercury_sys_init_thread_modules_write_out_proc_statics(
+        FILE *deep_fp, FILE *procrep_fp);
     #endif
 
     void mercury_sys_init_thread_modules_init(void)
@@ -228,7 +229,8 @@
     }
 
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_thread_modules_write_out_proc_statics(FILE *fp)
+    void mercury_sys_init_thread_modules_write_out_proc_statics(FILE *deep_fp,
+        FILE *procrep_fp)
     {
         /* no proc_statics to write out */
     }
Index: library/thread.semaphore.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/library/thread.semaphore.m,v
retrieving revision 1.10
diff -u -b -r1.10 thread.semaphore.m
--- library/thread.semaphore.m	22 Aug 2007 08:19:21 -0000	1.10
+++ library/thread.semaphore.m	6 Sep 2007 05:40:24 -0000
@@ -384,7 +384,8 @@
     void mercury_sys_init_semaphore_modules_init(void);
     void mercury_sys_init_semaphore_modules_init_type_tables(void);
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_semaphore_modules_write_out_proc_statics(FILE *fp);
+    void mercury_sys_init_semaphore_modules_write_out_proc_statics(
+        FILE *deep_fp, FILE *procrep_fp);
     #endif
 
     void mercury_sys_init_semaphore_modules_init(void)
@@ -400,7 +401,8 @@
     }
 
     #ifdef  MR_DEEP_PROFILING
-    void mercury_sys_init_semaphore_modules_write_out_proc_statics(FILE *fp)
+    void mercury_sys_init_semaphore_modules_write_out_proc_statics(
+        FILE *deep_fp, FILE *procrep_fp)
     {
         /* no proc_statics to write out */
     }
cvs diff: Diffing mdbcomp
Index: mdbcomp/prim_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/prim_data.m,v
retrieving revision 1.23
diff -u -b -r1.23 prim_data.m
--- mdbcomp/prim_data.m	23 Aug 2007 04:29:04 -0000	1.23
+++ mdbcomp/prim_data.m	6 Sep 2007 01:39:43 -0000
@@ -72,6 +72,10 @@
     % from `.opt' files, the defining module's name may need to be added
     % as a qualifier to the label.
     %
+    % The type string_proc_label in program_representation.m parallels this
+    % type, but differs from it in being used not inside the compiler by
+    % outside, which means it needs to use different types for many fields.
+    %
 :- type proc_label
     --->    ordinary_proc_label(
                 ord_defining_module     :: module_name,
Index: mdbcomp/program_representation.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/program_representation.m,v
retrieving revision 1.23
diff -u -b -r1.23 program_representation.m
--- mdbcomp/program_representation.m	8 Aug 2007 05:06:06 -0000	1.23
+++ mdbcomp/program_representation.m	10 Sep 2007 14:50:11 -0000
@@ -9,8 +9,8 @@
 % File: program_representation.m
 % Authors: zs, dougl
 %
-% This module defines the representation of procedure bodies
-% used by the declarative debugger.
+% This module defines the representation of procedure bodies used by the
+% declarative debugger (and maybe the deep profiler).
 %
 % One of the things we want the declarative debugger to be able to do
 % is to let the user specify which part of which output argument of an
@@ -18,16 +18,17 @@
 % that particular subterm came from, i.e. where it was bound. Doing this
 % requires knowing what the bodies of that procedure and its descendants are.
 %
-% If the Mercury compiler is invoked with options requesting declarative
-% debugging, it will include in each procedure layout a pointer to a simplified
-% representation of the goal that is the body of the corresponding procedure.
-% We use a simplified representation partly because we want to insulate the
-% code of the declarative debugger from irrelevant changes in HLDS types,
-% and partly because we want to minimize the space taken in up in executables
-% by these representations.
+% If the Mercury compiler is invoked with the right options, it will include
+% in each procedure layout a pointer to a simplified representation of the goal
+% that is the body of the corresponding procedure. We use a simplified
+% representation partly because we want to insulate the code using procedure
+% representations from irrelevant changes in HLDS types, and partly because
+% we want to minimize the space taken in up in executables by these
+% representations.
 %
 % The current representation is intended to contain all the information
-% we are pretty sure can be usefully exploited by the declarative debugger.
+% we are pretty sure can be usefully exploited by the declarative debugger
+% and/or the deep profiler.
 
 %-----------------------------------------------------------------------------%
 
@@ -39,22 +40,80 @@
 
 :- import_module bool.
 :- import_module char.
+:- import_module io.
 :- import_module list.
 :- import_module maybe.
 :- import_module type_desc.
 
-    % A representation of the goal we execute. These need to be generated
-    % statically and stored inside the executable.
+    % read_prog_rep_file(FileName, Result, !IO)
     %
-    % Each element of this structure will correspond one-to-one
-    % to the original stage 90 HLDS.
+:- pred read_prog_rep_file(string::in, io.res(prog_rep)::out, io::di, io::uo)
+    is det.
+
+:- type prog_rep
+    --->    prog_rep(
+                list(module_rep)
+            ).
+
+:- type module_rep
+    --->    module_rep(
+                mr_name         :: string,          % The module name.
+                mr_string_table :: string_table,
+                mr_procs        :: list(proc_rep)
+            ).
 
 :- type proc_rep
     --->    proc_rep(
-                list(var_rep),      % The head variables, in order,
-                                    % including the ones introduced
+                pr_id       :: string_proc_label,
+                pr_defn     :: proc_defn_rep
+            ).
+
+    % A string_proc_label is a data structure that uniquely identifies a
+    % procedure. It is a version of the proc_label type from prim_data.m
+    % that can be used outside the compiler, e.g. in RTTI data structures
+    % and in data filed generated by deep profiling.
+    %
+:- type string_proc_label
+    --->    str_ordinary_proc_label(
+                s_ord_pred_or_func      :: pred_or_func,
+                s_ord_decl_module       :: string,
+                s_ord_def_module        :: string,
+                s_ord_name              :: string,
+                s_ord_arity             :: int,
+                s_ord_mode              :: int
+            )
+    ;       str_special_proc_label(
+                s_spec_type_name        :: string,
+                s_spec_type_module      :: string,
+                s_spec_def_module       :: string,
+                s_spec_pred_name        :: string,
+                s_spec_arity            :: int,
+                s_spec_mode             :: int
+            ).
+
+:- type proclabel_kind_token
+    --->    proclabel_user_predicate
+    ;       proclabel_user_function
+    ;       proclabel_special.
+
+:- pred is_proclabel_kind(int::in, proclabel_kind_token::out) is semidet.
+
+    % A representation of the procedure definitions (clause heads and bodies)
+    % that we execute. These are generated by the compiler, which stores them
+    % in the form of a bytecode representation in a field of proc_layout
+    % structures in the executable.
+    %
+    % Each element of this structure will correspond one-to-one
+    % to an element of the original HLDS at the code generation stage.
+
+:- type proc_defn_rep
+    --->    proc_defn_rep(
+                % The head variables, in order, including the ones introduced
                                     % by the compiler.
-                goal_rep            % The procedure body.
+                list(var_rep),
+
+                % The procedure body.
+                goal_rep
             ).
 
 :- type goal_rep
@@ -65,7 +124,8 @@
                 list(goal_rep)      % The disjuncts in the original order.
             )
     ;       switch_rep(
-                list(goal_rep)      % The switch arms in the original order.
+                var_rep,            % The variable being switched on.
+                list(case_rep)      % The switch arms in the original order.
             )
     ;       ite_rep(
                 goal_rep,           % Condition.
@@ -88,6 +148,14 @@
                 atomic_goal_rep
             ).
 
+:- type case_rep
+    --->    case_rep(
+                cons_id_rep,        % The function symbol unified with the
+                                    % switched-on in this switch arm.
+                int,                % The arity of the function symbol.
+                goal_rep            % The code of the switch arm.
+            ).
+
 :- type atomic_goal_rep
     --->    unify_construct_rep(
                 var_rep,
@@ -102,7 +170,7 @@
     ;       partial_deconstruct_rep(
                 % A partial deconstruction of the form
                 % X = f(Y_1, Y_2, ..., Y_n)
-                % where X is more instanciated after the unification
+                % where X is more instantiated after the unification
                 % than before.
                 var_rep,            % X
                 cons_id_rep,        % f
@@ -180,7 +248,8 @@
     % generates events as ordinary calls do, then return the list of variables
     % that are passed as arguments.
     %
-:- func atomic_goal_generates_event_like_call(atomic_goal_rep) = maybe(list(var_rep)).
+:- func atomic_goal_generates_event_like_call(atomic_goal_rep) =
+    maybe(list(var_rep)).
 
     % If the given goal generates internal events directly then this
     % function will return yes and no otherwise.
@@ -267,14 +336,16 @@
     % the first head variable is at position 1.
 
 :- type arg_pos
-    --->    user_head_var(int)  % Nth in the list of arguments after
-                                % filtering out non-user-visible vars.
-    ;       any_head_var(int)   % Nth in the list of all arguments.
+    --->    user_head_var(int)
+            % Nth in the list of arguments after filtering out
+            % non-user-visible vars.
+
+    ;       any_head_var(int)
+            % Nth in the list of all arguments.
 
     ;       any_head_var_from_back(int).
-                                % (M-N+1)th argument in the list of all
-                                % arguments, where N is the value of the int
-                                % in the constructor and M is the total number
+            % (M-N+1)th argument in the list of all arguments, where N is
+            % the value of the int in the constructor and M is the total number
                                 % of arguments.
 
     % A particular subterm within a term is represented by a term_path.
@@ -283,9 +354,9 @@
     % goal_paths, this list is in top-down order.
 :- type term_path ==    list(int).
 
-    % Returns type_of(_ : proc_rep), for use in C code.
+    % Returns type_of(_ : proc_defn_rep), for use in C code.
     %
-:- func proc_rep_type = type_desc.
+:- func proc_defn_rep_type = type_desc.
 
     % Returns type_of(_ : goal_rep), for use in C code.
     %
@@ -333,8 +404,8 @@
 
 :- pred byte_to_goal_type(int::in, bytecode_goal_type::out) is semidet.
 
-    % A variable number is represented in a byte if there are no more than
-    % 255 variables in the procedure.  Otherwise a short is used.
+    % We represent a variable number as a byte if there are no more than
+    % 255 variables in the procedure; otherwise, we use two bytes.
     %
 :- type var_num_rep
     --->    byte
@@ -346,14 +417,8 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type bytecode
-    --->    dummy_bytecode.
-
-:- pragma foreign_type("C", bytecode, "const MR_uint_least8_t *",
-    [can_pass_as_mercury_type, stable]).
-:- pragma foreign_type("Java", bytecode, "java.lang.Object", []). %stub only
-
-:- pred read_proc_rep(bytecode::in, label_layout::in, proc_rep::out) is det.
+:- pred trace_read_proc_defn_rep(bytecode_bytes::in, label_layout::in,
+    proc_defn_rep::out) is semidet.
 
 %-----------------------------------------------------------------------------%
 
@@ -372,10 +437,10 @@
     %
     % If you are adding a predicate to no_type_info_builtin, remember that
     % this will only affect code built by a compiler linked with the new
-    % mdbcomp library.  e.g. if you add a predicate P to no_type_info_builtin,
-    % the compiler building the stage 1 library won't yet know about P.
-    % The stage 1 compiler _will_ know about P, so stage 2 is when P will
-    % be compiled differently.
+    % mdbcomp library. For example, if you add a predicate P to
+    % no_type_info_builtin, the compiler building the stage 1 library
+    % won't yet know about P. The stage 1 compiler _will_ know about P,
+    % so stage 2 is when P will be compiled differently.
     %
 :- pred no_type_info_builtin(module_name::in, string::in, int::in) is semidet.
 
@@ -389,26 +454,34 @@
 :- import_module require.
 :- import_module string.
 
-atomic_goal_generates_event_like_call(unify_construct_rep(_, _, _)) = no.
-atomic_goal_generates_event_like_call(unify_deconstruct_rep(_, _, _)) = no.
-atomic_goal_generates_event_like_call(partial_construct_rep(_, _, _)) = no.
-atomic_goal_generates_event_like_call(partial_deconstruct_rep(_, _, _)) = no.
-atomic_goal_generates_event_like_call(unify_assign_rep(_, _)) = no.
-atomic_goal_generates_event_like_call(unify_simple_test_rep(_, _)) = no.
-atomic_goal_generates_event_like_call(cast_rep(_, _)) = no.
-atomic_goal_generates_event_like_call(pragma_foreign_code_rep(_)) = no.
-atomic_goal_generates_event_like_call(higher_order_call_rep(_, Args)) =
-        yes(Args).
-atomic_goal_generates_event_like_call(method_call_rep(_, _, Args)) = yes(Args).
-atomic_goal_generates_event_like_call(builtin_call_rep(_, _, _)) = no.
-atomic_goal_generates_event_like_call(plain_call_rep(ModuleName, PredName,
-        Args)) =
-    ( call_does_not_generate_events(ModuleName, PredName, list.length(Args)) ->
-        no
+atomic_goal_generates_event_like_call(GoalRep) = Generates :-
+    (
+        ( GoalRep = unify_construct_rep(_, _, _)
+        ; GoalRep = unify_deconstruct_rep(_, _, _)
+        ; GoalRep = partial_construct_rep(_, _, _)
+        ; GoalRep = partial_deconstruct_rep(_, _, _)
+        ; GoalRep = unify_assign_rep(_, _)
+        ; GoalRep = unify_simple_test_rep(_, _)
+        ; GoalRep = cast_rep(_, _)
+        ; GoalRep = pragma_foreign_code_rep(_)
+        ; GoalRep = builtin_call_rep(_, _, _)
+        ; GoalRep = event_call_rep(_, _)
+        ),
+        Generates = no
     ;
-        yes(Args)
+        ( GoalRep = higher_order_call_rep(_, Args)
+        ; GoalRep = method_call_rep(_, _, Args)
+        ),
+        Generates = yes(Args)
+    ;
+        GoalRep = plain_call_rep(ModuleName, PredName, Args),
+        NumArgs = list.length(Args),
+        ( call_does_not_generate_events(ModuleName, PredName, NumArgs) ->
+            Generates = no
+        ;
+            Generates = yes(Args)
+        )
     ).
-atomic_goal_generates_event_like_call(event_call_rep(_, _)) = no.
 
 call_does_not_generate_events(ModuleName, PredName, Arity) :-
     (
@@ -435,7 +508,7 @@
 
 goal_generates_internal_event(conj_rep(_)) = no.
 goal_generates_internal_event(disj_rep(_)) = yes.
-goal_generates_internal_event(switch_rep(_)) = yes.
+goal_generates_internal_event(switch_rep(_, _)) = yes.
 goal_generates_internal_event(ite_rep(_, _, _)) = yes.
 goal_generates_internal_event(negation_rep(_)) = yes.
 goal_generates_internal_event(scope_rep(_, _)) = no.
@@ -458,9 +531,9 @@
     yes(atomic_goal_id(Module, Name, length(Args))).
 atomic_goal_identifiable(event_call_rep(_, _)) = no.
 
-:- pragma export(proc_rep_type = out, "ML_proc_rep_type").
+:- pragma export(proc_defn_rep_type = out, "ML_proc_defn_rep_type").
 
-proc_rep_type = type_of(_ : proc_rep).
+proc_defn_rep_type = type_of(_ : proc_defn_rep).
 
 :- pragma export(goal_rep_type = out, "ML_goal_rep_type").
 
@@ -493,7 +566,7 @@
 path_step_from_string_2('s', Str, step_switch(N, MaybeM)) :-
     string.words_separator(unify('-'), Str) = [NStr, MStr],
     string.to_int(NStr, N),
-    % short for "not applicable"
+    % "na" is short for "not applicable"
     ( MStr = "na" ->
         MaybeM = no
     ;
@@ -592,105 +665,298 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pragma foreign_export("C", read_proc_rep(in, in, out),
-    "MR_MDBCOMP_trace_read_rep").
+:- pred read_file_as_bytecode(string::in, io.res(bytecode)::out,
+    io::di, io::uo) is det.
+
+read_file_as_bytecode(FileName, Result, !IO) :-
+    read_file_as_bytecode_2(FileName, ByteCode, Size, Error, !IO),
+    ( Size < 0 ->
+        io.make_err_msg(Error, "opening " ++ FileName, Msg, !IO),
+        Result = error(io.make_io_error(Msg))
+    ;
+        Result = ok(bytecode(ByteCode, Size))
+    ).
+
+:- pred read_file_as_bytecode_2(string::in, bytecode_bytes::out, int::out,
+    io.system_error::out, io::di, io::uo) is det.
+
+:- pragma foreign_proc("C",
+    read_file_as_bytecode_2(FileName::in, Bytes::out, Size::out, Error::out,
+        _IO0::di, _IO::uo),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    struct  stat statbuf;
 
-read_proc_rep(Bytecode, Label, ProcRep) :-
+    if (stat(FileName, &statbuf) != 0) {
+        Bytes = NULL;
+        Size = -1;
+        Error = errno;
+    } else {
+        int     fd;
+        char    *buf;
+
+        Size = statbuf.st_size;
+        MR_allocate_aligned_string_msg(buf, Size, MR_PROC_LABEL);
+        fd = open(FileName, O_RDONLY, 0);
+        if (fd < 0) {
+            Bytes = NULL;
+            Size = -1;
+            Error = errno;
+        } else {
+            if (read(fd, buf, Size) != Size) {
+                Bytes = NULL;
+                Size = -1;
+                Error = errno;
+            } else {
+                if (close(fd) != 0) {
+                    Bytes = NULL;
+                    Size = -1;
+                    Error = errno;
+                } else {
+                    Bytes = (MR_uint_least8_t *) buf;
+                    Error = 0;
+                }
+            }
+        }
+    }
+").
+
+%-----------------------------------------------------------------------------%
+
+read_prog_rep_file(FileName, Result, !IO) :-
+    read_file_as_bytecode(FileName, ReadResult, !IO),
+    (
+        ReadResult = error(Error),
+        Result = error(Error)
+    ;
+        ReadResult = ok(ByteCode),
+        (
     some [!Pos] (
         !:Pos = 0,
-        read_int32(Bytecode, !Pos, Limit),
-        read_var_num_rep(Bytecode, !Pos, VarNumRep),
-        read_string(Bytecode, Label, !Pos, FileName),
-        Info = read_proc_rep_info(Limit, FileName),
-        read_vars(VarNumRep, Bytecode, !Pos, HeadVars),
-        read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Goal),
-        ProcRep = proc_rep(HeadVars, Goal),
-        require(unify(!.Pos, Limit), "read_proc_rep: limit mismatch")
+                read_line(ByteCode, Line, !Pos),
+                Line = procrep_id_string,
+                read_module_reps(ByteCode, [], RevModuleReps, !Pos),
+                ByteCode = bytecode(_, Size),
+                !.Pos = Size
+            )
+        ->
+            list.reverse(RevModuleReps, ModuleReps),
+            Result = ok(prog_rep(ModuleReps))
+        ;
+            Msg = FileName ++ "is not a valid program representation file",
+            Result = error(io.make_io_error(Msg))
+        )
+    ).
+
+    % Return the string written out by MR_write_out_procrep_id_string.
+    %
+:- func procrep_id_string = string.
+
+procrep_id_string = "Mercury deep profiler procrep version 1\n".
+
+:- pred read_module_reps(bytecode::in,
+    list(module_rep)::in, list(module_rep)::out,
+    int::in, int::out) is semidet.
+
+read_module_reps(ByteCode, !RevModuleReps, !Pos) :-
+    read_byte(ByteCode, MoreByte, !Pos),
+    is_more_modules(MoreByte, MoreModules),
+    (
+        MoreModules = no_more_modules
+    ;
+        MoreModules = next_module,
+        read_module_rep(ByteCode, ModuleRep, !Pos),
+        !:RevModuleReps = [ModuleRep | !.RevModuleReps],
+        read_module_reps(ByteCode, !RevModuleReps, !Pos)
+    ).
+
+:- pred read_module_rep(bytecode::in, module_rep::out, int::in, int::out)
+    is semidet.
+
+read_module_rep(ByteCode, ModuleRep, !Pos) :-
+    read_len_string(ByteCode, ModuleName, !Pos),
+    read_string_table(ByteCode, StringTable, !Pos),
+    read_proc_reps(ByteCode, StringTable, [], RevProcReps, !Pos),
+    list.reverse(RevProcReps, ProcReps),
+    ModuleRep = module_rep(ModuleName, StringTable, ProcReps).
+
+:- pred read_proc_reps(bytecode::in, string_table::in,
+    list(proc_rep)::in, list(proc_rep)::out, int::in, int::out) is semidet.
+
+read_proc_reps(ByteCode, StringTable, !RevProcReps, !Pos) :-
+    read_byte(ByteCode, MoreByte, !Pos),
+    is_more_procs(MoreByte, MoreProcs),
+    (
+        MoreProcs = no_more_procs
+    ;
+        MoreProcs = next_proc,
+        read_proc_rep(ByteCode, StringTable, ProcRep, !Pos),
+        !:RevProcReps = [ProcRep | !.RevProcReps],
+        read_proc_reps(ByteCode, StringTable, !RevProcReps, !Pos)
+    ).
+
+:- pred read_proc_rep(bytecode::in, string_table::in, proc_rep::out,
+    int::in, int::out) is semidet.
+
+read_proc_rep(ByteCode, StringTable, ProcRep, !Pos) :-
+    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_vars(VarNumRep, ByteCode, HeadVars, !Pos),
+    read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos),
+    ProcDefnRep = proc_defn_rep(HeadVars, Goal),
+    require(unify(!.Pos, StartPos + Size),
+        "trace_read_proc_defn_rep: limit mismatch"),
+    ProcRep = proc_rep(ProcLabel, ProcDefnRep).
+
+:- pred read_string_proc_label(bytecode::in, string_proc_label::out,
+    int::in, int::out) is semidet.
+
+read_string_proc_label(ByteCode, ProcLabel, !Pos) :-
+    read_byte(ByteCode, Byte, !Pos),
+    is_proclabel_kind(Byte, ProcLabelKind),
+    (
+        ProcLabelKind = proclabel_special,
+        read_len_string(ByteCode, TypeName, !Pos),
+        read_len_string(ByteCode, TypeModule, !Pos),
+        read_len_string(ByteCode, DefModule, !Pos),
+        read_len_string(ByteCode, PredName, !Pos),
+        read_num(ByteCode, Arity, !Pos),
+        read_num(ByteCode, ModeNum, !Pos),
+        ProcLabel = str_special_proc_label(TypeName, TypeModule, DefModule,
+            PredName, Arity, ModeNum)
+    ;
+        (
+            ProcLabelKind = proclabel_user_predicate,
+            PredOrFunc = pf_predicate
+        ;
+            ProcLabelKind = proclabel_user_function,
+            PredOrFunc = pf_function
+        ),
+        read_len_string(ByteCode, DeclModule, !Pos),
+        read_len_string(ByteCode, DefModule, !Pos),
+        read_len_string(ByteCode, PredName, !Pos),
+        read_num(ByteCode, Arity, !Pos),
+        read_num(ByteCode, ModeNum, !Pos),
+        ProcLabel = str_ordinary_proc_label(PredOrFunc, DeclModule, DefModule,
+            PredName, Arity, ModeNum)
+    ).
+
+%-----------------------------------------------------------------------------%
+
+:- pragma foreign_export("C", trace_read_proc_defn_rep(in, in, out),
+    "MR_MDBCOMP_trace_read_proc_defn_rep").
+
+trace_read_proc_defn_rep(Bytes, LabelLayout, ProcDefnRep) :-
+    ProcLayout = containing_proc_layout(LabelLayout),
+    ( containing_module_common_layout(ProcLayout, ModuleCommonLayout) ->
+        StringTable = module_common_string_table(ModuleCommonLayout)
+    ;
+        error("trace_read_proc_defn_rep: no module common layout")
+    ),
+    some [!Pos] (
+        !:Pos = 0,
+        % The size of the bytecode is not recorded anywhere in the proc layout
+        % except at the start of the bytecode itself.
+        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_vars(VarNumRep, ByteCode, HeadVars, !Pos),
+        read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos),
+        ProcDefnRep = proc_defn_rep(HeadVars, Goal),
+        require(unify(!.Pos, Size),
+            "trace_read_proc_defn_rep: limit mismatch")
     ).
 
 :- type read_proc_rep_info
     --->    read_proc_rep_info(
-                limit       :: int,
                 filename    :: string
             ).
 
-:- pred read_goal(var_num_rep::in, bytecode::in, label_layout::in, int::in,
-    int::out, read_proc_rep_info::in, goal_rep::out) is det.
+:- pred read_goal(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, goal_rep::out, int::in, int::out) is semidet.
 
-read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Goal) :-
-    read_byte(Bytecode, !Pos, GoalTypeByte),
+read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos) :-
+    read_byte(ByteCode, GoalTypeByte, !Pos),
     ( byte_to_goal_type(GoalTypeByte, GoalType) ->
         (
             GoalType = goal_conj,
-            read_goals(VarNumRep, Bytecode, Label, !Pos, Info,  Goals),
+            read_goals(VarNumRep, ByteCode, StringTable, Info, Goals, !Pos),
             Goal = conj_rep(Goals)
         ;
             GoalType = goal_disj,
-            read_goals(VarNumRep, Bytecode, Label, !Pos, Info, Goals),
+            read_goals(VarNumRep, ByteCode, StringTable, Info, Goals, !Pos),
             Goal = disj_rep(Goals)
         ;
             GoalType = goal_neg,
-            read_goal(VarNumRep, Bytecode, Label, !Pos, Info, SubGoal),
+            read_goal(VarNumRep, ByteCode, StringTable, Info, SubGoal, !Pos),
             Goal = negation_rep(SubGoal)
         ;
             GoalType = goal_ite,
-            read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Cond),
-            read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Then),
-            read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Else),
+            read_goal(VarNumRep, ByteCode, StringTable, Info, Cond, !Pos),
+            read_goal(VarNumRep, ByteCode, StringTable, Info, Then, !Pos),
+            read_goal(VarNumRep, ByteCode, StringTable, Info, Else, !Pos),
             Goal = ite_rep(Cond, Then, Else)
         ;
             GoalType = goal_switch,
-            read_goals(VarNumRep, Bytecode, Label, !Pos, Info, Goals),
-            Goal = switch_rep(Goals)
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_cases(VarNumRep, ByteCode, StringTable, Info, Cases, !Pos),
+            Goal = switch_rep(Var, Cases)
         ;
             GoalType = goal_assign,
-            read_var(VarNumRep, Bytecode, !Pos, Target),
-            read_var(VarNumRep, Bytecode, !Pos, Source),
+            read_var(VarNumRep, ByteCode, Target, !Pos),
+            read_var(VarNumRep, ByteCode, Source, !Pos),
             AtomicGoal = unify_assign_rep(Target, Source),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_construct,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_cons_id(Bytecode, Label, !Pos, ConsId),
-            read_vars(VarNumRep, Bytecode, !Pos, ArgVars),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_cons_id(ByteCode, StringTable, ConsId, !Pos),
+            read_vars(VarNumRep, ByteCode, ArgVars, !Pos),
             AtomicGoal = unify_construct_rep(Var, ConsId, ArgVars),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_deconstruct,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_cons_id(Bytecode, Label, !Pos, ConsId),
-            read_vars(VarNumRep, Bytecode, !Pos, ArgVars),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_cons_id(ByteCode, StringTable, ConsId, !Pos),
+            read_vars(VarNumRep, ByteCode, ArgVars, !Pos),
             AtomicGoal = unify_deconstruct_rep(Var, ConsId, ArgVars),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_partial_construct,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_cons_id(Bytecode, Label, !Pos, ConsId),
-            read_maybe_vars(VarNumRep, Bytecode, !Pos, MaybeVars),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_cons_id(ByteCode, StringTable, ConsId, !Pos),
+            read_maybe_vars(VarNumRep, ByteCode, MaybeVars, !Pos),
             AtomicGoal = partial_construct_rep(Var, ConsId, MaybeVars),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_partial_deconstruct,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_cons_id(Bytecode, Label, !Pos, ConsId),
-            read_maybe_vars(VarNumRep, Bytecode, !Pos, MaybeVars),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_cons_id(ByteCode, StringTable, ConsId, !Pos),
+            read_maybe_vars(VarNumRep, ByteCode, MaybeVars, !Pos),
             AtomicGoal = partial_deconstruct_rep(Var, ConsId, MaybeVars),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_simple_test,
-            read_var(VarNumRep, Bytecode, !Pos, Var1),
-            read_var(VarNumRep, Bytecode, !Pos, Var2),
+            read_var(VarNumRep, ByteCode, Var1, !Pos),
+            read_var(VarNumRep, ByteCode, Var2, !Pos),
             AtomicGoal = unify_simple_test_rep(Var1, Var2),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_scope,
-            read_byte(Bytecode, !Pos, MaybeCutByte),
+            read_byte(ByteCode, MaybeCutByte, !Pos),
             ( MaybeCutByte = 0 ->
                 MaybeCut = scope_is_no_cut
             ; MaybeCutByte = 1 ->
@@ -698,239 +964,215 @@
             ;
                 error("read_goal: bad maybe_cut")
             ),
-            read_goal(VarNumRep, Bytecode, Label, !Pos, Info, SubGoal),
+            read_goal(VarNumRep, ByteCode, StringTable, Info, SubGoal, !Pos),
             Goal = scope_rep(SubGoal, MaybeCut)
         ;
             GoalType = goal_ho_call,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = higher_order_call_rep(Var, Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_method_call,
-            read_var(VarNumRep, Bytecode, !Pos, Var),
-            read_method_num(Bytecode, !Pos, MethodNum),
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_var(VarNumRep, ByteCode, Var, !Pos),
+            read_method_num(ByteCode, MethodNum, !Pos),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = method_call_rep(Var, MethodNum, Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_cast,
-            read_var(VarNumRep, Bytecode, !Pos, OutputVar),
-            read_var(VarNumRep, Bytecode, !Pos, InputVar),
+            read_var(VarNumRep, ByteCode, OutputVar, !Pos),
+            read_var(VarNumRep, ByteCode, InputVar, !Pos),
             AtomicGoal = cast_rep(OutputVar, InputVar),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_plain_call,
-            read_string(Bytecode, Label, !Pos, ModuleName),
-            read_string(Bytecode, Label, !Pos, PredName),
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_string_via_offset(ByteCode, StringTable, ModuleName, !Pos),
+            read_string_via_offset(ByteCode, StringTable, PredName, !Pos),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = plain_call_rep(ModuleName, PredName, Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_builtin_call,
-            read_string(Bytecode, Label, !Pos, ModuleName),
-            read_string(Bytecode, Label, !Pos, PredName),
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_string_via_offset(ByteCode, StringTable, ModuleName, !Pos),
+            read_string_via_offset(ByteCode, StringTable, PredName, !Pos),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = builtin_call_rep(ModuleName, PredName, Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_event_call,
-            read_string(Bytecode, Label, !Pos, EventName),
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_string_via_offset(ByteCode, StringTable, EventName, !Pos),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = event_call_rep(EventName, Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable,
+                Info, AtomicGoal, Goal, !Pos)
         ;
             GoalType = goal_foreign,
-            read_vars(VarNumRep, Bytecode, !Pos, Args),
+            read_vars(VarNumRep, ByteCode, Args, !Pos),
             AtomicGoal = pragma_foreign_code_rep(Args),
-            read_atomic_info(VarNumRep, Bytecode, Label, !Pos,
-                Info, AtomicGoal, Goal)
+            read_atomic_info(VarNumRep, ByteCode, StringTable, Info,
+                AtomicGoal, Goal, !Pos)
         )
     ;
         error("read_goal: invalid goal type")
     ).
 
-:- pred read_atomic_info(var_num_rep::in, bytecode::in, label_layout::in,
-    int::in, int::out, read_proc_rep_info::in, atomic_goal_rep::in,
-    goal_rep::out) is det.
-
-read_atomic_info(VarNumRep, Bytecode, Label, !Pos, Info, AtomicGoal, Goal) :-
-    read_byte(Bytecode, !Pos, DetismByte),
+:- pred read_atomic_info(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, atomic_goal_rep::in, goal_rep::out,
+    int::in, int::out) is semidet.
+
+read_atomic_info(VarNumRep, ByteCode, StringTable, Info, AtomicGoal, Goal,
+        !Pos) :-
+    read_byte(ByteCode, DetismByte, !Pos),
     ( determinism_representation(DetismPrime, DetismByte) ->
         Detism = DetismPrime
     ;
         error("read_atomic_info: bad detism")
     ),
-    read_string(Bytecode, Label, !Pos, FileName0),
+    read_string_via_offset(ByteCode, StringTable, FileName0, !Pos),
     ( FileName0 = "" ->
         FileName = Info ^ filename
     ;
         FileName = FileName0
     ),
-    read_lineno(Bytecode, !Pos, LineNo),
-    read_vars(VarNumRep, Bytecode, !Pos, BoundVars),
+    read_lineno(ByteCode, LineNo, !Pos),
+    read_vars(VarNumRep, ByteCode, BoundVars, !Pos),
     Goal = atomic_goal_rep(Detism, FileName, LineNo, BoundVars, AtomicGoal).
 
-:- pred read_goals(var_num_rep::in, bytecode::in, label_layout::in, int::in,
-    int::out, read_proc_rep_info::in, list(goal_rep)::out) is det.
+:- pred read_goals(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, list(goal_rep)::out, int::in, int::out) is semidet.
 
-read_goals(VarNumRep, Bytecode, Label, !Pos, Info, Goals) :-
-    read_length(Bytecode, !Pos, Len),
-    read_goals_2(VarNumRep, Bytecode, Label, !Pos, Info, Len, Goals).
+read_goals(VarNumRep, ByteCode, StringTable, Info, Goals, !Pos) :-
+    read_length(ByteCode, Len, !Pos),
+    read_goals_2(VarNumRep, ByteCode, StringTable, Info, Len, Goals, !Pos).
 
-:- pred read_goals_2(var_num_rep::in, bytecode::in, label_layout::in, int::in,
-    int::out, read_proc_rep_info::in, int::in, list(goal_rep)::out) is det.
+:- pred read_goals_2(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, int::in, list(goal_rep)::out, int::in, int::out)
+    is semidet.
 
-read_goals_2(VarNumRep, Bytecode, Label, !Pos, Info, N, Goals) :-
+read_goals_2(VarNumRep, ByteCode, StringTable, Info, N, Goals, !Pos) :-
     ( N > 0 ->
-        read_goal(VarNumRep, Bytecode, Label, !Pos, Info, Head),
-        read_goals_2(VarNumRep, Bytecode, Label, !Pos, Info, N - 1, Tail),
+        read_goal(VarNumRep, ByteCode, StringTable, Info, Head, !Pos),
+        read_goals_2(VarNumRep, ByteCode, StringTable, Info, N - 1, Tail,
+            !Pos),
         Goals = [Head | Tail]
     ;
         Goals = []
     ).
 
-:- pred read_vars(var_num_rep::in, bytecode::in, int::in, int::out,
-    list(var_rep)::out) is det.
+:- pred read_cases(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, list(case_rep)::out, int::in, int::out) is semidet.
+
+read_cases(VarNumRep, ByteCode, StringTable, Info, Cases, !Pos) :-
+    read_length(ByteCode, Len, !Pos),
+    read_cases_2(VarNumRep, ByteCode, StringTable, Info, Len, Cases, !Pos).
+
+:- pred read_cases_2(var_num_rep::in, bytecode::in, string_table::in,
+    read_proc_rep_info::in, int::in, list(case_rep)::out, int::in, int::out)
+    is semidet.
+
+read_cases_2(VarNumRep, ByteCode, StringTable, Info, N, Cases, !Pos) :-
+    ( N > 0 ->
+        read_cons_id(ByteCode, StringTable, ConsId, !Pos),
+        read_short(ByteCode, ConsIdArity, !Pos),
+        read_goal(VarNumRep, ByteCode, StringTable, Info, Goal, !Pos),
+        Head = case_rep(ConsId, ConsIdArity, Goal),
+        read_cases_2(VarNumRep, ByteCode, StringTable, Info, N - 1, Tail,
+            !Pos),
+        Cases = [Head | Tail]
+    ;
+        Cases = []
+    ).
+
+:- pred read_vars(var_num_rep::in, bytecode::in, list(var_rep)::out,
+    int::in, int::out) is semidet.
 
-read_vars(VarNumRep, Bytecode, !Pos, Vars) :-
-    read_length(Bytecode, !Pos, Len),
-    read_vars_2(VarNumRep, Bytecode, Len, !Pos, Vars).
+read_vars(VarNumRep, ByteCode, Vars, !Pos) :-
+    read_length(ByteCode, Len, !Pos),
+    read_vars_2(VarNumRep, ByteCode, Len, Vars, !Pos).
 
-:- pred read_vars_2(var_num_rep::in, bytecode::in, int::in, int::in, int::out,
-    list(var_rep)::out) is det.
+:- pred read_vars_2(var_num_rep::in, bytecode::in, int::in,
+    list(var_rep)::out, int::in, int::out) is semidet.
 
-read_vars_2(VarNumRep, Bytecode, N, !Pos, Vars) :-
+read_vars_2(VarNumRep, ByteCode, N, Vars, !Pos) :-
     ( N > 0 ->
-        read_var(VarNumRep, Bytecode, !Pos, Head),
-        read_vars_2(VarNumRep, Bytecode, N - 1, !Pos, Tail),
+        read_var(VarNumRep, ByteCode, Head, !Pos),
+        read_vars_2(VarNumRep, ByteCode, N - 1, Tail, !Pos),
         Vars = [Head | Tail]
     ;
         Vars = []
     ).
 
-:- pred read_maybe_vars(var_num_rep::in, bytecode::in, int::in, int::out,
-    list(maybe(var_rep))::out) is det.
+:- pred read_maybe_vars(var_num_rep::in, bytecode::in,
+    list(maybe(var_rep))::out, int::in, int::out) is semidet.
 
-read_maybe_vars(VarNumRep, Bytecode, !Pos, MaybeVars) :-
-    read_length(Bytecode, !Pos, Len),
-    read_maybe_vars_2(VarNumRep, Bytecode, Len, !Pos, MaybeVars).
+read_maybe_vars(VarNumRep, ByteCode, MaybeVars, !Pos) :-
+    read_length(ByteCode, Len, !Pos),
+    read_maybe_vars_2(VarNumRep, ByteCode, Len, MaybeVars, !Pos).
 
-:- pred read_maybe_vars_2(var_num_rep::in, bytecode::in, int::in, int::in,
-    int::out, list(maybe(var_rep))::out) is det.
+:- pred read_maybe_vars_2(var_num_rep::in, bytecode::in, int::in,
+    list(maybe(var_rep))::out, int::in, int::out) is semidet.
 
-read_maybe_vars_2(VarNumRep, Bytecode, N, !Pos, MaybeVars) :-
+read_maybe_vars_2(VarNumRep, ByteCode, N, MaybeVars, !Pos) :-
     ( N > 0 ->
-        read_byte(Bytecode, !Pos, YesOrNo),
+        read_byte(ByteCode, YesOrNo, !Pos),
         ( YesOrNo = 1 ->
-            read_var(VarNumRep, Bytecode, !Pos, Head),
+            read_var(VarNumRep, ByteCode, Head, !Pos),
             MaybeHead = yes(Head)
         ; YesOrNo = 0 ->
             MaybeHead = no
         ;
             error("read_maybe_vars_2: invalid yes or no flag")
         ),
-        read_maybe_vars_2(VarNumRep, Bytecode, N - 1, !Pos, Tail),
+        read_maybe_vars_2(VarNumRep, ByteCode, N - 1, Tail, !Pos),
         MaybeVars = [MaybeHead | Tail]
     ;
         MaybeVars = []
     ).
 
-:- pred read_var(var_num_rep::in, bytecode::in, int::in, int::out,
-    var_rep::out) is det.
+:- pred read_var(var_num_rep::in, bytecode::in, var_rep::out,
+    int::in, int::out) is semidet.
 
-read_var(VarNumRep, Bytecode, !Pos, Var) :-
+read_var(VarNumRep, ByteCode, Var, !Pos) :-
     (
         VarNumRep = byte,
-        read_byte(Bytecode, !Pos, Var)
+        read_byte(ByteCode, Var, !Pos)
     ;
         VarNumRep = short,
-        read_short(Bytecode, !Pos, Var)
+        read_short(ByteCode, Var, !Pos)
     ).
 
-:- pred read_length(bytecode::in, int::in, int::out, var_rep::out) is det.
+:- pred read_length(bytecode::in, var_rep::out, int::in, int::out) is semidet.
 
-read_length(Bytecode, !Pos, Len) :-
-    read_short(Bytecode, !Pos, Len).
+read_length(ByteCode, Len, !Pos) :-
+    read_short(ByteCode, Len, !Pos).
 
-:- pred read_lineno(bytecode::in, int::in, int::out, var_rep::out) is det.
-
-read_lineno(Bytecode, !Pos, LineNo) :-
-    read_short(Bytecode, !Pos, LineNo).
-
-:- pred read_method_num(bytecode::in, int::in, int::out, var_rep::out) is det.
-
-read_method_num(Bytecode, !Pos, MethodNum) :-
-    read_short(Bytecode, !Pos, MethodNum).
-
-:- pred read_cons_id(bytecode::in, label_layout::in, int::in, int::out,
-    cons_id_rep::out) is det.
-
-read_cons_id(Bytecode, Label, !Pos, ConsId) :-
-    read_string(Bytecode, Label, !Pos, ConsId).
-
-%-----------------------------------------------------------------------------%
-
-:- pred read_byte(bytecode::in, int::in, int::out, int::out) is det.
-
-:- pragma foreign_proc("C",
-    read_byte(Bytecode::in, Pos0::in, Pos::out, Value::out),
-    [will_not_call_mercury, thread_safe, promise_pure],
-"
-    Value = Bytecode[Pos0];
-    Pos = Pos0 + 1;
-").
-
-:- pred read_short(bytecode::in, int::in, int::out, int::out) is det.
-
-:- pragma foreign_proc("C",
-    read_short(Bytecode::in, Pos0::in, Pos::out, Value::out),
-    [will_not_call_mercury, thread_safe, promise_pure],
-"
-    Value = (Bytecode[Pos0] << 8) + Bytecode[Pos0+1];
-    Pos = Pos0 + 2;
-").
+:- pred read_lineno(bytecode::in, int::out, int::in, int::out) is semidet.
 
-:- pred read_int32(bytecode::in, int::in, int::out, int::out) is det.
+read_lineno(ByteCode, LineNo, !Pos) :-
+    read_short(ByteCode, LineNo, !Pos).
 
-:- pragma foreign_proc("C",
-    read_int32(Bytecode::in, Pos0::in, Pos::out, Value::out),
-    [will_not_call_mercury, thread_safe, promise_pure],
-"
-    Value = (Bytecode[Pos0] << 24) + (Bytecode[Pos0+1] << 16) +
-        (Bytecode[Pos0+2] << 8) + Bytecode[Pos0+3];
-    Pos = Pos0 + 4;
-").
+:- pred read_method_num(bytecode::in, int::out, int::in, int::out) is semidet.
 
-:- pred read_string(bytecode::in, label_layout::in, int::in, int::out,
-    string::out) is det.
+read_method_num(ByteCode, MethodNum, !Pos) :-
+    read_short(ByteCode, MethodNum, !Pos).
 
-:- pragma foreign_proc("C",
-    read_string(Bytecode::in, Label::in, Pos0::in, Pos::out, Value::out),
-    [will_not_call_mercury, thread_safe, promise_pure],
-"
-    int         offset;
-    const char  *str;
+:- pred read_cons_id(bytecode::in, string_table::in, cons_id_rep::out,
+    int::in, int::out) is semidet.
 
-    offset = (Bytecode[Pos0] << 24) + (Bytecode[Pos0+1] << 16) +
-        (Bytecode[Pos0+2] << 8) + Bytecode[Pos0+3];
-    Pos = Pos0 + 4;
-    str = Label->MR_sll_entry->MR_sle_module_layout->MR_ml_string_table
-        + offset;
-    MR_make_aligned_string(Value, str);
-").
+read_cons_id(ByteCode, StringTable, ConsId, !Pos) :-
+    read_string_via_offset(ByteCode, StringTable, ConsId, !Pos).
 
-:- pred read_var_num_rep(bytecode::in, int::in, int::out, var_num_rep::out)
-    is det.
+:- pred read_var_num_rep(bytecode::in, var_num_rep::out, int::in, int::out)
+    is semidet.
 
-read_var_num_rep(Bytecode, !Pos, VarNumRep) :-
-    read_byte(Bytecode, !Pos, Byte),
+read_var_num_rep(ByteCode, VarNumRep, !Pos) :-
+    read_byte(ByteCode, Byte, !Pos),
     ( var_num_rep_byte(VarNumRep0, Byte) ->
         VarNumRep = VarNumRep0
     ;
@@ -1005,3 +1247,88 @@
 pred_is_external("builtin", "compare_representation", 4).
 
 %-----------------------------------------------------------------------------%
+
+:- type more_modules
+    --->    no_more_modules
+    ;       next_module.
+
+:- pragma foreign_enum("C", more_modules/0, [
+    no_more_modules - "MR_no_more_modules",
+    next_module     - "MR_next_module"
+]).
+
+:- pred is_more_modules(int::in, more_modules::out) is semidet.
+
+:- pragma foreign_proc("C",
+    is_more_modules(Int::in, MoreModules::out),
+    [promise_pure, will_not_call_mercury, thread_safe],
+"
+    MoreModules = (MR_MoreModules) Int;
+
+    switch (MoreModules) {
+        case MR_no_more_modules:
+        case MR_next_module:
+            SUCCESS_INDICATOR = MR_TRUE;
+            break;
+
+        default:
+            SUCCESS_INDICATOR = MR_FALSE;
+            break;
+    }
+").
+
+:- type more_procs
+    --->    no_more_procs
+    ;       next_proc.
+
+:- pragma foreign_enum("C", more_procs/0, [
+    no_more_procs   - "MR_no_more_procs",
+    next_proc       - "MR_next_proc"
+]).
+
+:- pred is_more_procs(int::in, more_procs::out) is semidet.
+
+:- pragma foreign_proc("C",
+    is_more_procs(Int::in, MoreProcs::out),
+    [promise_pure, will_not_call_mercury, thread_safe],
+"
+    MoreProcs = (MR_MoreProcs) Int;
+
+    switch (MoreProcs) {
+        case MR_no_more_procs:
+        case MR_next_proc:
+            SUCCESS_INDICATOR = MR_TRUE;
+            break;
+
+        default:
+            SUCCESS_INDICATOR = MR_FALSE;
+            break;
+    }
+").
+
+:- pragma foreign_enum("C", proclabel_kind_token/0, [
+    proclabel_user_predicate    - "MR_proclabel_user_predicate",
+    proclabel_user_function     - "MR_proclabel_user_function",
+    proclabel_special           - "MR_proclabel_special"
+]).
+
+:- pragma foreign_proc("C",
+    is_proclabel_kind(Int::in, ProcLabelKind::out),
+    [promise_pure, will_not_call_mercury, thread_safe],
+"
+    ProcLabelKind = (MR_ProcLabelToken) Int;
+
+    switch (ProcLabelKind) {
+        case MR_proclabel_user_predicate:
+        case MR_proclabel_user_function:
+        case MR_proclabel_special:
+            SUCCESS_INDICATOR = MR_TRUE;
+            break;
+
+        default:
+            SUCCESS_INDICATOR = MR_FALSE;
+            break;
+    }
+").
+
+%-----------------------------------------------------------------------------%
Index: mdbcomp/rtti_access.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/mdbcomp/rtti_access.m,v
retrieving revision 1.10
diff -u -b -r1.10 rtti_access.m
--- mdbcomp/rtti_access.m	14 Jun 2007 07:18:38 -0000	1.10
+++ mdbcomp/rtti_access.m	6 Sep 2007 11:00:34 -0000
@@ -1,5 +1,5 @@
 %-----------------------------------------------------------------------------%
-% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+% vim: ft=mercury ts=4 sw=4 et
 %-----------------------------------------------------------------------------%
 % Copyright (C) 2005-2006 The University of Melbourne.
 % This file may only be copied under the terms of the GNU General
@@ -39,6 +39,8 @@
 :- pred get_context_from_label_layout(label_layout::in, string::out, int::out)
     is semidet.
 
+%-----------------------------------------------------------------------------%
+
 :- type proc_layout.
 
 :- func get_proc_label_from_layout(proc_layout) = proc_label.
@@ -46,6 +48,7 @@
 :- func get_proc_name(proc_label) = string.
 
     % find_initial_version_arg_num(Proc, OutputArgNum, InputArgNum).
+    %
     % Given a procedure and an output argument number of that procedure,
     % find an input argument which has the same name as the output argument,
     % expect for a numerical suffix and possibly an underscore.  The output
@@ -57,24 +60,123 @@
     % heuristic is used by the subterm dependency tracking algorithm to help
     % speed up the search.
     % Argument numbers start at one.
-    % This procedure is implemented in C to avoid having to allocate
-    % memory to import non word-aligned strings into Mercury code.
+    % This procedure is implemented in C to avoid having to allocate memory
+    % to import non-word-aligned strings into Mercury code.
     %
 :- pred find_initial_version_arg_num(proc_layout::in, int::in, int::out)
     is semidet.
 
 :- func get_all_modes_for_layout(proc_layout) = list(proc_layout).
 
+:- func containing_proc_layout(label_layout) = proc_layout.
+
+:- func proc_bytecode_bytes(proc_layout) = bytecode_bytes.
+
 %-----------------------------------------------------------------------------%
+
+:- type string_table
+    --->    string_table(
+                string_table_chars,
+                            % The characters of the string table, which
+                            % may include null characters.
+                int         % The number of characters in the string table.
+            ).
+
+:- type module_common_layout.
+:- type string_table_chars.
+
+:- pred containing_module_common_layout(proc_layout::in,
+    module_common_layout::out) is semidet.
+
+:- func module_common_string_table(module_common_layout) = string_table.
+
+:- func lookup_string_table(string_table, int) = string.
+
+%-----------------------------------------------------------------------------%
+
+:- type bytecode
+    --->    bytecode(
+                bytecode_bytes,     % The bytes of the bytecode.`
+                int                 % The number of bytes in the bytecode.
+            ).
+
+:- type bytecode_bytes
+    --->    dummy_bytecode_bytes.
+
+:- pragma foreign_type("C", bytecode_bytes, "const MR_uint_least8_t *",
+    [can_pass_as_mercury_type, stable]).
+:- pragma foreign_type("Java", bytecode_bytes, "java.lang.Object", []).
+    % stub only
+
+    % read_byte(ByteCode, Byte, !Pos):
+    %
+    % Read a single byte.
+    %
+:- pred read_byte(bytecode::in, int::out, int::in, int::out) is semidet.
+
+    % read_short(ByteCode, Short, !Pos):
+    %
+    % Read a short that is represented by two bytes.
+    %
+:- pred read_short(bytecode::in, int::out, int::in, int::out) is semidet.
+
+    % read_int32(ByteCode, Int, !Pos):
+    %
+    % Read four byte integer.
+    %
+:- pred read_int32(bytecode::in, int::out, int::in, int::out) is semidet.
+
+    % read_num(ByteCode, Num, !Pos):
+    %
+    % Read an integer encoded using the deep profiler's variable length
+    % encoding scheme.
+    %
+:- pred read_num(bytecode::in, int::out, int::in, int::out) is semidet.
+
+    % read_string_via_offset(ByteCode, StringTable, String, !Pos):
+    %
+    % Read a string represented as a four-byte integer giving an offset
+    % in the string table.
+    %
+:- pred read_string_via_offset(bytecode::in, string_table::in, string::out,
+    int::in, int::out) is semidet.
+
+    % read_line(ByteCode, Line, !Pos):
+    %
+    % Read a sequence of characters ending in a newline.
+    %
+:- pred read_line(bytecode::in, string::out, int::in, int::out) is semidet.
+
+    % read_len_string(ByteCode, String, !Pos):
+    %
+    % Read a string represented as a <length, characters> sequence, in which
+    % the length is encoded using the deep profiler's variable length
+    % encoding scheme.
+    %
+:- pred read_len_string(bytecode::in, string::out, int::in, int::out)
+    is semidet.
+
+    % read_string_table(ByteCode, StringTable, !Pos):
+    %
+    % Given that ByteCode contains a string table starting at the position
+    % given by !.Pos, return that string table and set !:Pos to point to
+    % the first byte after it.
+    %
+:- pred read_string_table(bytecode::in, string_table::out,
+    int::in, int::out) is semidet.
+
 %-----------------------------------------------------------------------------%
 
 :- implementation.
 
+:- import_module char.
+:- import_module int.
 :- import_module require.
+:- import_module string.
 
 :- pragma foreign_type("C", label_layout, "const MR_LabelLayout *",
     [can_pass_as_mercury_type, stable]).
-    % stubs only
+    % The Java and Erlang definitions are only stubs.
 :- pragma foreign_type("Java", label_layout, "java.lang.Object", []).
 :- pragma foreign_type("Erlang", label_layout, "").
 
@@ -127,10 +229,12 @@
     ),
     PathPort = make_path_port(GoalPath, Port).
 
+%-----------------------------------------------------------------------------%
+
 :- pragma foreign_type("C", proc_layout, "const MR_ProcLayout *",
     [can_pass_as_mercury_type, stable]).
-    % stubs only
-:- pragma foreign_type("Java", proc_layout, "java.lang.Object", []). %stub only
+    % The Java and Erlang definitions are only stubs.
+:- pragma foreign_type("Java", proc_layout, "java.lang.Object", []).
 :- pragma foreign_type("Erlang", proc_layout, "").
 
 get_proc_label_from_layout(Layout) = ProcLabel :-
@@ -429,6 +533,220 @@
     Layouts = list;
 ").
 
+:- pragma foreign_proc("C",
+    containing_proc_layout(LabelLayout::in) = (ProcLayout::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    ProcLayout = LabelLayout->MR_sll_entry;
+").
+
+:- pragma foreign_proc("C",
+    proc_bytecode_bytes(ProcLayout::in) = (ByteCodeBytes::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    ByteCodeBytes = ProcLayout->MR_sle_body_bytes;
+#ifdef MR_DEBUG_PROC_REP
+    printf(""lookup_proc_bytecode: %p %p\\n"", ProcLayout, ByteCodeBytes);
+#endif
+").
+
+    % Default version for non-C backends.
+proc_bytecode_bytes(_) = dummy_bytecode_bytes.
+
+%-----------------------------------------------------------------------------%
+
+:- pragma foreign_type("C", module_common_layout,
+    "const MR_ModuleCommonLayout *",
+    [can_pass_as_mercury_type, stable]).
+    % The Java and Erlang definitions are only stubs.
+:- pragma foreign_type("Java", module_common_layout, "java.lang.Object", []).
+:- pragma foreign_type("Erlang", module_common_layout, "").
+
+:- pragma foreign_type("C", string_table_chars, "MR_ConstString",
+    [can_pass_as_mercury_type, stable]).
+    % The Java and Erlang definitions are only stubs.
+:- pragma foreign_type("Java", string_table_chars, "java.lang.Object", []).
+:- pragma foreign_type("Erlang", string_table_chars, "").
+
+:- pragma foreign_proc("C",
+    containing_module_common_layout(ProcLayout::in, ModuleCommonLayout::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    if (MR_PROC_LAYOUT_HAS_THIRD_GROUP(ProcLayout)) {
+        ModuleCommonLayout = ProcLayout->MR_sle_module_common_layout;
+        SUCCESS_INDICATOR = MR_TRUE;
+    } else {
+        SUCCESS_INDICATOR = MR_FALSE;
+    }
+").
+
+module_common_string_table(ModuleCommonLayout) = StringTable :-
+    module_string_table_components(ModuleCommonLayout, StringTableChars, Size),
+    StringTable = string_table(StringTableChars, Size).
+
+:- pred module_string_table_components(module_common_layout::in,
+    string_table_chars::out, int::out) is det.
+
+:- pragma foreign_proc("C",
+    module_string_table_components(ModuleCommonLayout::in,
+        StringTableChars::out, Size::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    StringTableChars = ModuleCommonLayout->MR_mlc_string_table;
+    Size = ModuleCommonLayout->MR_mlc_string_table_size;
+").
+
+lookup_string_table(StringTable, StartOffset) = Str :-
+    StringTable = string_table(StringTableChars, Size),
+    (
+        0 =< StartOffset,
+        StartOffset < Size
+    ->
+        Str = lookup_string_table_2(StringTableChars, StartOffset)
+    ;
+        error("lookup_string_table: bounds violation")
+    ).
+
+:- func lookup_string_table_2(string_table_chars, int) = string.
+
+:- pragma foreign_proc("C",
+    lookup_string_table_2(StringTableChars::in, StartOffset::in) = (Str::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    MR_make_aligned_string(Str, StringTableChars + StartOffset);
+").
+
+%-----------------------------------------------------------------------------%
+
+read_byte(ByteCode, Value, !Pos) :-
+    ByteCode = bytecode(Bytes, Size),
+    !.Pos + 1 =< Size,
+    read_byte_2(Bytes, Value, !Pos).
+
+:- pred read_byte_2(bytecode_bytes::in, int::out, int::in, int::out) is det.
+
+:- pragma foreign_proc("C",
+    read_byte_2(ByteCode::in, Value::out, Pos0::in, Pos::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    Value = ByteCode[Pos0];
+    Pos = Pos0 + 1;
+").
+
+read_short(ByteCode, Value, !Pos) :-
+    ByteCode = bytecode(Bytes, Size),
+    !.Pos + 2 =< Size,
+    read_short_2(Bytes, Value, !Pos).
+
+:- pred read_short_2(bytecode_bytes::in, int::out, int::in, int::out) is det.
+
+:- pragma foreign_proc("C",
+    read_short_2(ByteCode::in, Value::out, Pos0::in, Pos::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    Value = (ByteCode[Pos0] << 8) + ByteCode[Pos0+1];
+    Pos = Pos0 + 2;
+").
+
+read_int32(ByteCode, Value, !Pos) :-
+    ByteCode = bytecode(Bytes, Size),
+    !.Pos + 4 =< Size,
+    read_int32_2(Bytes, Value, !Pos).
+
+:- pred read_int32_2(bytecode_bytes::in, int::out, int::in, int::out) is det.
+
+:- pragma foreign_proc("C",
+    read_int32_2(ByteCode::in, Value::out, Pos0::in, Pos::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    Value = (ByteCode[Pos0] << 24) + (ByteCode[Pos0+1] << 16) +
+        (ByteCode[Pos0+2] << 8) + ByteCode[Pos0+3];
+    Pos = Pos0 + 4;
+").
+
+read_num(ByteCode, Num, !Pos) :-
+    read_num_2(ByteCode, 0, Num, !Pos).
+
+:- pred read_num_2(bytecode::in, int::in, int::out, int::in, int::out)
+    is semidet.
+
+read_num_2(ByteCode, Num0, Num, !Pos) :-
+    read_byte(ByteCode, Byte, !Pos),
+    Num1 = (Num0 << 7) \/ (Byte /\ 0x7F),
+    ( Byte /\ 0x80 \= 0 ->
+        read_num_2(ByteCode, Num1, Num, !Pos)
+    ;
+        Num = Num1
+    ).
+
+read_string_via_offset(ByteCode, StringTable, String, !Pos) :-
+    read_int32(ByteCode, Offset, !Pos),
+    String = lookup_string_table(StringTable, Offset).
+
+read_line(ByteCode, Line, !Pos) :-
+    read_line_2(ByteCode, [], RevChars, !Pos),
+    string.from_rev_char_list(RevChars, Line).
+
+:- pred read_line_2(bytecode::in, list(char)::in, list(char)::out,
+    int::in, int::out) is semidet.
+
+read_line_2(ByteCode, !RevChars, !Pos) :-
+    read_byte(ByteCode, Byte, !Pos),
+    char.from_int(Byte, Char),
+    ( Char = '\n' ->
+        !:RevChars = [Char | !.RevChars]
+    ;
+        !:RevChars = [Char | !.RevChars],
+        read_line_2(ByteCode, !RevChars, !Pos)
+    ).
+
+read_len_string(ByteCode, String, !Pos) :-
+    read_num(ByteCode, Length, !Pos),
+    read_len_string_2(ByteCode, Length, [], RevChars, !Pos),
+    string.from_rev_char_list(RevChars, String).
+
+:- pred read_len_string_2(bytecode::in, int::in,
+    list(char)::in, list(char)::out, int::in, int::out) is semidet.
+
+read_len_string_2(ByteCode, N, !RevChars, !Pos) :-
+    ( N =< 0 ->
+        true
+    ;
+        read_byte(ByteCode, Byte, !Pos),
+        char.from_int(Byte, Char),
+        !:RevChars = [Char | !.RevChars],
+        read_len_string_2(ByteCode, N - 1, !RevChars, !Pos)
+    ).
+
+read_string_table(ByteCode, StringTable, !Pos) :-
+    read_num(ByteCode, Size, !Pos),
+    ByteCode = bytecode(Bytes, NumBytes),
+    !.Pos + Size =< NumBytes,
+    bytecode_string_table_2(Bytes, !.Pos, Size, StringTableChars),
+    !:Pos = !.Pos + Size,
+    StringTable = string_table(StringTableChars, Size).
+
+:- pred bytecode_string_table_2(bytecode_bytes::in, Offset::in, Size::in,
+    string_table_chars::out) is det.
+
+:- pragma foreign_proc("C",
+    bytecode_string_table_2(Bytes::in, Offset::in, Size::in,
+        StringTableChars::out),
+    [will_not_call_mercury, thread_safe, promise_pure],
+"
+    char    *buf;
+    char    *table;
+    int     i;
+
+    MR_allocate_aligned_string_msg(buf, Size, MR_PROC_LABEL);
+    table = ((char *) Bytes) + Offset;
+    for (i = 0; i < Size; i++) {
+        buf[i] = table[i];
+    }
+
+    StringTableChars = (MR_ConstString) buf;
+").
+
 %-----------------------------------------------------------------------------%
 :- end_module mdbcomp.rtti_access.
 %-----------------------------------------------------------------------------%
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
Index: runtime/mercury_builtin_types.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_builtin_types.c,v
retrieving revision 1.21
diff -u -b -r1.21 mercury_builtin_types.c
--- runtime/mercury_builtin_types.c	16 Feb 2007 02:32:31 -0000	1.21
+++ runtime/mercury_builtin_types.c	4 Sep 2007 14:41:38 -0000
@@ -834,11 +834,11 @@
 
     #define MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, m, n, a)                   \
       do {                                                                  \
-          MR_write_out_uci_proc_static(fp,                                  \
+          MR_write_out_uci_proc_static(fp, NULL,                            \
             &MR_proc_layout_uci_name(m, __Unify__, n, a, 0));               \
-          MR_write_out_uci_proc_static(fp,                                  \
+          MR_write_out_uci_proc_static(fp, NULL,                            \
             &MR_proc_layout_uci_name(m, __Compare__, n, a, 0));             \
-          MR_write_out_uci_proc_static(fp,                                  \
+          MR_write_out_uci_proc_static(fp, NULL,                            \
             &MR_proc_layout_uci_name(m, __CompareRep__, n, a, 0));          \
       } while (0)
 
@@ -1591,7 +1591,8 @@
 void mercury_sys_init_mercury_builtin_types_init(void);
 void mercury_sys_init_mercury_builtin_types_init_type_tables(void);
 #ifdef  MR_DEEP_PROFILING
-void mercury_sys_init_mercury_builtin_types_write_out_proc_statics(FILE *fp);
+void mercury_sys_init_mercury_builtin_types_write_out_proc_statics(
+    FILE *deep_fp, FILE *procrep_fp);
 #endif
 
 void
@@ -1696,37 +1697,41 @@
 
 #ifdef  MR_DEEP_PROFILING
 void
-mercury_sys_init_mercury_builtin_types_write_out_proc_statics(FILE *fp)
+mercury_sys_init_mercury_builtin_types_write_out_proc_statics(FILE *deep_fp,
+    FILE *procrep_fp)
 {
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, int, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, string, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, float, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, character, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, void, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, c_pointer, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, pred, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, func, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, tuple, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, succip, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, hp, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, curfr, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, maxfr, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, redofr, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, redoip, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, trailptr, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, ticket, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin, heap_pointer, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin, ref, 1);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin, type_ctor_info, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin, type_info, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin,
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, int, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, string, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, float, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, character, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, void, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, c_pointer, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, pred, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, func, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, tuple, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, succip, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, hp, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, curfr, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, maxfr, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, redofr, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, redoip, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, trailptr, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, ticket, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin,
+        heap_pointer, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin, ref, 1);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin,
+        type_ctor_info, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin, type_info, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin,
         base_typeclass_info, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, private_builtin, typeclass_info, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, type_desc, type_ctor_desc, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, type_desc, pseudo_type_desc, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, type_desc, type_desc, 0);
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, user_by_rtti, 0); 
-    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(fp, builtin, dummy, 0); 
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, private_builtin,
+        typeclass_info, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, type_desc, type_ctor_desc, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, type_desc, pseudo_type_desc, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, type_desc, type_desc, 0);
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, user_by_rtti, 0); 
+    MR_WRITE_OUT_PROC_STATIC_LAYOUTS(deep_fp, builtin, dummy, 0); 
 }
 #endif /* MR_DEEP_PROFILING */
 
Index: runtime/mercury_deep_profiling.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_deep_profiling.c,v
retrieving revision 1.26
diff -u -b -r1.26 mercury_deep_profiling.c
--- runtime/mercury_deep_profiling.c	29 Nov 2006 05:18:20 -0000	1.26
+++ runtime/mercury_deep_profiling.c	10 Sep 2007 08:51:31 -0000
@@ -39,7 +39,7 @@
 
 MR_CallSiteStatic   MR_main_parent_call_site_statics[1] =
 {
-    { MR_callback, NULL, NULL, "Mercury runtime", 0, "" }
+    { MR_callsite_callback, NULL, NULL, "Mercury runtime", 0, "" }
 };
 
 MR_ProcStatic   MR_main_parent_proc_static =
@@ -256,10 +256,11 @@
 ** Functions for writing out the data at the end of the execution.
 */
 
-static  void    MR_deep_data_output_error(const char *msg);
+static  void    MR_deep_data_output_error(const char *msg, const char *file);
 static  void    MR_write_out_profiling_tree_check_unwritten(FILE *check_fp);
 
-static  void    MR_write_out_id_string(FILE *fp);
+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_call_site_static(FILE *fp,
                     const MR_CallSiteStatic *css);
@@ -287,7 +288,7 @@
 
 static  void    MR_write_csd_ptr(FILE *fp, const MR_CallSiteDynamic *csd);
 static  void    MR_write_ptr(FILE *fp, MR_NodeKind kind, const int node_id);
-static  void    MR_write_kind(FILE *fp, MR_CallSite_Kind kind);
+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);
@@ -365,7 +366,8 @@
 static  FILE        *debug_fp;
 #endif
 
-#define MR_MDPROF_DATAFILENAME  "Deep.data"
+#define MR_MDPROF_DATA_FILENAME     "Deep.data"
+#define MR_MDPROF_PROCREP_FILENAME  "Deep.procrep"
 
 void
 MR_write_out_profiling_tree(void)
@@ -374,15 +376,25 @@
     MR_ProfilingHashNode    *n;
     MR_ProcId               *pid;
     int                     root_pd_id;
-    FILE                    *fp;
+    FILE                    *deep_fp;
+    FILE                    *procrep_fp;
+    FILE                    *check_fp;
     int                     ticks_per_sec;
     unsigned                num_call_seqs;
-    FILE                    *check_fp;
 
-    fp = fopen(MR_MDPROF_DATAFILENAME, "wb+");
-    if (fp == NULL) {
+    deep_fp = fopen(MR_MDPROF_DATA_FILENAME, "wb+");
+    if (deep_fp == NULL) {
+        MR_fatal_error("cannot open `%s' for writing: %s",
+            MR_MDPROF_DATA_FILENAME, strerror(errno));
+    }
+
+    procrep_fp = NULL;
+    if (MR_output_deep_procrep_file) {
+        procrep_fp = fopen(MR_MDPROF_PROCREP_FILENAME, "wb+");
+        if (procrep_fp == NULL) {
         MR_fatal_error("cannot open `%s' for writing: %s",
-            MR_MDPROF_DATAFILENAME, strerror(errno));
+                MR_MDPROF_PROCREP_FILENAME, strerror(errno));
+        }
     }
 
 #ifdef  MR_DEEP_PROFILING_DEBUG
@@ -395,11 +407,15 @@
 #endif
 
     /* We overwrite these zeros (and the id string) after the seek below. */
-    MR_write_out_id_string(fp);
-    MR_write_fixed_size_int(fp, 0);
-    MR_write_fixed_size_int(fp, 0);
-    MR_write_fixed_size_int(fp, 0);
-    MR_write_fixed_size_int(fp, 0);
+    MR_write_out_deep_id_string(deep_fp);
+    MR_write_fixed_size_int(deep_fp, 0);
+    MR_write_fixed_size_int(deep_fp, 0);
+    MR_write_fixed_size_int(deep_fp, 0);
+    MR_write_fixed_size_int(deep_fp, 0);
+
+    if (procrep_fp != NULL) {
+        MR_write_out_procrep_id_string(procrep_fp);
+    }
 
 #ifdef  MR_CLOCK_TICKS_PER_SECOND
     ticks_per_sec = MR_CLOCK_TICKS_PER_SECOND;
@@ -412,12 +428,12 @@
     num_call_seqs = 0;
 #endif
 
-    MR_write_num(fp, ticks_per_sec);
-    MR_write_num(fp, MR_quanta_inside_deep_profiling_code);
-    MR_write_num(fp, MR_quanta_outside_deep_profiling_code);
-    MR_write_num(fp, num_call_seqs);
-    MR_write_byte(fp, sizeof(MR_Word));
-    MR_write_byte(fp, 0); /* the canonical flag is MR_FALSE = 0 */
+    MR_write_num(deep_fp, ticks_per_sec);
+    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);
@@ -437,27 +453,36 @@
     }
 #endif
 
-    MR_write_ptr(fp, kind_pd, root_pd_id);
+    MR_write_ptr(deep_fp, kind_pd, root_pd_id);
 
-    MR_write_out_proc_dynamic(fp, &MR_main_parent_proc_dynamic);
+    MR_write_out_proc_dynamic(deep_fp, &MR_main_parent_proc_dynamic);
 
-    MR_write_out_user_proc_static(fp, &MR_main_parent_proc_layout);
+    MR_write_out_user_proc_static(deep_fp, NULL, &MR_main_parent_proc_layout);
     MR_deep_assert(NULL, NULL, NULL,
         MR_address_of_write_out_proc_statics != NULL);
-    (*MR_address_of_write_out_proc_statics)(fp);
+    (*MR_address_of_write_out_proc_statics)(deep_fp, procrep_fp);
 
-    if (fseek(fp, 0L, SEEK_SET) != 0) {
-        MR_deep_data_output_error("cannot seek to start of");
+    if (fseek(deep_fp, 0L, SEEK_SET) != 0) {
+        MR_deep_data_output_error("cannot seek to start of",
+            MR_MDPROF_DATA_FILENAME);
     }
 
-    MR_write_out_id_string(fp);
-    MR_write_fixed_size_int(fp, MR_call_site_dynamic_table->last_id);
-    MR_write_fixed_size_int(fp, MR_call_site_static_table->last_id);
-    MR_write_fixed_size_int(fp, MR_proc_dynamic_table->last_id);
-    MR_write_fixed_size_int(fp, MR_proc_layout_table->last_id);
+    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);
+    MR_write_fixed_size_int(deep_fp, MR_proc_layout_table->last_id);
+
+    if (fclose(deep_fp) != 0) {
+        MR_deep_data_output_error("cannot close", MR_MDPROF_DATA_FILENAME);
+    }
 
-    if (fclose(fp) != 0) {
-        MR_deep_data_output_error("cannot close");
+    if (procrep_fp != NULL) {
+        putc(MR_no_more_modules, procrep_fp);
+        if (fclose(procrep_fp) != 0) {
+            MR_deep_data_output_error("cannot close",
+                MR_MDPROF_PROCREP_FILENAME);
+        }
     }
 
 #ifdef MR_DEEP_PROFILING_STATISTICS
@@ -630,44 +655,64 @@
 }
 
 static void
-MR_deep_data_output_error(const char *op)
+MR_deep_data_output_error(const char *op, const char *filename)
 {
-    MR_warning("%s %s: %s", op, MR_MDPROF_DATAFILENAME, strerror(errno));
+    MR_warning("%s %s: %s", op, filename, strerror(errno));
 
     /*
-    ** An incomplete profiling data file is useless. Removing it
-    ** prevents misunderstandings about that, and may also cure a
-    ** disk-full condition, if the close failure was caused by
-    ** that.
+    ** An incomplete profiling data file is useless. Removing it prevents
+    ** misunderstandings about that, and may also cure a disk-full condition,
+    ** if the close failure was caused by that.
     */
 
-    if (remove(MR_MDPROF_DATAFILENAME) != 0) {
+    if (remove(MR_MDPROF_DATA_FILENAME) != 0) {
+        MR_warning("cannot remove %s: %s",
+            MR_MDPROF_DATA_FILENAME, strerror(errno));
+    }
+
+    if (remove(MR_MDPROF_PROCREP_FILENAME) != 0) {
         MR_warning("cannot remove %s: %s",
-            MR_MDPROF_DATAFILENAME, strerror(errno));
+            MR_MDPROF_PROCREP_FILENAME, strerror(errno));
     }
 
     exit(1);
 }
 
 static void
-MR_write_out_id_string(FILE *fp)
+MR_write_out_deep_id_string(FILE *fp)
 {
-    /* Must be the same as id_string in deep_profiler/read_profile.m */
-    const char  *id_string = "Mercury deep profiler data version 3\n";
+    /* Must be the same as deep_id_string in deep_profiler/read_profile.m */
+    const char  *id_string = "Mercury deep profiler data version 4\n";
+
+    fputs(id_string, fp);
+}
+
+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";
 
     fputs(id_string, fp);
 }
 
 void
-MR_write_out_user_proc_static(FILE *fp, const MR_ProcLayoutUser *proc_layout)
+MR_write_out_user_proc_static(FILE *deep_fp, FILE *procrep_fp,
+    const MR_ProcLayoutUser *proc_layout)
 {
-    MR_write_out_proc_static(fp, (const MR_ProcLayout *) proc_layout);
+    MR_write_out_proc_static(deep_fp, procrep_fp,
+        (const MR_ProcLayout *) proc_layout);
 }
 
 void
-MR_write_out_uci_proc_static(FILE *fp, const MR_ProcLayoutUCI *proc_layout)
+MR_write_out_uci_proc_static(FILE *deep_fp, FILE *procrep_fp,
+    const MR_ProcLayoutUCI *proc_layout)
 {
-    MR_write_out_proc_static(fp, (const MR_ProcLayout *) proc_layout);
+    MR_write_out_proc_static(deep_fp, procrep_fp,
+        (const MR_ProcLayout *) proc_layout);
 }
 
 #ifdef  MR_DEEP_PROFILING_LOG
@@ -683,7 +728,32 @@
 #endif  /* MR_DEEP_PROFILING_LOG */
 
 void
-MR_write_out_proc_static(FILE *fp, const MR_ProcLayout *proc_layout)
+MR_write_out_module_proc_reps_start(FILE *procrep_fp,
+    const MR_ModuleCommonLayout *module_common)
+{
+    if (procrep_fp != NULL) {
+        int         i;
+
+        putc(MR_next_module, procrep_fp);
+        MR_write_string(procrep_fp, module_common->MR_mlc_name);
+        MR_write_num(procrep_fp, module_common->MR_mlc_string_table_size);
+        for (i = 0; i < module_common->MR_mlc_string_table_size; i++) {
+            putc(module_common->MR_mlc_string_table[i], procrep_fp);
+        }
+    }
+}
+
+void
+MR_write_out_module_proc_reps_end(FILE *procrep_fp)
+{
+    if (procrep_fp != NULL) {
+        putc(MR_no_more_procs, procrep_fp);
+    }
+}
+
+void
+MR_write_out_proc_static(FILE *deep_fp, FILE *procrep_fp,
+    const MR_ProcLayout *proc_layout)
 {
     const MR_ProcStatic *ps;
     const MR_ProcId     *procid;
@@ -706,7 +776,7 @@
     if (MR_deep_prof_doing_logging) {
         procid = &proc_layout->MR_sle_proc_id;
         if (MR_PROC_ID_IS_UCI(*procid)) {
-            fprintf(fp,
+            fprintf(deep_fp,
                 "proc_static_uci(%ld,\"%s\",\"%s\",\"%s\",\"%s\",%d,%d,[",
                 (long) proc_layout->MR_sle_proc_static,
                 procid->MR_proc_uci.MR_uci_type_name,
@@ -716,7 +786,7 @@
                 procid->MR_proc_uci.MR_uci_type_arity,
                 procid->MR_proc_uci.MR_uci_mode);
         } else {
-            fprintf(fp,
+            fprintf(deep_fp,
                 "proc_static_user(%ld,%s,\"%s\",\"%s\",\"%s\",%d,%d,[",
                 (long) proc_layout->MR_sle_proc_static,
                 procid->MR_proc_user.MR_user_pred_or_func == MR_PREDICATE ?
@@ -730,47 +800,47 @@
 
         for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
             if (i == 0) {
-                fputs("\n\t", fp);
+                fputs("\n\t", deep_fp);
             } else {
-                fputs(",\n\t", fp);
+                fputs(",\n\t", deep_fp);
             }
 
             switch (ps->MR_ps_call_sites[i].MR_css_kind) {
                 case MR_normal_call:
-                    fprintf(fp, "css_normal(%ld, %ld)",
+                    fprintf(deep_fp, "css_normal(%ld, %ld)",
                         (long) &ps->MR_ps_call_sites[i],
                         (long) &ps->MR_ps_call_sites[i].
                             MR_css_callee_ptr_if_known->MR_sle_proc_static);
                     break;
 
                 case MR_special_call:
-                    fprintf(fp, "css_special(%ld)",
+                    fprintf(deep_fp, "css_special(%ld)",
                         (long) &ps->MR_ps_call_sites[i]);
                     break;
 
                 case MR_higher_order_call:
-                    fprintf(fp, "css_higher_order(%ld)",
+                    fprintf(deep_fp, "css_higher_order(%ld)",
                         (long) &ps->MR_ps_call_sites[i]);
                     break;
 
                 case MR_method_call:
-                    fprintf(fp, "css_method(%ld)",
+                    fprintf(deep_fp, "css_method(%ld)",
                         (long) &ps->MR_ps_call_sites[i]);
                     break;
 
                 case MR_callback:
-                    fprintf(fp, "css_callback(%ld)",
+                    fprintf(deep_fp, "css_callback(%ld)",
                         (long) &ps->MR_ps_call_sites[i]);
                     break;
 
                 default:
-                    fprintf(fp, "css_unknown(%ld)",
+                    fprintf(deep_fp, "css_unknown(%ld)",
                         (long) &ps->MR_ps_call_sites[i]);
                     break;
             }
         }
 
-        fprintf(fp, "]).\n");
+        fprintf(deep_fp, "]).\n");
         return;
     }
 #endif
@@ -817,10 +887,82 @@
 
     MR_flag_written_proc_layout(proc_layout);
 
-    MR_write_byte(fp, MR_deep_token_proc_static);
-    MR_write_ptr(fp, kind_ps, ps_id);
+    MR_write_byte(deep_fp, MR_deep_item_proc_static);
+    MR_write_ptr(deep_fp, kind_ps, ps_id);
 
     procid = &proc_layout->MR_sle_proc_id;
+    MR_write_out_str_proc_label(deep_fp, procid);
+
+    MR_write_string(deep_fp, ps->MR_ps_file_name);
+    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);
+
+    for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
+        (void) MR_insert_call_site_static(&ps->MR_ps_call_sites[i], &css_id,
+            NULL, MR_FALSE);
+
+#ifdef MR_DEEP_PROFILING_DEBUG
+        if (debug_fp != NULL) {
+            fprintf(debug_fp,
+                "call site id %d in proc_static %p/%p/%d -> %d\n",
+                i, proc_layout, ps, ps_id, css_id);
+        }
+#endif
+
+        MR_write_ptr(deep_fp, kind_css, css_id);
+    }
+
+    for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
+#ifdef MR_DEEP_PROFILING_DEBUG
+        if (debug_fp != NULL) {
+            fprintf(debug_fp, "in proc_static %p/%p/%d, call site %d\n",
+                proc_layout, ps, ps_id, i);
+        }
+#endif
+
+        MR_write_out_call_site_static(deep_fp, &ps->MR_ps_call_sites[i]);
+    }
+
+    if (procrep_fp != NULL) {
+        const MR_uint_least8_t  *bytecode;
+
+        /*
+        ** Some predicates in the Mercury standard library, such as
+        ** exception.builtin_catch, have Mercury declarations but no Mercury
+        ** implementation (even as foreign_proc code). We do still generate
+        ** proc_static structures for them (since we *want* the hand-written
+        ** C code to be able to collect deep profiling data (in this case,
+        ** to count the number of executions of the EXCP port). This means that
+        ** (a) they will have proc_layout structures, and (b) the bytecode
+        ** pointer field in these structures will be NULL.
+        **
+        ** We handle such procedures by simply not including them in the
+        ** module representation. This is fine, as long as any code that reads
+        ** and processes the program representation is aware that the bodies
+        ** of procedures defined outside Mercury may be missing.
+        */
+
+        bytecode = proc_layout->MR_sle_body_bytes;
+        if (bytecode != NULL) {
+            int size;
+            int bytenum;
+
+            putc(MR_next_proc, procrep_fp);
+            MR_write_out_str_proc_label(procrep_fp, procid);
+
+            size = (bytecode[0] << 24) + (bytecode[1] << 16) +
+                (bytecode[2] << 8) + bytecode[3];
+            for (bytenum = 0; bytenum < size; bytenum++) {
+                putc(bytecode[bytenum], procrep_fp);
+            }
+        }
+    }
+}
+
+void
+MR_write_out_str_proc_label(FILE *deep_fp, const MR_ProcId *procid)
+{
     if (MR_PROC_ID_IS_UCI(*procid)) {
 #ifdef MR_DEEP_PROFILING_DEBUG
         if (debug_fp != NULL) {
@@ -834,13 +976,13 @@
         }
 #endif
 
-        MR_write_byte(fp, MR_deep_token_isa_uci_pred);
-        MR_write_string(fp, procid->MR_proc_uci.MR_uci_type_name);
-        MR_write_string(fp, procid->MR_proc_uci.MR_uci_type_module);
-        MR_write_string(fp, procid->MR_proc_uci.MR_uci_def_module);
-        MR_write_string(fp, procid->MR_proc_uci.MR_uci_pred_name);
-        MR_write_num(fp, procid->MR_proc_uci.MR_uci_type_arity);
-        MR_write_num(fp, procid->MR_proc_uci.MR_uci_mode);
+        MR_write_byte(deep_fp, MR_proclabel_special);
+        MR_write_string(deep_fp, procid->MR_proc_uci.MR_uci_type_name);
+        MR_write_string(deep_fp, procid->MR_proc_uci.MR_uci_type_module);
+        MR_write_string(deep_fp, procid->MR_proc_uci.MR_uci_def_module);
+        MR_write_string(deep_fp, procid->MR_proc_uci.MR_uci_pred_name);
+        MR_write_num(deep_fp, procid->MR_proc_uci.MR_uci_type_arity);
+        MR_write_num(deep_fp, procid->MR_proc_uci.MR_uci_mode);
     } else {
 #ifdef MR_DEEP_PROFILING_DEBUG
         if (debug_fp != NULL) {
@@ -855,47 +997,16 @@
 #endif
 
         if (procid->MR_proc_user.MR_user_pred_or_func == MR_PREDICATE) {
-            MR_write_byte(fp, MR_deep_token_isa_predicate);
+            MR_write_byte(deep_fp, MR_proclabel_user_predicate);
         } else {
-            MR_write_byte(fp, MR_deep_token_isa_function);
-        }
-
-        MR_write_string(fp, procid->MR_proc_user.MR_user_decl_module);
-        MR_write_string(fp, procid->MR_proc_user.MR_user_def_module);
-        MR_write_string(fp, procid->MR_proc_user.MR_user_name);
-        MR_write_num(fp, procid->MR_proc_user.MR_user_arity);
-        MR_write_num(fp, procid->MR_proc_user.MR_user_mode);
-    }
-
-    MR_write_string(fp, ps->MR_ps_file_name);
-    MR_write_num(fp, ps->MR_ps_line_number);
-    MR_write_byte(fp, ps->MR_ps_is_in_interface);
-    MR_write_num(fp, ps->MR_ps_num_call_sites);
-
-    for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
-        (void) MR_insert_call_site_static(&ps->MR_ps_call_sites[i], &css_id,
-            NULL, MR_FALSE);
-
-#ifdef MR_DEEP_PROFILING_DEBUG
-        if (debug_fp != NULL) {
-            fprintf(debug_fp,
-                "call site id %d in proc_static %p/%p/%d -> %d\n",
-                i, proc_layout, ps, ps_id, css_id);
-        }
-#endif
-
-        MR_write_ptr(fp, kind_css, css_id);
-    }
-
-    for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
-#ifdef MR_DEEP_PROFILING_DEBUG
-        if (debug_fp != NULL) {
-            fprintf(debug_fp, "in proc_static %p/%p/%d, call site %d\n",
-                proc_layout, ps, ps_id, i);
+            MR_write_byte(deep_fp, MR_proclabel_user_function);
         }
-#endif
 
-        MR_write_out_call_site_static(fp, &ps->MR_ps_call_sites[i]);
+        MR_write_string(deep_fp, procid->MR_proc_user.MR_user_decl_module);
+        MR_write_string(deep_fp, procid->MR_proc_user.MR_user_def_module);
+        MR_write_string(deep_fp, procid->MR_proc_user.MR_user_name);
+        MR_write_num(deep_fp, procid->MR_proc_user.MR_user_arity);
+        MR_write_num(deep_fp, procid->MR_proc_user.MR_user_mode);
     }
 }
 
@@ -929,10 +1040,10 @@
     }
 #endif
 
-    MR_write_byte(fp, MR_deep_token_call_site_static);
+    MR_write_byte(fp, MR_deep_item_call_site_static);
     MR_write_ptr(fp, kind_css, css_id);
     MR_write_kind(fp, css->MR_css_kind);
-    if (css->MR_css_kind == MR_normal_call) {
+    if (css->MR_css_kind == MR_callsite_normal_call) {
         (void) MR_insert_proc_layout(css->MR_css_callee_ptr_if_known, &ps_id,
             NULL, MR_FALSE);
 #ifdef MR_DEEP_PROFILING_DEBUG
@@ -977,7 +1088,7 @@
     }
 #endif
 
-    MR_write_byte(fp, MR_deep_token_call_site_dynamic);
+    MR_write_byte(fp, MR_deep_item_call_site_dynamic);
     if (! MR_insert_call_site_dynamic(csd, &csd_id, NULL, MR_FALSE)) {
         MR_fatal_error("MR_write_out_call_site_dynamic: insert succeeded");
     }
@@ -1121,7 +1232,7 @@
     MR_deep_num_pd_array_slots += ps->MR_ps_num_call_sites;
 #endif
 
-    MR_write_byte(fp, MR_deep_token_proc_dynamic);
+    MR_write_byte(fp, MR_deep_item_proc_dynamic);
     MR_write_ptr(fp, kind_pd, pd_id);
     MR_write_ptr(fp, kind_ps, ps_id);
     MR_write_num(fp, ps->MR_ps_num_call_sites);
@@ -1137,7 +1248,7 @@
         MR_write_kind(fp, ps->MR_ps_call_sites[i].MR_css_kind);
         switch (ps->MR_ps_call_sites[i].MR_css_kind)
         {
-            case MR_normal_call:
+            case MR_callsite_normal_call:
 #ifdef MR_DEEP_PROFILING_DEBUG
                 if (debug_fp != NULL) {
                     fprintf(debug_fp,
@@ -1148,10 +1259,10 @@
                 MR_write_csd_ptr(fp, pd->MR_pd_call_site_ptr_ptrs[i]);
                 break;
 
-            case MR_special_call:
-            case MR_higher_order_call:
-            case MR_method_call:
-            case MR_callback:
+            case MR_callsite_special_call:
+            case MR_callsite_higher_order_call:
+            case MR_callsite_method_call:
+            case MR_callsite_callback:
                 MR_write_out_ho_call_site_ptrs(fp, pd,
                     (MR_CallSiteDynList *) pd->MR_pd_call_site_ptr_ptrs[i]);
                 break;
@@ -1161,15 +1272,15 @@
     for (i = 0; i < ps->MR_ps_num_call_sites; i++) {
         switch (ps->MR_ps_call_sites[i].MR_css_kind)
         {
-            case MR_normal_call:
+            case MR_callsite_normal_call:
                 MR_write_out_call_site_dynamic(fp,
                     pd->MR_pd_call_site_ptr_ptrs[i]);
                 break;
 
-            case MR_special_call:
-            case MR_higher_order_call:
-            case MR_method_call:
-            case MR_callback:
+            case MR_callsite_special_call:
+            case MR_callsite_higher_order_call:
+            case MR_callsite_method_call:
+            case MR_callsite_callback:
                 MR_write_out_ho_call_site_nodes(fp,
                     (MR_CallSiteDynList *) pd->MR_pd_call_site_ptr_ptrs[i]);
                 break;
@@ -1194,7 +1305,7 @@
         MR_write_csd_ptr(fp, dynlist->MR_csdlist_call_site);
         dynlist = dynlist->MR_csdlist_next;
     }
-    MR_write_byte(fp, MR_deep_token_end);
+    MR_write_byte(fp, MR_deep_item_end);
 }
 
 static void
@@ -1234,7 +1345,7 @@
 }
 
 static void
-MR_write_kind(FILE *fp, MR_CallSite_Kind kind)
+MR_write_kind(FILE *fp, MR_CallSiteKind kind)
 {
     int byte;
 
@@ -1244,14 +1355,7 @@
     }
 #endif
 
-    /* convert from a MR_CallSite_Kind to an MR_Profiling_Encoding_Token */
-    byte = (int) kind +
-        ((int) MR_deep_token_normal_call - (int) MR_normal_call);
-    if (byte < MR_deep_token_normal_call || byte > MR_deep_token_callback) {
-        MR_fatal_error("MR_write_kind: bad kind %d %d\n", (int) kind, byte);
-    }
-
-    MR_write_byte(fp, byte);
+    MR_write_byte(fp, (const char) kind);
 }
 
 static void
Index: runtime/mercury_deep_profiling.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_deep_profiling.h,v
retrieving revision 1.17
diff -u -b -r1.17 mercury_deep_profiling.h
--- runtime/mercury_deep_profiling.h	29 Nov 2006 05:18:21 -0000	1.17
+++ runtime/mercury_deep_profiling.h	10 Sep 2007 05:17:20 -0000
@@ -19,12 +19,12 @@
 #include <stdio.h>
 
 typedef enum {
-	MR_normal_call,
-	MR_special_call,
-	MR_higher_order_call,
-	MR_method_call,
-	MR_callback
-} MR_CallSite_Kind;
+	MR_callsite_normal_call,
+	MR_callsite_special_call,
+	MR_callsite_higher_order_call,
+	MR_callsite_method_call,
+	MR_callsite_callback
+} MR_CallSiteKind;
 
 struct MR_ProfilingMetrics_Struct {
 #ifdef MR_DEEP_PROFILING_PORT_COUNTS
@@ -56,7 +56,7 @@
 };
 
 struct MR_CallSiteStatic_Struct {
-    	MR_CallSite_Kind			MR_css_kind;
+    	MR_CallSiteKind				MR_css_kind;
 	MR_ProcLayout				*MR_css_callee_ptr_if_known;
 	MR_ConstString				MR_css_type_subst_if_known;
 	MR_ConstString				MR_css_file_name;
@@ -97,20 +97,28 @@
 };
 
 typedef enum {
-	MR_deep_token_end = 0,
-	MR_deep_token_call_site_static,
-	MR_deep_token_call_site_dynamic,
-	MR_deep_token_proc_static,
-	MR_deep_token_proc_dynamic,
-	MR_deep_token_normal_call,
-	MR_deep_token_special_call,
-	MR_deep_token_higher_order_call,
-	MR_deep_token_method_call,
-	MR_deep_token_callback,
-	MR_deep_token_isa_predicate,
-	MR_deep_token_isa_function,
-	MR_deep_token_isa_uci_pred
-} MR_Profile_Encoding_Token;
+	MR_deep_item_end = 0,
+	MR_deep_item_call_site_static,
+	MR_deep_item_call_site_dynamic,
+	MR_deep_item_proc_static,
+	MR_deep_item_proc_dynamic
+} MR_DeepProfNextItem;
+
+typedef enum {
+	MR_no_more_modules,
+	MR_next_module
+} MR_MoreModules;
+
+typedef enum {
+	MR_no_more_procs,
+	MR_next_proc
+} MR_MoreProcs;
+
+typedef enum {
+	MR_proclabel_user_predicate,
+	MR_proclabel_user_function,
+	MR_proclabel_special
+} MR_ProcLabelToken;
 
 #define	MR_enter_instrumentation()					\
 	do { MR_inside_deep_profiling_code = MR_TRUE; } while (0)
@@ -363,11 +371,18 @@
 			const char *cond, const char *filename,
 			int linenumber);
 extern	void	MR_setup_callback(void *entry);
-extern	void	MR_write_out_user_proc_static(FILE *fp,
-			const MR_ProcLayoutUser *ptr);
-extern	void	MR_write_out_uci_proc_static(FILE *fp,
-			const MR_ProcLayoutUCI *ptr);
-extern	void	MR_write_out_proc_static(FILE *fp, const MR_ProcLayout *ptr);
+
+extern	void	MR_write_out_str_proc_label(FILE *deep_fp,
+			const MR_ProcId *procid);
+extern	void	MR_write_out_user_proc_static(FILE *deep_fp, FILE *procrep_fp,
+			const MR_ProcLayoutUser *proc_layout);
+extern	void	MR_write_out_uci_proc_static(FILE *deep_fp, FILE *procrep_fp,
+			const MR_ProcLayoutUCI *proc_layout);
+extern	void	MR_write_out_proc_static(FILE *deep_fp, FILE *procrep_fp,
+			const MR_ProcLayout *proc_layout);
+extern	void	MR_write_out_module_proc_reps_start(FILE *procrep_fp,
+			const MR_ModuleCommonLayout *module_common);
+extern	void	MR_write_out_module_proc_reps_end(FILE *procrep_fp);
 extern	void	MR_write_out_profiling_tree(void);
 
 extern	void	MR_deep_prof_init(void);
Index: runtime/mercury_deep_profiling_hand.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_deep_profiling_hand.h,v
retrieving revision 1.8
diff -u -b -r1.8 mercury_deep_profiling_hand.h
--- runtime/mercury_deep_profiling_hand.h	29 Nov 2006 05:18:21 -0000	1.8
+++ runtime/mercury_deep_profiling_hand.h	5 Sep 2007 15:52:21 -0000
@@ -100,7 +100,7 @@
 		cmodule, cname, carity, cmode, line)			\
 	static const MR_CallSiteStatic					\
 	MR_call_sites_uci_name(module, name, type, arity, mode)[] = {	\
-		{ MR_normal_call, (MR_ProcLayout *)			\
+		{ MR_callsite_normal_call, (MR_ProcLayout *)		\
 		&MR_proc_layout_user_name(cmodule, cname, carity, cmode),\
 		NULL, "", line, "" }					\
 	}
@@ -108,7 +108,7 @@
 #define	MR_call_sites_user_one_ho(module, name, arity, mode, line)	\
 	static const MR_CallSiteStatic					\
 	MR_call_sites_user_name(module, name, arity, mode)[] = {	\
-		{ MR_higher_order_call, NULL,				\
+		{ MR_callsite_higher_order_call, NULL,			\
 		NULL, "", line, "" }					\
 	}
 
Index: runtime/mercury_engine.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_engine.c,v
retrieving revision 1.58
diff -u -b -r1.58 mercury_engine.c
--- runtime/mercury_engine.c	4 Apr 2007 01:09:52 -0000	1.58
+++ runtime/mercury_engine.c	29 Aug 2007 05:21:02 -0000
@@ -73,6 +73,7 @@
     { "notnearest",     MR_NOT_NEAREST_FLAG },
     { "debugslots",     MR_DEBUG_SLOTS_FLAG },
     { "deepdebugfile",  MR_DEEP_PROF_DEBUG_FILE_FLAG },
+    { "deepprocrepfile",    MR_DEEP_PROF_PROCREP_FILE_FLAG },
     { "stackextend",    MR_STACK_EXTEND_FLAG },
     { "detail",         MR_DETAILFLAG }
 };
Index: runtime/mercury_engine.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_engine.h,v
retrieving revision 1.48
diff -u -b -r1.48 mercury_engine.h
--- runtime/mercury_engine.h	10 May 2007 05:24:16 -0000	1.48
+++ runtime/mercury_engine.h	29 Aug 2007 05:20:17 -0000
@@ -67,9 +67,10 @@
 #define MR_NOT_NEAREST_FLAG             19
 #define MR_DEBUG_SLOTS_FLAG             20
 #define MR_DEEP_PROF_DEBUG_FILE_FLAG    21
-#define MR_STACK_EXTEND_FLAG            22
-#define MR_DETAILFLAG                   23
-#define MR_MAXFLAG                      24
+#define MR_DEEP_PROF_PROCREP_FILE_FLAG  22
+#define MR_STACK_EXTEND_FLAG            23
+#define MR_DETAILFLAG                   24
+#define MR_MAXFLAG                      25
 /* MR_DETAILFLAG should be the last real flag */
 
 /*
@@ -139,6 +140,9 @@
 ** generating a Deep.data file, to also generate a human-readable Deep.debug
 ** file.
 **
+** MR_deep_prof_procrep_file_flag, if set, causes the runtime, whenever it is
+** generating a Deep.data file, to also generate a Deep.procrep file.
+**
 ** MR_stack_extend_debug controls whether the runtime prints diagnostics
 ** whenever it extends a stack.
 */
@@ -166,6 +170,8 @@
 #define MR_debug_slots_flag             MR_debugflag[MR_DEBUG_SLOTS_FLAG]
 #define MR_deep_prof_debug_file_flag    MR_debugflag[\
                                             MR_DEEP_PROF_DEBUG_FILE_FLAG]
+#define MR_deep_prof_procrep_file_flag    MR_debugflag[\
+                                            MR_DEEP_PROF_PROCREP_FILE_FLAG]
 #define MR_stack_extend_debug           MR_debugflag[MR_STACK_EXTEND_FLAG]
 #define MR_detaildebug                  MR_debugflag[MR_DETAILFLAG]
 
Index: runtime/mercury_grade.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_grade.h,v
retrieving revision 1.72
diff -u -b -r1.72 mercury_grade.h
--- runtime/mercury_grade.h	31 Jul 2007 07:58:44 -0000	1.72
+++ runtime/mercury_grade.h	4 Sep 2007 10:48:01 -0000
@@ -61,8 +61,8 @@
 */
 
 #define MR_GRADE_PART_0	v14_
-#define MR_GRADE_EXEC_TRACE_VERSION_NO	7
-#define MR_GRADE_DEEP_PROF_VERSION_NO	2
+#define MR_GRADE_EXEC_TRACE_VERSION_NO	8
+#define MR_GRADE_DEEP_PROF_VERSION_NO	3
 
 #ifdef MR_HIGHLEVEL_CODE
 
Index: runtime/mercury_stack_layout.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_layout.c,v
retrieving revision 1.2
diff -u -b -r1.2 mercury_stack_layout.c
--- runtime/mercury_stack_layout.c	29 Nov 2006 05:18:25 -0000	1.2
+++ runtime/mercury_stack_layout.c	4 Sep 2007 11:51:47 -0000
@@ -20,12 +20,14 @@
 MR_ConstString
 MR_hlds_var_name(const MR_ProcLayout *entry, int hlds_var_num)
 {
+    const MR_ModuleCommonLayout *module_common;
     const char  *string_table;
     MR_Integer  string_table_size;
     int         offset;
 
-    string_table = entry->MR_sle_module_layout->MR_ml_string_table;
-    string_table_size = entry->MR_sle_module_layout->MR_ml_string_table_size;
+    module_common = entry->MR_sle_module_common_layout;
+    string_table = module_common->MR_mlc_string_table;
+    string_table_size = module_common->MR_mlc_string_table_size;
 
     if (hlds_var_num == 0) {
         /* this value is not a variable */
Index: runtime/mercury_stack_layout.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.112
diff -u -b -r1.112 mercury_stack_layout.h
--- runtime/mercury_stack_layout.h	12 Jun 2007 06:06:33 -0000	1.112
+++ runtime/mercury_stack_layout.h	4 Sep 2007 11:49:50 -0000
@@ -842,10 +842,6 @@
 ** are where on entry, so it can reexecute the procedure if asked to do so
 ** and if the values of the required variables are still available.
 **
-** The module_layout field points to the module info structure of the module
-** containing the procedure. This allows the debugger access to the string table
-** stored there, as well the table associating source-file contexts with labels.
-**
 ** The labels field contains a pointer to an array of pointers to label layout
 ** structures; the size of the array is given by the num_labels field. The
 ** initial part of the array will contain a pointer to the label layout
@@ -998,19 +994,30 @@
 **   one for user-defined procedures and one for procedures of the compiler
 **   generated Unify, Index and Compare predicates.
 **
-** - The third group is the MR_ExecTrace and MR_ProcStatic structures, which
-**   contain information specifically intended for the debugger and the deep
-**   profiler respectively. The MR_ExecTrace structure will be generated
-**   only if the module is compiled with execution tracing, while the
-**   MR_ProcStatic structure will be generated only if the module is compiled
-**   in a deep profiling grade.
-**
-**   The body_bytes field also belongs to this group. If this is NULL, 
-**   it means that no representation of the procedure body is available.
-**   If non-NULL, it contains a pointer to an array of bytecodes that
-**   represents the body of the procedure. The bytecode array should be
-**   interpreted by read_proc_rep in browser/declarative_execution.m
-**   (it starts with an encoded form of the array's length).
+** - The third group is everything else. Currently, this consists of
+**   information that is of interest to the debugger, to the deep profiler,
+**   or both.
+**
+**   The information that is of interest to the debugger only is stored in
+**   the MR_ExecTrace structure, which will be generated only if the module
+**   is compiled with execution tracing. The information that is of interest to
+**   the deep profiler is stored in the MR_ProcStatic structure, which will be
+**   generated only if the module is compiled in a deep profiling grade. The
+**   other fields in the group are of interest to both the debugger and the
+**   deep profiler, and will be generated if either execution tracing or deep
+**   profiling is enabled.
+**
+**   If the body_bytes field is NULL, it means that no representation of the
+**   procedure body is available. If non-NULL, it contains a pointer to anz
+**   array of bytecodes that represents the body of the procedure. The
+**   bytecode array should be interpreted by the read_proc_rep predicate in
+**   browser/declarative_execution.m (it starts with an encoded form of the
+**   array's length).
+**
+**   The module_common_layout field points to the part of the module layout
+**   structure of the module containing the procedure that is common to the
+**   debugger and the deep profiler. Amongst other things, it gives access to
+**   the string table that the body_bytes fields refers to.
 **
 ** The runtime system considers all proc layout structures to be of type
 ** MR_ProcLayout, but must use the macros defined below to check for the
@@ -1024,9 +1031,10 @@
 ** If the options with which a module is compiled do not require execution
 ** tracing, then the MR_ExecTrace substructure will not present, and if the
 ** options do not require procedure identification, then the MR_ProcId
-** substructure will not be present either. The body_bytes field cannot be
-** non-NULL unless at least one of exec trace and proc static substructures
-** is present, but it is otherwise independent of those substructures.
+** substructure will not be present either. The body_bytes and module_layout
+** fields cannot be non-NULL unless at least one of exec trace and proc static
+** substructures is present, but they are otherwise independent of those
+** substructures.
 **
 ** The compiler itself generates proc layout structures using the following
 ** three types.
@@ -1045,6 +1053,7 @@
 	MR_STATIC_CODE_CONST MR_ExecTrace	*MR_sle_exec_trace;
 	MR_ProcStatic				*MR_sle_proc_static;
 	const MR_uint_least8_t			*MR_sle_body_bytes;
+	const MR_ModuleCommonLayout		*MR_sle_module_common_layout;
 };
 
 typedef	struct MR_ProcLayoutUser_Struct {
@@ -1053,6 +1062,7 @@
 	MR_STATIC_CODE_CONST MR_ExecTrace	*MR_sle_exec_trace;
 	MR_ProcStatic				*MR_sle_proc_static;
 	const MR_uint_least8_t			*MR_sle_body_bytes;
+	const MR_ModuleCommonLayout		*MR_sle_module_common_layout;
 } MR_ProcLayoutUser;
 
 typedef	struct MR_ProcLayoutUCI_Struct {
@@ -1061,6 +1071,7 @@
 	MR_STATIC_CODE_CONST MR_ExecTrace	*MR_sle_exec_trace;
 	MR_ProcStatic				*MR_sle_proc_static;
 	const MR_uint_least8_t			*MR_sle_body_bytes;
+	const MR_ModuleCommonLayout		*MR_sle_module_common_layout;
 } MR_ProcLayoutUCI;
 
 typedef	struct MR_ProcLayout_Traversal_Struct {
@@ -1072,8 +1083,17 @@
 		(MR_PROC_ID_EXISTS(entry->MR_sle_proc_id))
 
 #define	MR_PROC_LAYOUT_HAS_EXEC_TRACE(entry)			\
-		(MR_PROC_LAYOUT_HAS_PROC_ID(entry)		\
-		&& entry->MR_sle_exec_trace != NULL)
+		(MR_PROC_LAYOUT_HAS_PROC_ID(entry) &&		\
+		entry->MR_sle_exec_trace != NULL)
+
+#define	MR_PROC_LAYOUT_HAS_PROC_STATIC(entry)			\
+		(MR_PROC_LAYOUT_HAS_PROC_ID(entry) &&		\
+		entry->MR_sle_proc_static != NULL)
+
+#define	MR_PROC_LAYOUT_HAS_THIRD_GROUP(entry)			\
+		(MR_PROC_LAYOUT_HAS_PROC_ID(entry) &&		\
+		( entry->MR_sle_exec_trace != NULL		\
+		|| entry->MR_sle_proc_static != NULL))
 
 #define	MR_sle_code_addr	MR_sle_traversal.MR_trav_code_addr
 #define	MR_sle_succip_locn	MR_sle_traversal.MR_trav_succip_locn
@@ -1383,16 +1403,21 @@
 ** compiler/layout_out.m.
 */
 
-#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__SYNTH_ATTR
+#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__COMMON
 #define	MR_LAYOUT_VERSION__USER_DEFINED	1
 #define	MR_LAYOUT_VERSION__EVENTSETNAME	2
 #define	MR_LAYOUT_VERSION__SYNTH_ATTR	3
+#define	MR_LAYOUT_VERSION__COMMON	4
+
+struct MR_ModuleCommonLayout_Struct {
+	MR_uint_least8_t                MR_mlc_version_number;
+	MR_ConstString			MR_mlc_name;
+	MR_Integer			MR_mlc_string_table_size;
+	const char			*MR_mlc_string_table;
+};
 
 struct MR_ModuleLayout_Struct {
-	MR_uint_least8_t                MR_ml_version_number;
-	MR_ConstString			MR_ml_name;
-	MR_Integer			MR_ml_string_table_size;
-	const char			*MR_ml_string_table;
+	const MR_ModuleCommonLayout	*MR_ml_common;
 	MR_Integer			MR_ml_proc_count;
 	const MR_ProcLayout		**MR_ml_procs;
 	MR_Integer			MR_ml_filename_count;
@@ -1408,6 +1433,11 @@
 	MR_UserEventSpec		*MR_ml_user_event_specs;
 };
 
+#define	MR_ml_version_number	MR_ml_common->MR_mlc_version_number
+#define	MR_ml_name		MR_ml_common->MR_mlc_name
+#define	MR_ml_string_table_size	MR_ml_common->MR_mlc_string_table_size
+#define	MR_ml_string_table	MR_ml_common->MR_mlc_string_table
+
 /*-------------------------------------------------------------------------*/
 /*
 ** Definitions for MR_ClosureId
Index: runtime/mercury_string.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_string.h,v
retrieving revision 1.34
diff -u -b -r1.34 mercury_string.h
Index: runtime/mercury_trace_base.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_trace_base.c,v
retrieving revision 1.82
diff -u -b -r1.82 mercury_trace_base.c
--- runtime/mercury_trace_base.c	2 May 2007 02:16:00 -0000	1.82
+++ runtime/mercury_trace_base.c	10 Sep 2007 05:14:19 -0000
@@ -1306,63 +1306,68 @@
 ** declarative debugger is in fact invoked.
 */
 
-#define PROC_REP_TABLE_SIZE (1 << 16)   /* 64k */
+#define PROC_DEFN_REP_TABLE_SIZE (1 << 16)   /* 64k */
 
 typedef struct {
     const MR_ProcLayout     *plr_layout;
     MR_Word                 plr_rep;
-} MR_ProcLayout_Rep;
+} MR_ProcLayoutRep;
 
-static  void                MR_do_init_proc_rep_table(void);
-static  const void          *proc_layout_rep_key(const void *proc_layout);
-static  int                 hash_proc_layout_addr(const void *addr);
-static  MR_bool             equal_proc_layouts(const void *addr1,
+static  void                MR_do_init_proc_defn_rep_table(void);
+static  const void          *MR_proc_layout_rep_key(const void *proc_layout);
+static  int                 MR_hash_proc_layout_addr(const void *addr);
+static  MR_bool             MR_equal_proc_layouts(const void *addr1,
                                 const void *addr2);
 
-static  MR_Hash_Table       proc_rep_table = { PROC_REP_TABLE_SIZE, NULL,
-                                proc_layout_rep_key, hash_proc_layout_addr,
-                                equal_proc_layouts };
+static  MR_Hash_Table       proc_defn_rep_table = {
+                                PROC_DEFN_REP_TABLE_SIZE,
+                                NULL,
+                                MR_proc_layout_rep_key,
+                                MR_hash_proc_layout_addr,
+                                MR_equal_proc_layouts
+                            };
 
 static void
-MR_do_init_proc_rep_table(void)
+MR_do_init_proc_defn_rep_table(void)
 {
     static  MR_bool done = MR_FALSE;
 
     if (!done) {
-        MR_init_hash_table(proc_rep_table);
+        MR_init_hash_table(proc_defn_rep_table);
         done = MR_TRUE;
     }
 }
 
 void
-MR_insert_proc_rep(const MR_ProcLayout *proc_layout, MR_Word proc_rep)
+MR_insert_proc_defn_rep(const MR_ProcLayout *proc_layout,
+    MR_Word proc_defn_rep)
 {
-    MR_ProcLayout_Rep  *layout_rep;
+    MR_ProcLayoutRep    *layout_rep;
 
-    MR_do_init_proc_rep_table();
+    MR_do_init_proc_defn_rep_table();
 
-    layout_rep = MR_GC_NEW(MR_ProcLayout_Rep);
+    layout_rep = MR_GC_NEW(MR_ProcLayoutRep);
     layout_rep->plr_layout = proc_layout;
-    layout_rep->plr_rep = proc_rep;
+    layout_rep->plr_rep = proc_defn_rep;
 
-    (void) MR_insert_hash_table(proc_rep_table, layout_rep);
+    (void) MR_insert_hash_table(proc_defn_rep_table, layout_rep);
 
 #ifdef  MR_DEBUG_PROC_REP
     if (MR_progdebug) {
         printf("insert: layout %p, rep %x, pair %p\n",
-            proc_layout, proc_rep, layout_rep);
+            proc_layout, proc_defn_rep, layout_rep);
     }
 #endif
 }
 
 MR_Word
-MR_lookup_proc_rep(const MR_ProcLayout *proc_layout)
+MR_lookup_proc_defn_rep(const MR_ProcLayout *proc_layout)
 {
-    const MR_ProcLayout_Rep  *layout_rep;
+    const MR_ProcLayoutRep  *layout_rep;
 
-    MR_do_init_proc_rep_table();
+    MR_do_init_proc_defn_rep_table();
 
-    layout_rep = MR_lookup_hash_table(proc_rep_table, proc_layout);
+    layout_rep = MR_lookup_hash_table(proc_defn_rep_table, proc_layout);
     if (layout_rep == NULL) {
 #ifdef  MR_DEBUG_PROC_REP
         if (MR_progdebug) {
@@ -1384,11 +1389,11 @@
 }
 
 static const void *
-proc_layout_rep_key(const void *pair)
+MR_proc_layout_rep_key(const void *pair)
 {
-    MR_ProcLayout_Rep   *proc_layout_rep;
+    MR_ProcLayoutRep    *proc_layout_rep;
 
-    proc_layout_rep = (MR_ProcLayout_Rep *) pair;
+    proc_layout_rep = (MR_ProcLayoutRep *) pair;
     if (proc_layout_rep == NULL) {
         return NULL;
     } else {
@@ -1397,13 +1402,13 @@
 }
 
 static int
-hash_proc_layout_addr(const void *addr)
+MR_hash_proc_layout_addr(const void *addr)
 {
-    return (((MR_Unsigned) addr) >> 5) % PROC_REP_TABLE_SIZE;
+    return (((MR_Unsigned) addr) >> 5) % PROC_DEFN_REP_TABLE_SIZE;
 }
 
 static MR_bool
-equal_proc_layouts(const void *addr1, const void *addr2)
+MR_equal_proc_layouts(const void *addr1, const void *addr2)
 {
     return ((const MR_ProcLayout *) addr1) == ((const MR_ProcLayout *) addr2);
 }
Index: runtime/mercury_trace_base.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_trace_base.h,v
retrieving revision 1.60
diff -u -b -r1.60 mercury_trace_base.h
--- runtime/mercury_trace_base.h	2 May 2007 02:16:00 -0000	1.60
+++ runtime/mercury_trace_base.h	3 Aug 2007 08:06:31 -0000
@@ -602,16 +602,17 @@
 ** this construction process allocates a significant amount of memory and
 ** takes a nontrivial amount of time, we cache the results in this table.
 **
-** MR_insert_proc_rep adds the result of a conversion to the cache.
+** MR_insert_proc_defn_rep adds the result of a conversion to the cache.
 **
-** MR_lookup_proc_rep checks whether a previous call to MR_lookup_proc_rep
-** has already cached the procedure body representation of a given procedure;
-** a zero return value means that the answer is "no".
+** MR_lookup_proc_defn_rep checks whether a previous call to
+** MR_insert_proc_defn_rep has already cached the procedure body
+** representation of a given procedure; a zero return value means that
+** the answer is "no".
 */
 
-extern	void	MR_insert_proc_rep(const MR_ProcLayout *proc_layout,
-		MR_Word proc_rep);
-extern	MR_Word MR_lookup_proc_rep(const MR_ProcLayout *proc_layout);
+extern	void	MR_insert_proc_defn_rep(const MR_ProcLayout *proc_layout,
+			MR_Word proc_defn_rep);
+extern	MR_Word MR_lookup_proc_defn_rep(const MR_ProcLayout *proc_layout);
 
 #ifndef	MR_HIGHLEVEL_CODE
 
Index: runtime/mercury_types.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_types.h,v
retrieving revision 1.50
diff -u -b -r1.50 mercury_types.h
--- runtime/mercury_types.h	13 Aug 2007 01:27:52 -0000	1.50
+++ runtime/mercury_types.h	4 Sep 2007 11:39:51 -0000
@@ -249,6 +249,7 @@
 
 typedef struct MR_LongLval_Struct               MR_LongLval;
 typedef struct MR_ProcLayout_Struct             MR_ProcLayout;
+typedef struct MR_ModuleCommonLayout_Struct     MR_ModuleCommonLayout;
 typedef struct MR_ModuleLayout_Struct           MR_ModuleLayout;
 typedef struct MR_LabelLayout_Struct            MR_LabelLayout;
 typedef struct MR_SynthAttr_Struct              MR_SynthAttr;
Index: runtime/mercury_wrapper.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_wrapper.c,v
retrieving revision 1.182
diff -u -b -r1.182 mercury_wrapper.c
--- runtime/mercury_wrapper.c	1 May 2007 01:11:42 -0000	1.182
+++ runtime/mercury_wrapper.c	10 Sep 2007 05:16:47 -0000
@@ -302,8 +302,10 @@
 
 MR_bool             MR_profiling = MR_TRUE;
 MR_bool             MR_print_deep_profiling_statistics = MR_FALSE;
-MR_bool             MR_deep_profiling_save_results = MR_TRUE;
-MR_bool             MR_complexity_save_results = MR_TRUE;
+MR_bool             MR_output_deep_procrep_file;
+static  unsigned    MR_deep_prof_random_write = 0;
+static  MR_bool     MR_deep_profiling_save_results = MR_TRUE;
+static  MR_bool     MR_complexity_save_results = MR_TRUE;
 
 #ifdef  MR_TYPE_CTOR_STATS
 
@@ -366,7 +368,8 @@
 void    (*MR_address_of_init_modules_complexity)(void);
 #endif
 #ifdef  MR_DEEP_PROFILING
-void    (*MR_address_of_write_out_proc_statics)(FILE *fp);
+void    (*MR_address_of_write_out_proc_statics)(FILE *deep_fp,
+            FILE *procrep_fp);
 #endif
 void    (*MR_address_of_init_modules_required)(void);
 void    (*MR_address_of_final_modules_required)(void);
@@ -1090,6 +1093,8 @@
     MR_NUM_OUTPUT_ARGS,
     MR_DEBUG_THREADS_OPT,
     MR_DEEP_PROF_DEBUG_FILE_OPT,
+    MR_DEEP_PROF_PROCREP_FILE_OPT,
+    MR_DEEP_PROF_RANDOM_WRITE,
     MR_DEEP_PROF_LOG_FILE_OPT,
     MR_DEEP_PROF_LOG_PROG_OPT,
     MR_TABLING_STATISTICS_OPT,
@@ -1178,6 +1183,12 @@
     { "num-output-args",                1, 0, MR_NUM_OUTPUT_ARGS },
     { "debug-threads",                  0, 0, MR_DEBUG_THREADS_OPT },
     { "deep-debug-file",                0, 0, MR_DEEP_PROF_DEBUG_FILE_OPT },
+    { "deep-procrep-file",              0, 0, MR_DEEP_PROF_PROCREP_FILE_OPT },
+    /*
+    ** The --deep-random-write option is only for use by tools/bootcheck.
+    ** It is deliberately not documented.
+    */
+    { "deep-random-write",              1, 0, MR_DEEP_PROF_RANDOM_WRITE },
     { "deep-log-file",                  1, 0, MR_DEEP_PROF_LOG_FILE_OPT },
     { "deep-log-prog",                  1, 0, MR_DEEP_PROF_LOG_PROG_OPT },
     { "tabling-statistics",             0, 0, MR_TABLING_STATISTICS_OPT },
@@ -1610,6 +1621,16 @@
                 MR_deep_prof_debug_file_flag = MR_TRUE;
                 break;
 
+            case MR_DEEP_PROF_PROCREP_FILE_OPT:
+                MR_output_deep_procrep_file = MR_TRUE;
+                break;
+
+            case MR_DEEP_PROF_RANDOM_WRITE:
+                if (sscanf(MR_optarg, "%u", &MR_deep_prof_random_write) != 1) {
+                    MR_usage();
+                }
+                break;
+
             case MR_DEEP_PROF_LOG_FILE_OPT:
 #if defined(MR_DEEP_PROFILING) && defined(MR_DEEP_PROFILING_LOG)
                 MR_deep_prof_log_file = fopen(MR_optarg, "w");
@@ -2590,8 +2611,22 @@
 #ifdef MR_DEEP_PROFILING
     MR_deep_prof_turn_off_time_profiling();
     if (MR_deep_profiling_save_results) {
+        if (MR_deep_prof_random_write == 0) {
+            /*
+            ** If MR_deep_prof_random_write is not set, always write out
+            ** the results of deep profiling.
+            */
+            MR_write_out_profiling_tree();
+        } else {
+            /*
+            ** If MR_deep_prof_random_write is set to N, write out the results
+            ** of deep profiling only on every Nth program run (on average).
+            */
+            if ((getpid() % MR_deep_prof_random_write) == 0) {
         MR_write_out_profiling_tree();
     }
+        }
+    }
   #ifdef MR_DEEP_PROFILING_LOG
     (void) fclose(MR_deep_prof_log_file);
   #endif
Index: runtime/mercury_wrapper.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_wrapper.h,v
retrieving revision 1.79
diff -u -b -r1.79 mercury_wrapper.h
--- runtime/mercury_wrapper.h	9 Feb 2007 04:05:18 -0000	1.79
+++ runtime/mercury_wrapper.h	10 Sep 2007 05:16:48 -0000
@@ -95,7 +95,8 @@
 extern	void		(*MR_address_of_init_modules_complexity)(void);
 #endif
 #ifdef	MR_DEEP_PROFILING
-extern	void		(*MR_address_of_write_out_proc_statics)(FILE *fp);
+extern	void		(*MR_address_of_write_out_proc_statics)(FILE *deep_fp,
+				FILE *procrep_fp);
 #endif
 extern	void		(*MR_address_of_init_modules_required)(void);
 extern	void		(*MR_address_of_final_modules_required)(void);
@@ -301,6 +302,7 @@
 			MR_time_profile_method;
 
 extern	MR_bool		MR_profiling;
+extern	MR_bool		MR_output_deep_procrep_file;
 extern	MR_bool		MR_print_deep_profiling_statistics;
 
 #ifdef  MR_TYPE_CTOR_STATS
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/standalone_c
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/solver_types
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
Index: slice/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/slice/Mmakefile,v
retrieving revision 1.12
diff -u -b -r1.12 Mmakefile
--- slice/Mmakefile	20 Jul 2007 01:22:06 -0000	1.12
+++ slice/Mmakefile	3 Aug 2007 08:30:55 -0000
@@ -72,6 +72,7 @@
 all:	$(MDBCOMP_MODULES) $(MERCURY_MAIN_MODULES) $(TAGS_FILE_EXISTS)
 
 #-----------------------------------------------------------------------------#
+#
 # We need to start by turning write permission on for each copied file
 # in case some exist, but we need to ignore errors in case some don't exist.
 # The exit 0 is to prevent make itself from printing a message about the
@@ -128,7 +129,7 @@
 tags:	$(MTAGS) $(mslice.ms) $(mdice.ms) $(mtc_union.ms) $(mcov.ms) \
 		$(mtc_diff.ms) $(LIBRARY_DIR)/*.m
 	$(MTAGS) $(mslice.ms) $(mdice.ms) $(mtc_union.ms) $(mcov.ms) \
-		$(mtc_diff.ms) $($(LIBRARY_DIR)/*.m
+		$(mtc_diff.ms) $(LIBRARY_DIR)/*.m
 
 .PHONY: tags_file_exists
 tags_file_exists:
@@ -161,8 +162,8 @@
 #-----------------------------------------------------------------------------#
 
 realclean_local:
-	rm -f tags SLICE_FLAGS SLICE_FLAGS.date mdbcomp.*.err \
-		$(MDBCOMP_MODULES)
+	rm -f tags SLICE_FLAGS SLICE_FLAGS.date \
+		$(MDBCOMP_MODULES) mdbcomp.*.err
 
 #-----------------------------------------------------------------------------#
 
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
cvs diff: Diffing tests/debugger/declarative
Index: tests/debugger/declarative/dependency.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/declarative/dependency.exp,v
retrieving revision 1.14
diff -u -b -r1.14 dependency.exp
--- tests/debugger/declarative/dependency.exp	14 Aug 2007 01:54:54 -0000	1.14
+++ tests/debugger/declarative/dependency.exp	4 Sep 2007 23:02:29 -0000
@@ -20,7 +20,7 @@
 mdb> format raw_pretty
 mdb> p proc_body
 	
-proc_rep(
+proc_defn_rep(
   [|](1, []), 
   conj_rep(
     [|](
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/par_conj
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/trailing
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
Index: tools/bootcheck
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/tools/bootcheck,v
retrieving revision 1.197
diff -u -b -r1.197 bootcheck
--- tools/bootcheck	15 Aug 2007 04:01:08 -0000	1.197
+++ tools/bootcheck	10 Sep 2007 05:32:21 -0000
@@ -1,5 +1,5 @@
 #!/bin/sh
-# vim: ts=4 sw=4 wm=0 tw=0 et
+# vim: ts=4 sw=4 et
 #---------------------------------------------------------------------------#
 # Copyright (C) 1995-2001 The University of Melbourne.
 # This file may only be copied under the terms of the GNU General
@@ -547,6 +547,15 @@
     export MERCURY_OPTIONS
 fi
 
+# In deep profiling grades, we want to test the code for writing out the
+# profiling tree, but there is no point in testing it on every single
+# invocation of the compiler, and doing so leads to *very* slow bootchecks.
+# We therefore enable it only for every 25th invocation, on average.
+#
+# When the profiling data is written out, however, we also want to test
+# writing out the program representation.
+MERCURY_OPTIONS="$MERCURY_OPTIONS --deep-random-write=25 --deep-procrep-file"
+
 if $trace_count
 then
     MERCURY_OPTIONS="$MERCURY_OPTIONS --trace-count-if-exec=mercury_compile"
@@ -865,6 +874,9 @@
         MMAKE=$MMAKE_DIR/mmake
         mmake_opts="$mmake_opts $target_opt"
 
+        MERCURY_MKINIT="$root/util/mkinit"
+        export MERCURY_MKINIT
+
         if (cd $stage2dir && $MMAKE $mmake_opts $jfactor runtime)
         then
             echo "building of stage 2 runtime successful"
cvs diff: Diffing trace
Index: trace/mercury_trace_cmd_browsing.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_cmd_browsing.c,v
retrieving revision 1.6
diff -u -b -r1.6 mercury_trace_cmd_browsing.c
--- trace/mercury_trace_cmd_browsing.c	31 Jul 2007 05:48:20 -0000	1.6
+++ trace/mercury_trace_cmd_browsing.c	4 Sep 2007 23:01:29 -0000
@@ -554,12 +554,13 @@
                 problem = "current procedure has no body bytecodes";
             } else {
                 MR_TRACE_CALL_MERCURY(
-                    MR_MDBCOMP_trace_read_rep(entry->MR_sle_body_bytes,
+                    MR_MDBCOMP_trace_read_proc_defn_rep(
+                        entry->MR_sle_body_bytes,
                         event_info->MR_event_sll, &rep);
                 );
 
                 browser_term = MR_type_value_to_browser_term(
-                    (MR_TypeInfo) ML_proc_rep_type(), rep);
+                    (MR_TypeInfo) ML_proc_defn_rep_type(), rep);
             }
         } else {
             MR_VarSpec  var_spec;
@@ -766,11 +767,11 @@
     }
 
     MR_TRACE_CALL_MERCURY(
-        MR_MDBCOMP_trace_read_rep(entry->MR_sle_body_bytes,
+        MR_MDBCOMP_trace_read_proc_defn_rep(entry->MR_sle_body_bytes,
             event_info->MR_event_sll, &rep);
     );
 
-    (*browser)(ML_proc_rep_type(), rep, caller, format);
+    (*browser)(ML_proc_defn_rep_type(), rep, caller, format);
     return (const char *) NULL;
 }
 
cvs diff: Diffing util
Index: util/mkinit.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/util/mkinit.c,v
retrieving revision 1.118
diff -u -b -r1.118 mkinit.c
--- util/mkinit.c	18 Jun 2007 05:41:30 -0000	1.118
+++ util/mkinit.c	10 Sep 2007 03:27:51 -0000
@@ -162,7 +162,7 @@
     "void",
     "void",
     "void",
-    "FILE *fp",
+    "FILE *deep_fp, FILE *procrep_fp",
     "void",
     "void"
 };
@@ -173,7 +173,7 @@
     "void",
     "void",
     "void",
-    "FILE *",
+    "FILE *, FILE *",
     "void",
     "void"
 };
@@ -184,7 +184,7 @@
     "",
     "",
     "",
-    "fp",
+    "deep_fp, procrep_fp",
     "",
     ""
 };
@@ -387,7 +387,8 @@
     "   MR_address_of_init_modules_type_tables = init_modules_type_tables;\n"
     "   MR_address_of_init_modules_debugger = init_modules_debugger;\n"
     "#ifdef MR_RECORD_TERM_SIZES\n"
-    "   MR_address_of_init_modules_complexity = init_modules_complexity_procs;\n"
+    "   MR_address_of_init_modules_complexity =\n"
+    "       init_modules_complexity_procs;\n"
     "#endif\n"
     "#ifdef MR_DEEP_PROFILING\n"
     "   MR_address_of_write_out_proc_statics =\n"
cvs diff: Diffing vim
cvs diff: Diffing vim/after
cvs diff: Diffing vim/ftplugin
cvs diff: Diffing vim/syntax
--------------------------------------------------------------------------
mercury-reviews mailing list
Post messages to:       mercury-reviews at csse.unimelb.edu.au
Administrative Queries: owner-mercury-reviews at csse.unimelb.edu.au
Subscriptions:          mercury-reviews-request at csse.unimelb.edu.au
--------------------------------------------------------------------------



More information about the reviews mailing list