[m-rev.] for review: making user events more useful

Zoltan Somogyi zs at csse.unimelb.edu.au
Mon Dec 4 17:01:07 AEDT 2006


This is for review by Julien in Mark's absence.

Zoltan.

Implement some of Mark's wish list for making user events more useful.

1. When executing "print *" in mdb, we used to print both the values of all
   attributes and the values of all live variables. Since some attributes'
   values were given directly by live variables, this lead to some things being
   printed twice. This diff eliminates this duplication.

2. At user events, we now print the name of the event. Whether we print the
   other stuff we also print at events (the predicate containing the event,
   and its source location) is now controlled by a new mdb command,
   "user_event_context".

3. We would like different solvers to be compilable independently of one
   another. This means that neither solver's event set should depend on the
   existence of the events needed by the other solvers. This diff therefore
   eliminates the requirement that all modules of the program be compiled with
   the same event set specification. Instead, a program may contain modules
   that were compiled with different event sets. Each event set is named;
   the new requirement is that different named event sets may coexist in the
   program (each being used to compile some modules), but two event sets with
   the same name must be identical in all other respects as well (we need this
   requirement to prevent inconsistencies arising between different versions of
   the same event set).

4. We now generate user events even from modules compiled with --trace shallow.
   The problem here is that user events can occur in procedures that do not
   get caller events and whose ancestors may not get caller events either.
   Yet these procedures must still pass on debugger information such as call
   sequence numbers and the call depth to the predicate with the user event.
   This diff therefore decouples the generation of code for this basic debugger
   infrastructure information from the generation of call events by inventing
   two new trace levels, settable by the compiler only (i.e. not from the
   command line). The trace level "basic_user" is for procedures containing a
   user event whose trace level (in a shallow traced module) would otherwise be
   "none". The trace level "basic" is for procedures not containing a user
   event but which nevertheless may need to transmit information (e.g. depth)
   to a user event. For the foreseeable future, this means that shallow traced
   modules containing user events will have some debugging overhead compiled
   into *all* their procedures.

runtime/mercury_stack_layout.h:
	Add a new field to MR_UserEvent structures, giving the HLDS number of
	the variable representing each attribute.

	Add a new field to module layout structures, giving the name of the
	event set (if any) the module was compiled with.

	Add the new trace levels to the MR_TraceLevel type.

	Update the current layout structure version number.

runtime/mercury_stack_trace.[ch]:
	Allow the printing of the containing predicate's name and/or the
	filename/linenumber context to be turned off when printing contexts.
	Factor out some of the code involved in this printing.

	Give a bunch of variables better names.

	Rename a type to get rid of unnecessary underscores.

compiler/prog_data.m:
compiler/prog_event.m:
	Include the event set name in the information we have about the event
	set.

compiler/simplify.m:
	Mark each procedure and each module that contains user events
	as containing user events.

	Use the same technique to mark each procedure that contains parallel
	conjunctions as containing parallel conjunctions, instead of marking
	the predicate containing the procedure. (Switch detection may eliminate
	arbitrary goals, including parallel conjunctions, from switch arms
	that are unreachable due to initial insts, and in any case we want to
	handle the procedures of a predicate independently from each other
	after mode analysis.)

	Also, change the code handling generic calls to switch on the generic
	call kind, and factor out some common code.

compiler/hlds_module.m:
compiler/hlds_pred.m:
	Provide slots in the proc_info and the module_info for the information
	gathered by simplify.

compiler/trace_params.m:
	Implement the new trace levels described above. This required changing
	the signature of some of the predicates of this module.

compiler/code_info.m:
	Record whether the compiler generated any trace events. We need to know
	this, because if it did, then we must generate a proc layout structure
	for it.

compiler/proc_gen.m:
	Act on the information recorded by code_info.m.

	Factor out the code for generating the call event and its layout
	structure, since the conditions for generating this event have changed.

compiler/continuation_info.m:
compiler/call_gen.m:
	For each user event, record the id of the variables corresponding to
	each argument of a user event.

compiler/layout.m:
compiler/layout_out.m:
compiler/stack_layout.m:
	Generate the new field (giving the HLDS variable number of each
	attribute) in user event structures, and the new field (event set name)
	in module layout structures.

	Allow the call event's layout structure to be missing. This is needed
	for user events in shallow traced modules.

compiler/options.m:
compiler/handle_options.m:
compiler/mercury_compiler.m:
	Rename the option for specifying event sets from --event-spec-file-name
	to --event-set-file-name, since it specifies only one event set, not
	all events.

compiler/jumpopt.m:
	Give some predicates better names.

compiler/dep_par_conj.m:
compiler/deforest.m:
compiler/granularity.m:
compiler/hlds_out.m:
compiler/inlining.m:
compiler/intermod.m:
compiler/lambda.m:
compiler/liveness.m:
compiler/modes.m:
compiler/opt_debug.m:
compiler/optimize.m:
compiler/size_proc.m:
compiler/stack_alloc.m:
compiler/store_alloc.m:
compiler/table_gen.m:
compiler/trace_gen.m:
compiler/typecheck.m:
	Conform to the changes above.

doc/mdb_categories:
	Mention the new mdb command.

doc/user_guide.texi:
	Update the documentation of user events to account for the changes
	above.

trace/mercury_event_parser.y:
trace/mercury_event_scanner.l:
	Modify the grammar for event set specifications to a name for the
	event set.

trace/mercury_event_spec.[ch]:
	Instead of recording information about event sets internally
	in this module, return a representation of each event set read in
	to the callers, for them to do with as they please.

	Include the event set name when we print the Mercury term for
	compiler/prog_event.m.

trace/mercury_trace.c:
	Do not assume that every procedure that contains an event contains a
	call event (and hence a call event layout structure), since that
	is not true anymore.

trace/mercury_trace_cmd_parameter.[ch]:
	Implement the new mdb command "user_event_context".

trace/mercury_trace_cmd_internal.[ch]:
	Include "user_event_context" in the list of mdb commands.

	Print the user event name at user events. Let the current setting
	of the user_event_context mdb command determine what else to print
	at such events.

	Instead of reading in one event set on initialization, read in
	all event sets that occur in the program.

trace/mercury_trace_tables.[ch]:
	Allow the gathering of information for more than one event set
	from the modules of the program.

trace/mercury_trace_vars.[ch]:
	For each attribute value of a user event, record what the HLDS variable
	number of the attribute is. When printing all variables at an event,
	mark the variable numbers of printed attributes as being printed
	already, causing the variable with the same number not to be printed.

	Include the name of the variable (if it has one) in the description
	of an attribute. Without this, users may wonder why the value of the
	variable wasn't printed.

trace/mercury_trace_cmd_browsing.[ch]:
	Pass the current setting of the user_event_context mdb command to
	runtime/mercury_stack_trace.c when printing the context of an event.

tests/debugger/user_event_shallow.{m,inp,exp}:
	New test case to test the new functionality. This test case is the same
	as the user_event test case, but it is compiled with shallow tracing,
	and its mdb input exercises the user_event_context mdb command.

tests/debugger/user_event_spec:
tests/invalid/invalid_event_spec:
	Update these event set spec files by adding an event set name.

tests/debugger/Mmakefile:
tests/debugger/Mercury.options:
	Enable the new test case.

tests/debugger/user_event.exp:
	Update the expected output of the old user event test case, which now
	prints event names, but doesn't print attribute values twice.

tests/debugger/completion.exp:
	Expect the new "user_event_context" mdb command in the command list.

tests/debugger/mdb_command_test.inp:
	Test the existence of the documentation for the new mdb command.

tests/invalid/Mercury.options:
	Conform to the name change of the --event-spec-file-name option.

cvs diff: Diffing .
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
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/call_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/call_gen.m,v
retrieving revision 1.186
diff -u -b -r1.186 call_gen.m
--- compiler/call_gen.m	1 Dec 2006 15:03:50 -0000	1.186
+++ compiler/call_gen.m	4 Dec 2006 03:40:45 -0000
@@ -238,7 +238,8 @@
 
 generate_event_call(EventName, Args, GoalInfo, Code, !CI) :-
     code_info.get_module_info(!.CI, ModuleInfo),
-    module_info_get_event_spec_map(ModuleInfo, EventSpecMap),
+    module_info_get_event_set(ModuleInfo, EventSet),
+    EventSpecMap = EventSet ^ event_set_spec_map,
     (
         event_arg_names(EventSpecMap, EventName, AttributeNames),
         event_number(EventSpecMap, EventName, EventNumber)
@@ -265,7 +266,7 @@
         [Code | Codes], !CI) :-
     produce_variable(Var, Code, Rval, !CI),
     Type = variable_type(!.CI, Var),
-    Attr = user_attribute(Rval, Type, Name),
+    Attr = user_attribute(Rval, Type, Name, Var),
     generate_event_attributes(Names, Vars, Attrs, Codes, !CI).
 
 %---------------------------------------------------------------------------%
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.335
diff -u -b -r1.335 code_info.m
--- compiler/code_info.m	1 Dec 2006 15:03:51 -0000	1.335
+++ compiler/code_info.m	4 Dec 2006 03:40:45 -0000
@@ -182,6 +182,10 @@
     %
 :- pred get_layout_info(code_info::in, proc_label_layout_info::out) is det.
 
+:- pred get_proc_trace_events(code_info::in, bool::out) is det.
+
+:- pred set_proc_trace_events(bool::in, code_info::in, code_info::out) is det.
+
     % Get the global static data structures that have
     % been created during code generation for closure layouts.
     %
@@ -394,6 +398,9 @@
                                     % are live and where at which labels,
                                     % for tracing and/or accurate gc.
 
+                proc_trace_events   :: bool,
+                                    % Did the procedure have any trace events?
+
                 stackslot_max       :: int,
                                     % The maximum number of extra
                                     % temporary stackslots that have been
@@ -457,7 +464,10 @@
     proc_info_get_stack_slots(ProcInfo, StackSlots),
     globals.get_options(Globals, Options),
     globals.get_trace_level(Globals, TraceLevel),
-    ( eff_trace_level_is_none(PredInfo, ProcInfo, TraceLevel) = no ->
+    (
+        eff_trace_level_is_none(ModuleInfo, PredInfo, ProcInfo, TraceLevel)
+            = no
+    ->
         trace_fail_vars(ModuleInfo, ProcInfo, FailVars),
         MaybeFailVars = yes(FailVars),
         set.union(Liveness, FailVars, EffLiveness)
@@ -528,6 +538,7 @@
             counter.init(1),
             SaveSuccip,
             LayoutMap,
+            no,
             0,
             TempContentMap,
             PersistentTemps,
@@ -550,7 +561,10 @@
 
 init_maybe_trace_info(TraceLevel, Globals, ModuleInfo, PredInfo,
         ProcInfo, TraceSlotInfo, !CI) :-
-    ( eff_trace_level_is_none(PredInfo, ProcInfo, TraceLevel) = no ->
+    (
+        eff_trace_level_is_none(ModuleInfo, PredInfo, ProcInfo, TraceLevel)
+            = no
+    ->
         trace_setup(ModuleInfo, PredInfo, ProcInfo, Globals, TraceSlotInfo,
             TraceInfo, !CI),
         set_maybe_trace_info(yes(TraceInfo), !CI)
@@ -582,6 +596,7 @@
 get_label_counter(CI, CI ^ code_info_persistent ^ label_num_src).
 get_succip_used(CI, CI ^ code_info_persistent ^ store_succip).
 get_layout_info(CI, CI ^ code_info_persistent ^ label_info).
+get_proc_trace_events(CI, CI ^ code_info_persistent ^ proc_trace_events).
 get_max_temp_slot_count(CI, CI ^ code_info_persistent ^ stackslot_max).
 get_temp_content_map(CI, CI ^ code_info_persistent ^ temp_contents).
 get_persistent_temps(CI, CI ^ code_info_persistent ^ persistent_temps).
@@ -606,6 +621,8 @@
 set_label_counter(LC, CI, CI ^ code_info_persistent ^ label_num_src := LC).
 set_succip_used(SU, CI, CI ^ code_info_persistent ^ store_succip := SU).
 set_layout_info(LI, CI, CI ^ code_info_persistent ^ label_info := LI).
+set_proc_trace_events(PTE, CI,
+    CI ^ code_info_persistent ^ proc_trace_events := PTE).
 set_max_temp_slot_count(TM, CI,
     CI ^ code_info_persistent ^ stackslot_max := TM).
 set_temp_content_map(CM, CI, CI ^ code_info_persistent ^ temp_contents := CM).
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.83
diff -u -b -r1.83 continuation_info.m
--- compiler/continuation_info.m	24 Nov 2006 03:48:00 -0000	1.83
+++ compiler/continuation_info.m	1 Dec 2006 01:02:19 -0000
@@ -276,7 +276,8 @@
     --->    user_attribute(
                 attr_locn               :: rval,
                 attr_type               :: mer_type,
-                attr_name               :: string
+                attr_name               :: string,
+                attr_var                :: prog_var
             ).
 
 :- type user_event_info
Index: compiler/deforest.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/deforest.m,v
retrieving revision 1.77
diff -u -b -r1.77 deforest.m
--- compiler/deforest.m	1 Dec 2006 15:03:53 -0000	1.77
+++ compiler/deforest.m	4 Dec 2006 03:40:46 -0000
@@ -1815,21 +1815,22 @@
         proc_info_get_rtti_varmaps(ProcInfo0, RttiVarMaps0),
         inlining.do_inline_call(UnivQVars, Args, CalledPredInfo,
             CalledProcInfo, VarSet0, VarSet, VarTypes0, VarTypes,
-            TypeVarSet0, TypeVarSet, RttiVarMaps0, RttiVarMaps,
-            MayHaveParallelConj, Goal1),
-        pred_info_set_typevarset(TypeVarSet, PredInfo0, PredInfo1),
+            TypeVarSet0, TypeVarSet, RttiVarMaps0, RttiVarMaps, Goal1),
+        pred_info_set_typevarset(TypeVarSet, PredInfo0, PredInfo),
+        proc_info_get_has_parallel_conj(CalledProcInfo, CalledHasParallelConj),
+
+        proc_info_set_varset(VarSet, ProcInfo0, ProcInfo1),
+        proc_info_set_vartypes(VarTypes, ProcInfo1, ProcInfo2),
+        proc_info_set_rtti_varmaps(RttiVarMaps, ProcInfo2, ProcInfo3),
         (
-            MayHaveParallelConj = yes,
-            pred_info_get_markers(PredInfo1, Markers1),
-            add_marker(marker_may_have_parallel_conj, Markers1, Markers),
-            pred_info_set_markers(Markers, PredInfo1, PredInfo)
+            CalledHasParallelConj = yes,
+            proc_info_set_has_parallel_conj(yes, ProcInfo3, ProcInfo)
         ;
-            MayHaveParallelConj = no,
-            PredInfo = PredInfo1
+            CalledHasParallelConj = no,
+            % Leave the has_parallel_conj field of the proc_info as it is.
+            ProcInfo = ProcInfo3
         ),
-        proc_info_set_varset(VarSet, ProcInfo0, ProcInfo1),
-        proc_info_set_vartypes(VarTypes, ProcInfo1, ProcInfo2),
-        proc_info_set_rtti_varmaps(RttiVarMaps, ProcInfo2, ProcInfo),
+
         pd_info_set_pred_info(PredInfo, !PDInfo),
         pd_info_set_proc_info(ProcInfo, !PDInfo),
 
Index: compiler/dep_par_conj.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/dep_par_conj.m,v
retrieving revision 1.14
diff -u -b -r1.14 dep_par_conj.m
--- compiler/dep_par_conj.m	1 Dec 2006 15:03:54 -0000	1.14
+++ compiler/dep_par_conj.m	4 Dec 2006 03:40:46 -0000
@@ -212,22 +212,24 @@
 
 process_pred_for_dep_par_conj(PredId, !ModuleInfo, !ParProcs, !IO) :-
     module_info_pred_info(!.ModuleInfo, PredId, PredInfo),
-    pred_info_get_markers(PredInfo, Markers),
-    (if check_marker(Markers, marker_may_have_parallel_conj) then
         ProcIds = pred_info_non_imported_procids(PredInfo),
         list.foldl3(process_proc_for_dep_par_conj(PredId), ProcIds,
-            !ModuleInfo, !ParProcs, !IO)
-    else
-        true
-    ).
+        !ModuleInfo, !ParProcs, !IO).
 
 :- pred process_proc_for_dep_par_conj(pred_id::in, proc_id::in,
     module_info::in, module_info::out, par_procs::in, par_procs::out,
     io::di, io::uo) is det.
 
 process_proc_for_dep_par_conj(PredId, ProcId, !ModuleInfo, !ParProcs, !IO) :-
+    module_info_proc_info(!.ModuleInfo, PredId, ProcId, ProcInfo),
+    proc_info_get_has_parallel_conj(ProcInfo, HasParallelConj),
+    (
+        HasParallelConj = no
+    ;
+        HasParallelConj = yes,
     process_proc_for_dep_par_conj_with_ignores(PredId, ProcId, set.init,
-        !ModuleInfo, !ParProcs, !IO).
+            !ModuleInfo, !ParProcs, !IO)
+    ).
 
 :- pred process_proc_for_dep_par_conj_with_ignores(pred_id::in, proc_id::in,
     set(prog_var)::in, module_info::in, module_info::out,
Index: compiler/granularity.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/granularity.m,v
retrieving revision 1.3
diff -u -b -r1.3 granularity.m
--- compiler/granularity.m	1 Dec 2006 15:03:57 -0000	1.3
+++ compiler/granularity.m	4 Dec 2006 03:40:46 -0000
@@ -64,10 +64,11 @@
 runtime_granularity_test_in_proc(SCC, proc(PredId, ProcId), !ModuleInfo) :-
     module_info_preds(!.ModuleInfo, PredTable0),
     map.lookup(PredTable0, PredId, PredInfo0),
-    pred_info_get_markers(PredInfo0, Markers),
-    ( check_marker(Markers, marker_may_have_parallel_conj) ->
         pred_info_get_procedures(PredInfo0, ProcTable0),
         map.lookup(ProcTable0, ProcId, ProcInfo0),
+    proc_info_get_has_parallel_conj(ProcInfo0, HasParallelConj),
+    (
+        HasParallelConj = yes,
         proc_info_get_goal(ProcInfo0, Goal0),
         runtime_granularity_test_in_goal(Goal0, Goal, no, Changed,
             SCC, !.ModuleInfo),
@@ -83,9 +84,9 @@
             module_info_set_preds(PredTable, !ModuleInfo)
         )
     ;
+        HasParallelConj = no
         % There is no parallelism in this procedure, so there is no granularity
         % to control.
-        true
     ).
 
 :- pred runtime_granularity_test_in_goal(hlds_goal::in, hlds_goal::out,
Index: compiler/handle_options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/handle_options.m,v
retrieving revision 1.285
diff -u -b -r1.285 handle_options.m
--- compiler/handle_options.m	1 Dec 2006 15:03:57 -0000	1.285
+++ compiler/handle_options.m	4 Dec 2006 03:40:46 -0000
@@ -367,17 +367,17 @@
     some [!Globals] (
         globals.io_get_globals(!:Globals, !IO),
 
-        globals.lookup_string_option(!.Globals, event_spec_file_name,
-            EventSpecFileName0),
-        ( EventSpecFileName0 = "" ->
-            io.get_environment_var("MERCURY_EVENT_SPEC_FILE_NAME",
-                MaybeEventSpecFileName, !IO),
-            (
-                MaybeEventSpecFileName = yes(EventSpecFileName),
-                globals.set_option(event_spec_file_name,
-                    string(EventSpecFileName), !Globals)
+        globals.lookup_string_option(!.Globals, event_set_file_name,
+            EventSetFileName0),
+        ( EventSetFileName0 = "" ->
+            io.get_environment_var("MERCURY_EVENT_SET_FILE_NAME",
+                MaybeEventSetFileName, !IO),
+            (
+                MaybeEventSetFileName = yes(EventSetFileName),
+                globals.set_option(event_set_file_name,
+                    string(EventSetFileName), !Globals)
             ;
-                MaybeEventSpecFileName = no
+                MaybeEventSetFileName = no
             )
         ;
             true
@@ -1222,8 +1222,8 @@
         ->
             true
         ;
-            add_error("debugging is available only in " ++
-                "low level C grades", !Errors)
+            add_error("debugging is available only in low level C grades",
+                !Errors)
         ),
 
         % The pthreads headers on some architectures (Solaris, Linux)
Index: compiler/hlds_module.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_module.m,v
retrieving revision 1.146
diff -u -b -r1.146 hlds_module.m
--- compiler/hlds_module.m	1 Dec 2006 15:03:59 -0000	1.146
+++ compiler/hlds_module.m	4 Dec 2006 03:40:47 -0000
@@ -339,6 +339,11 @@
 :- pred module_info_set_contains_par_conj(module_info::in, module_info::out)
     is det.
 
+:- pred module_info_get_contains_user_event(module_info::in, bool::out) is det.
+
+:- pred module_info_set_contains_user_event(module_info::in, module_info::out)
+    is det.
+
 :- pred module_info_get_foreign_decl(module_info::in, foreign_decl_info::out)
     is det.
 
@@ -496,10 +501,9 @@
 :- pred module_info_get_interface_module_specifiers(module_info::in,
     set(module_name)::out) is det.
 
-:- pred module_info_get_event_spec_map(module_info::in,
-    event_spec_map::out) is det.
+:- pred module_info_get_event_set(module_info::in, event_set::out) is det.
 
-:- pred module_info_set_event_spec_map(event_spec_map::in,
+:- pred module_info_set_event_set(event_set::in,
     module_info::in, module_info::out) is det.
 
 %-----------------------------------------------------------------------------%
@@ -671,6 +675,7 @@
                 module_name                 :: module_name,
                 globals                     :: globals,
                 contains_par_conj           :: bool,
+                contains_user_event         :: bool,
                 contains_foreign_type       :: bool,
                 foreign_decl_info           :: foreign_decl_info,
                 foreign_body_info           :: foreign_body_info,
@@ -769,7 +774,7 @@
                 % (Used by unused_imports analysis).
                 interface_module_specifiers :: set(module_specifier),
 
-                event_spec_map              :: event_spec_map
+                event_set                   :: event_set
             ).
 
 module_info_init(Name, Items, Globals, QualifierInfo, RecompInfo,
@@ -807,12 +812,13 @@
     map.init(FieldNameTable),
 
     map.init(NoTagTypes),
-    ModuleSubInfo = module_sub_info(Name, Globals, no, no, [], [], [], [],
+    EventSet = event_set("", map.init),
+    ModuleSubInfo = module_sub_info(Name, Globals, no, no, no, [], [], [], [],
         no, 0, [], [], StratPreds, UnusedArgInfo, ExceptionInfo, TrailingInfo,
         MM_TablingInfo, map.init, counter.init(1), ImportedModules,
         IndirectlyImportedModules, TypeSpecInfo, NoTagTypes, no, [],
         init_analysis_info(mmc), [], [],
-        map.init, used_modules_init, set.init, map.init),
+        map.init, used_modules_init, set.init, EventSet),
     ModuleInfo = module_info(ModuleSubInfo, PredicateTable, Requests,
         UnifyPredMap, QualifierInfo, Types, Insts, Modes, Ctors,
         ClassTable, InstanceTable, AssertionTable, ExclusiveTable,
@@ -869,6 +875,7 @@
 module_info_get_contains_foreign_type(MI,
     MI ^ sub_info ^ contains_foreign_type).
 module_info_get_contains_par_conj(MI, MI ^ sub_info ^ contains_par_conj).
+module_info_get_contains_user_event(MI, MI ^ sub_info ^ contains_user_event).
 module_info_get_foreign_decl(MI, MI ^ sub_info ^ foreign_decl_info).
 module_info_get_foreign_body_code(MI, MI ^ sub_info ^ foreign_body_info).
 module_info_get_foreign_import_module(MI,
@@ -902,7 +909,7 @@
 module_info_get_used_modules(MI, MI ^ sub_info ^ used_modules).
 module_info_get_interface_module_specifiers(MI,
     MI ^ sub_info ^ interface_module_specifiers).
-module_info_get_event_spec_map(MI, MI ^ sub_info ^ event_spec_map).
+module_info_get_event_set(MI, MI ^ sub_info ^ event_set).
 
     % XXX There is some debate as to whether duplicate initialise directives
     % in the same module should constitute an error. Currently it is not, but
@@ -970,6 +977,8 @@
     MI ^ sub_info ^ contains_foreign_type := yes).
 module_info_set_contains_par_conj(MI,
     MI ^ sub_info ^ contains_par_conj := yes).
+module_info_set_contains_user_event(MI,
+    MI ^ sub_info ^ contains_user_event := yes).
 module_info_set_foreign_decl(NewVal, MI,
     MI ^ sub_info ^ foreign_decl_info := NewVal).
 module_info_set_foreign_body_code(NewVal, MI,
@@ -1028,8 +1037,7 @@
     MI ^ sub_info ^ structure_reuse_map := ReuseMap).
 module_info_set_used_modules(UsedModules, MI,
     MI ^ sub_info ^ used_modules := UsedModules).
-module_info_set_event_spec_map(EventSpecMap, MI,
-    MI ^ sub_info ^ event_spec_map := EventSpecMap).
+module_info_set_event_set(EventSet, MI, MI ^ sub_info ^ event_set := EventSet).
 
 module_info_add_parents_to_used_modules(Modules, MI,
         MI ^ sub_info ^ used_modules := UsedModules) :-
Index: compiler/hlds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_out.m,v
retrieving revision 1.412
diff -u -b -r1.412 hlds_out.m
--- compiler/hlds_out.m	1 Dec 2006 15:03:59 -0000	1.412
+++ compiler/hlds_out.m	4 Dec 2006 03:40:47 -0000
@@ -1016,7 +1016,6 @@
 marker_name(marker_does_not_terminate, "does_not_terminate").
 marker_name(marker_calls_are_fully_qualified, "calls_are_fully_qualified").
 marker_name(marker_mode_check_clauses, "mode_check_clauses").
-marker_name(marker_may_have_parallel_conj, "may_have_parallel_conj").
 marker_name(marker_mutable_access_pred, "mutable_access_pred").
 
 write_marker(Marker, !IO) :-
@@ -3587,6 +3586,8 @@
     proc_info_get_rtti_varmaps(Proc, RttiVarMaps),
     proc_info_get_eval_method(Proc, EvalMethod),
     proc_info_get_is_address_taken(Proc, IsAddressTaken),
+    proc_info_get_has_parallel_conj(Proc, HasParallelConj),
+    proc_info_get_has_user_event(Proc, HasUserEvent),
     proc_info_get_call_table_tip(Proc, MaybeCallTableTip),
     proc_info_get_maybe_deep_profile_info(Proc, MaybeDeepProfileInfo),
     proc_info_get_maybe_untuple_info(Proc, MaybeUntupleInfo),
@@ -3644,6 +3645,22 @@
         io.write_string("% address is not taken\n", !IO)
     ),
 
+    (
+        HasParallelConj = yes,
+        io.write_string("% contains parallel conjunction\n", !IO)
+    ;
+        HasParallelConj = no,
+        io.write_string("% does not contain parallel conjunction\n", !IO)
+    ),
+
+    (
+        HasUserEvent = yes,
+        io.write_string("% contains user event\n", !IO)
+    ;
+        HasUserEvent = no,
+        io.write_string("% does not contain user event\n", !IO)
+    ),
+
     ( EvalMethod = eval_normal ->
         true
     ;
Index: compiler/hlds_pred.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_pred.m,v
retrieving revision 1.213
diff -u -b -r1.213 hlds_pred.m
--- compiler/hlds_pred.m	1 Dec 2006 15:04:00 -0000	1.213
+++ compiler/hlds_pred.m	4 Dec 2006 04:36:00 -0000
@@ -399,11 +399,6 @@
                         % inst_match.bound_inst_list_contains_instname and
                         % instmap.merge) would be unacceptable.
 
-    ;       marker_may_have_parallel_conj
-                        % The predicate may contain parallel conjunctions.
-                        % It should be run through the dependent parallel
-                        % conjunction transformation.
-
     ;       marker_mutable_access_pred.
                         % This predicate is part of the machinery used to
                         % access mutables.  This marker is used to inform
@@ -1740,6 +1735,8 @@
     maybe(list(arg_info))::out) is det.
 :- pred proc_info_get_liveness_info(proc_info::in, liveness_info::out) is det.
 :- pred proc_info_get_need_maxfr_slot(proc_info::in, bool::out) is det.
+:- pred proc_info_get_has_user_event(proc_info::in, bool::out) is det.
+:- pred proc_info_get_has_parallel_conj(proc_info::in, bool::out) is det.
 :- pred proc_info_get_call_table_tip(proc_info::in,
     maybe(prog_var)::out) is det.
 :- pred proc_info_get_maybe_proc_table_info(proc_info::in,
@@ -1791,6 +1788,10 @@
     proc_info::in, proc_info::out) is det.
 :- pred proc_info_set_need_maxfr_slot(bool::in,
     proc_info::in, proc_info::out) is det.
+:- pred proc_info_set_has_user_event(bool::in,
+    proc_info::in, proc_info::out) is det.
+:- pred proc_info_set_has_parallel_conj(bool::in,
+    proc_info::in, proc_info::out) is det.
 :- pred proc_info_set_call_table_tip(maybe(prog_var)::in,
     proc_info::in, proc_info::out) is det.
 :- pred proc_info_set_maybe_proc_table_info(maybe(proc_table_info)::in,
@@ -2061,6 +2062,20 @@
                 % during the live_vars pass; it is invalid before then.
                 need_maxfr_slot             :: bool,
 
+                % Does this procedure contain a user event?
+                %
+                % This slot is set by the simplification pass.
+                proc_has_user_event         :: bool,
+
+                % Does this procedure contain parallel conjunction?
+                % If yes, it should be run through the dependent parallel
+                % conjunction transformation.
+                %
+                % This slot is set by the simplification pass.
+                % Note that after some optimization passes, this flag
+                % may be a conservative approximation.
+                proc_has_parallel_conj        :: bool,
+
                 % If the procedure's evaluation method is memo, loopcheck or
                 % minimal, this slot identifies the variable that holds the tip
                 % of the call table. Otherwise, this field will be set to `no'.
@@ -2200,7 +2215,7 @@
     SharingInfo = structure_sharing_info_init,
     ReuseInfo = structure_reuse_info_init,
     ProcSubInfo = proc_sub_info(no, no, Term2Info, IsAddressTaken, StackSlots,
-        ArgInfo, InitialLiveness, no, no, no, no, no, no,
+        ArgInfo, InitialLiveness, no, no, no, no, no, no, no, no,
         SharingInfo, ReuseInfo),
     ProcInfo = proc_info(MContext, BodyVarSet, BodyTypes, HeadVars, InstVarSet,
         DeclaredModes, Modes, no, MaybeArgLives, MaybeDet, InferredDet,
@@ -2216,7 +2231,7 @@
     ReuseInfo = structure_reuse_info_init,
     ProcSubInfo = proc_sub_info(ArgSizes, Termination, Termination2,
         IsAddressTaken, StackSlots, ArgInfo, Liveness, no, no, no, no, no,
-        no, SharingInfo, ReuseInfo),
+        no, no, no, SharingInfo, ReuseInfo),
     ProcInfo = proc_info(Context, BodyVarSet, BodyTypes, HeadVars,
         InstVarSet, no, HeadModes, no, HeadLives,
         DeclaredDetism, InferredDetism, Goal, CanProcess, ModeErrors,
@@ -2239,7 +2254,7 @@
     SharingInfo = structure_sharing_info_init,
     ReuseInfo = structure_reuse_info_init,
     ProcSubInfo = proc_sub_info(no, no, Term2Info, IsAddressTaken,
-        StackSlots, no, Liveness, no, no, no, no, no, no,
+        StackSlots, no, Liveness, no, no, no, no, no, no, no, no,
         SharingInfo, ReuseInfo),
     ProcInfo = proc_info(Context, VarSet, VarTypes, HeadVars,
         InstVarSet, no, HeadModes, no, MaybeHeadLives,
@@ -2276,6 +2291,9 @@
 proc_info_maybe_arg_info(PI, PI ^ proc_sub_info ^ arg_pass_info).
 proc_info_get_liveness_info(PI, PI ^ proc_sub_info ^ initial_liveness).
 proc_info_get_need_maxfr_slot(PI, PI ^ proc_sub_info ^ need_maxfr_slot).
+proc_info_get_has_user_event(PI, PI ^ proc_sub_info ^ proc_has_user_event).
+proc_info_get_has_parallel_conj(PI,
+    PI ^ proc_sub_info ^ proc_has_parallel_conj).
 proc_info_get_call_table_tip(PI, PI ^ proc_sub_info ^ call_table_tip).
 proc_info_get_maybe_proc_table_info(PI, PI ^ proc_sub_info ^ maybe_table_info).
 proc_info_get_table_attributes(PI, PI ^ proc_sub_info ^ table_attributes).
@@ -2309,6 +2327,10 @@
     PI ^ proc_sub_info ^ initial_liveness := IL).
 proc_info_set_need_maxfr_slot(NMS, PI,
     PI ^ proc_sub_info ^ need_maxfr_slot := NMS).
+proc_info_set_has_user_event(HUE, PI,
+    PI ^ proc_sub_info ^ proc_has_user_event := HUE).
+proc_info_set_has_parallel_conj(HPC, PI,
+    PI ^ proc_sub_info ^ proc_has_parallel_conj := HPC).
 proc_info_set_call_table_tip(CTT, PI,
     PI ^ proc_sub_info ^ call_table_tip := CTT).
 proc_info_set_maybe_proc_table_info(MTI, PI,
Index: compiler/inlining.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/inlining.m,v
retrieving revision 1.148
diff -u -b -r1.148 inlining.m
--- compiler/inlining.m	1 Dec 2006 15:04:00 -0000	1.148
+++ compiler/inlining.m	4 Dec 2006 03:40:47 -0000
@@ -113,7 +113,7 @@
 :- pred do_inline_call(list(tvar)::in, list(prog_var)::in,
     pred_info::in, proc_info::in, prog_varset::in, prog_varset::out,
     vartypes::in, vartypes::out, tvarset::in, tvarset::out,
-    rtti_varmaps::in, rtti_varmaps::out, bool::out, hlds_goal::out) is det.
+    rtti_varmaps::in, rtti_varmaps::out, hlds_goal::out) is det.
 
     % get_type_substitution(CalleeArgTypes, CallerArgTypes,
     %   HeadTypeParams, CalleeExistQTVars, TypeSubn):
@@ -426,6 +426,11 @@
                 i_done_any_inlining :: bool,
                                     % Did we do any inlining in the proc?
 
+                i_inlined_parallel  :: bool,
+                                    % Did  we inline any procs for which
+                                    % proc_info_get_has_parallel_conj returns
+                                    % `yes'?
+
                 i_need_requant      :: bool,
                                     % Does the goal need to be requantified?
 
@@ -464,6 +469,7 @@
         proc_info_get_rtti_varmaps(!.ProcInfo, RttiVarMaps0),
 
         DidInlining0 = no,
+        InlinedParallel0 = no,
         Requantify0 = no,
         DetChanged0 = no,
         PurityChanged0 = no,
@@ -471,12 +477,13 @@
         InlineInfo0 = inline_info(VarThresh, HighLevelCode, AnyTracing,
             InlinedProcs, !.ModuleInfo, UnivQTVars, Markers0,
             VarSet0, VarTypes0, TypeVarSet0, RttiVarMaps0,
-            DidInlining0, Requantify0, DetChanged0, PurityChanged0),
+            DidInlining0, InlinedParallel0, Requantify0, DetChanged0,
+            PurityChanged0),
 
         inlining_in_goal(Goal0, Goal, InlineInfo0, InlineInfo),
 
         InlineInfo = inline_info(_, _, _, _, _, _, Markers, VarSet, VarTypes,
-            TypeVarSet, RttiVarMaps, DidInlining, Requantify,
+            TypeVarSet, RttiVarMaps, DidInlining, InlinedParallel, Requantify,
             DetChanged, PurityChanged),
 
         pred_info_set_markers(Markers, !PredInfo),
@@ -488,6 +495,13 @@
         proc_info_set_goal(Goal, !ProcInfo),
 
         (
+            InlinedParallel = yes,
+            proc_info_set_has_parallel_conj(yes, !ProcInfo)
+        ;
+            InlinedParallel = no
+        ),
+
+        (
             Requantify = yes,
             requantify_proc(!ProcInfo)
         ;
@@ -595,15 +609,15 @@
 inlining_in_call(PredId, ProcId, ArgVars, Builtin,
         Context, Sym, Goal, GoalInfo0, GoalInfo, !Info) :-
     !.Info = inline_info(VarThresh, HighLevelCode, AnyTracing,
-        InlinedProcs, ModuleInfo, HeadTypeParams, Markers0,
-        VarSet0, VarTypes0, TypeVarSet0, RttiVarMaps0,
-        _DidInlining0, Requantify0, DetChanged0, PurityChanged0),
+        InlinedProcs, ModuleInfo, HeadTypeParams, Markers,
+        VarSet0, VarTypes0, TypeVarSet0, RttiVarMaps0, _DidInlining0,
+        InlinedParallel0, Requantify0, DetChanged0, PurityChanged0),
 
     module_info_pred_proc_info(ModuleInfo, PredId, ProcId, PredInfo, ProcInfo),
     % Should we inline this call?
     (
         should_inline_proc(PredId, ProcId, Builtin, HighLevelCode,
-            AnyTracing, InlinedProcs, Markers0, ModuleInfo, UserReq),
+            AnyTracing, InlinedProcs, Markers, ModuleInfo, UserReq),
         (
             UserReq = yes
         ;
@@ -622,7 +636,7 @@
     ->
         do_inline_call(HeadTypeParams, ArgVars, PredInfo, ProcInfo,
             VarSet0, VarSet, VarTypes0, VarTypes, TypeVarSet0, TypeVarSet,
-            RttiVarMaps0, RttiVarMaps, MayHaveParallelConj, Goal - GoalInfo),
+            RttiVarMaps0, RttiVarMaps, Goal - GoalInfo),
 
         % If some of the output variables are not used in the calling
         % procedure, requantify the procedure.
@@ -654,18 +668,19 @@
             DetChanged = yes
         ),
 
+        proc_info_get_has_parallel_conj(ProcInfo, HasParallelConj),
         (
-            MayHaveParallelConj = yes,
-            add_marker(marker_may_have_parallel_conj, Markers0, Markers)
+            HasParallelConj = yes,
+            InlinedParallel = yes
         ;
-            MayHaveParallelConj = no,
-            Markers = Markers0
+            HasParallelConj = no,
+            InlinedParallel = InlinedParallel0
         ),
 
         !:Info = inline_info(VarThresh, HighLevelCode, AnyTracing,
             InlinedProcs, ModuleInfo, HeadTypeParams, Markers,
-            VarSet, VarTypes, TypeVarSet, RttiVarMaps,
-            DidInlining, Requantify, DetChanged, PurityChanged)
+            VarSet, VarTypes, TypeVarSet, RttiVarMaps, DidInlining,
+            InlinedParallel, Requantify, DetChanged, PurityChanged)
     ;
         Goal = plain_call(PredId, ProcId, ArgVars, Builtin, Context, Sym),
         GoalInfo = GoalInfo0
@@ -675,7 +690,7 @@
 
 do_inline_call(HeadTypeParams, ArgVars, PredInfo, ProcInfo,
         VarSet0, VarSet, VarTypes0, VarTypes, TypeVarSet0, TypeVarSet,
-        RttiVarMaps0, RttiVarMaps, MayHaveParallelConj, Goal) :-
+        RttiVarMaps0, RttiVarMaps, Goal) :-
 
     proc_info_get_goal(ProcInfo, CalledGoal),
 
@@ -706,7 +721,7 @@
     apply_variable_renaming_to_vartypes(TypeRenaming,
         CalleeVarTypes0, CalleeVarTypes1),
 
-    % next, compute the type substitution and then apply it
+    % Next, compute the type substitution and then apply it.
 
     % Note: there's no need to update the type_info locations maps,
     % either for the caller or callee, since for any type vars in the
@@ -751,11 +766,7 @@
     % have been produced by extracting type_infos or typeclass_infos
     % from typeclass_infos in the caller, so they won't necessarily
     % be the same.
-    rtti_varmaps_overlay(CalleeRttiVarMaps1, RttiVarMaps0, RttiVarMaps),
-
-    pred_info_get_markers(PredInfo, CalleeMarkers),
-    MayHaveParallelConj = pred_to_bool(check_marker(CalleeMarkers,
-        marker_may_have_parallel_conj)).
+    rtti_varmaps_overlay(CalleeRttiVarMaps1, RttiVarMaps0, RttiVarMaps).
 
 get_type_substitution(HeadTypes, ArgTypes,
         HeadTypeParams, CalleeExistQVars, TypeSubn) :-
Index: compiler/intermod.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/intermod.m,v
retrieving revision 1.213
diff -u -b -r1.213 intermod.m
--- compiler/intermod.m	1 Dec 2006 15:04:01 -0000	1.213
+++ compiler/intermod.m	4 Dec 2006 03:40:47 -0000
@@ -1804,7 +1804,6 @@
 should_output_marker(marker_check_termination, no).
 should_output_marker(marker_calls_are_fully_qualified, no).
 should_output_marker(marker_mode_check_clauses, yes).
-should_output_marker(marker_may_have_parallel_conj, no).
 should_output_marker(marker_mutable_access_pred, no).
 
 :- pred get_pragma_foreign_code_vars(list(foreign_arg)::in, list(mer_mode)::in,
Index: compiler/jumpopt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/jumpopt.m,v
retrieving revision 1.96
diff -u -b -r1.96 jumpopt.m
--- compiler/jumpopt.m	1 Dec 2006 15:04:02 -0000	1.96
+++ compiler/jumpopt.m	4 Dec 2006 03:40:47 -0000
@@ -26,9 +26,9 @@
 
 %-----------------------------------------------------------------------------%
 
-    % jumpopt_main(LayoutLabels, MayAlterRtti, ProcLabel, Fulljumpopt,
-    %   Recjump, PessimizeTailCalls, CheckedNondetTailCall, !LabelCounter,
-    %   !Instrs, Mod):
+    % optimize_jumps_in_proc(LayoutLabels, MayAlterRtti, ProcLabel,
+    %   Fulljumpopt, Recjump, PessimizeTailCalls, CheckedNondetTailCall,
+    %   !LabelCounter, !Instrs, Mod):
     %
     % Take an instruction list and optimize jumps. This includes the jumps
     % implicit in procedure returns.
@@ -53,9 +53,10 @@
     % Mod will say whether the instruction sequence was modified
     % by the optimization.
     %
-:- pred jumpopt_main(set(label)::in, may_alter_rtti::in, proc_label::in,
-    bool::in, bool::in, bool::in, bool::in, counter::in, counter::out,
-    list(instruction)::in, list(instruction)::out, bool::out) is det.
+:- pred optimize_jumps_in_proc(set(label)::in, may_alter_rtti::in,
+    proc_label::in, bool::in, bool::in, bool::in, bool::in,
+    counter::in, counter::out, list(instruction)::in, list(instruction)::out,
+    bool::out) is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -98,8 +99,9 @@
 % frameopt, which can do a better job of optimizing this block, have
 % been applied.
 
-jumpopt_main(LayoutLabels, MayAlterRtti, ProcLabel, Fulljumpopt, Recjump,
-        PessimizeTailCalls, CheckedNondetTailCall, !C, !Instrs, Mod) :-
+optimize_jumps_in_proc(LayoutLabels, MayAlterRtti, ProcLabel, Fulljumpopt,
+        Recjump, PessimizeTailCalls, CheckedNondetTailCall, !C, !Instrs,
+        Mod) :-
     some [!Instrmap, !Blockmap, !Lvalmap, !Procmap, !Sdprocmap, !Succmap,
             !Forkmap] (
         Instrs0 = !.Instrs,
@@ -109,9 +111,9 @@
         map.init(!:Procmap),
         map.init(!:Sdprocmap),
         map.init(!:Succmap),
-        jumpopt.build_maps(!.Instrs, Recjump, !Instrmap, !Blockmap, !Lvalmap,
+        jump_opt_build_maps(!.Instrs, Recjump, !Instrmap, !Blockmap, !Lvalmap,
             !Procmap, !Sdprocmap, !Succmap),
-        jumpopt.build_forkmap(!.Instrs, !.Sdprocmap, map.init, !:Forkmap),
+        jump_opt_build_forkmap(!.Instrs, !.Sdprocmap, map.init, !:Forkmap),
         (
             PessimizeTailCalls = no
         ;
@@ -124,7 +126,7 @@
         (
             CheckedNondetTailCall = yes,
             CheckedNondetTailCallInfo0 = yes(ProcLabel - !.C),
-            jumpopt.instr_list(!.Instrs, comment(""), !.Instrmap, !.Blockmap,
+            jump_opt_instr_list(!.Instrs, comment(""), !.Instrmap, !.Blockmap,
                 !.Lvalmap, !.Procmap, !.Sdprocmap, !.Forkmap, !.Succmap,
                 LayoutLabels, Fulljumpopt, MayAlterRtti,
                 CheckedNondetTailCallInfo0, CheckedNondetTailCallInfo,
@@ -139,7 +141,7 @@
         ;
             CheckedNondetTailCall = no,
             CheckedNondetTailCallInfo0 = no,
-            jumpopt.instr_list(!.Instrs, comment(""), !.Instrmap, !.Blockmap,
+            jump_opt_instr_list(!.Instrs, comment(""), !.Instrmap, !.Blockmap,
                 !.Lvalmap, !.Procmap, !.Sdprocmap, !.Forkmap, !.Succmap,
                 LayoutLabels, Fulljumpopt, MayAlterRtti,
                 CheckedNondetTailCallInfo0, _, [], RevInstrs)
@@ -155,14 +157,14 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred jumpopt.build_maps(list(instruction)::in, bool::in,
+:- pred jump_opt_build_maps(list(instruction)::in, bool::in,
     instrmap::in, instrmap::out, tailmap::in, tailmap::out,
     lvalmap::in, lvalmap::out, tailmap::in, tailmap::out,
     tailmap::in, tailmap::out, tailmap::in, tailmap::out) is det.
 
-jumpopt.build_maps([], _, !Instrmap, !Blockmap,
+jump_opt_build_maps([], _, !Instrmap, !Blockmap,
         !Lvalmap, !Procmap, !Sdprocmap, !Succmap).
-jumpopt.build_maps([Instr0 | Instrs0], Recjump, !Instrmap, !Blockmap,
+jump_opt_build_maps([Instr0 | Instrs0], Recjump, !Instrmap, !Blockmap,
         !Lvalmap, !Procmap, !Sdprocmap, !Succmap) :-
     Instr0 = Uinstr0 - _,
     ( Uinstr0 = label(Label) ->
@@ -208,17 +210,17 @@
     ;
         true
     ),
-    jumpopt.build_maps(Instrs0, Recjump, !Instrmap, !Blockmap, !Lvalmap,
+    jump_opt_build_maps(Instrs0, Recjump, !Instrmap, !Blockmap, !Lvalmap,
         !Procmap, !Sdprocmap, !Succmap).
 
     % Find labels followed by a test of r1 where both paths set r1 to
     % its original value and proceed.
     %
-:- pred jumpopt.build_forkmap(list(instruction)::in, tailmap::in,
+:- pred jump_opt_build_forkmap(list(instruction)::in, tailmap::in,
     tailmap::in, tailmap::out) is det.
 
-jumpopt.build_forkmap([], _Sdprocmap, !Forkmap).
-jumpopt.build_forkmap([Instr - _Comment|Instrs], Sdprocmap, !Forkmap) :-
+jump_opt_build_forkmap([], _Sdprocmap, !Forkmap).
+jump_opt_build_forkmap([Instr - _Comment|Instrs], Sdprocmap, !Forkmap) :-
     (
         Instr = label(Label),
         opt_util.is_forkproceed_next(Instrs, Sdprocmap, Between)
@@ -227,7 +229,7 @@
     ;
         true
     ),
-    jumpopt.build_forkmap(Instrs, Sdprocmap, !Forkmap).
+    jump_opt_build_forkmap(Instrs, Sdprocmap, !Forkmap).
 
 %-----------------------------------------------------------------------------%
 
@@ -266,17 +268,17 @@
     % building it in right order would make instr_list not tail recursive,
     % and thus unable to handle very long instruction lists.
     %
-:- pred jumpopt.instr_list(list(instruction)::in, instr::in, instrmap::in,
+:- pred jump_opt_instr_list(list(instruction)::in, instr::in, instrmap::in,
     tailmap::in, lvalmap::in, tailmap::in, tailmap::in, tailmap::in,
     tailmap::in, set(label)::in, bool::in, may_alter_rtti::in,
     maybe(pair(proc_label, counter))::in,
     maybe(pair(proc_label, counter))::out,
     list(instruction)::in, list(instruction)::out) is det.
 
-jumpopt.instr_list([], _PrevInstr, _Instrmap, _Blockmap, _Lvalmap,
+jump_opt_instr_list([], _PrevInstr, _Instrmap, _Blockmap, _Lvalmap,
         _Procmap, _Sdprocmap, _Forkmap, _Succmap, _LayoutLabels,
         _Fulljumpopt, _MayAlterRtti, !CheckedNondetTailCallInfo, !RevInstrs).
-jumpopt.instr_list([Instr0 | Instrs0], PrevInstr, Instrmap, Blockmap,
+jump_opt_instr_list([Instr0 | Instrs0], PrevInstr, Instrmap, Blockmap,
         Lvalmap, Procmap, Sdprocmap, Forkmap, Succmap, LayoutLabels,
         Fulljumpopt, MayAlterRtti, !CheckedNondetTailCallInfo, !RevInstrs) :-
     Instr0 = Uinstr0 - Comment0,
@@ -462,7 +464,7 @@
                 % DestLabel from Blockmap, though only while
                 % processing AdjustedBlock.
                 map.delete(Blockmap, DestLabel, CrippledBlockmap),
-                jumpopt.instr_list(AdjustedBlock, comment(""), Instrmap,
+                jump_opt_instr_list(AdjustedBlock, comment(""), Instrmap,
                     CrippledBlockmap, Lvalmap, Procmap, Sdprocmap, Forkmap,
                     Succmap, LayoutLabels, Fulljumpopt, MayAlterRtti,
                     !CheckedNondetTailCallInfo, [], RevNewInstrs),
@@ -716,7 +718,7 @@
 %               short_label(Instrmap, FixNoLayout, FixNoLayoutDest),
 %               FixNoLayoutDest \= FixNoLayout
 %           ->
-%               error("jumpopt.instr_list: pragma_c fix_no_layout")
+%               error("jump_opt_instr_list: pragma_c fix_no_layout")
 %           ;
 %               true
 %           ),
@@ -725,7 +727,7 @@
 %               short_label(Instrmap, FixLayout, FixLayoutDest),
 %               FixLayoutDest \= FixLayout
 %           ->
-%               error("jumpopt.instr_list: pragma_c fix_layout")
+%               error("jump_opt_instr_list: pragma_c fix_layout")
 %           ;
 %               true
 %           ),
@@ -734,7 +736,7 @@
 %               short_label(Instrmap, FixOnlyLayout, FixOnlyLayoutDest),
 %               FixOnlyLayoutDest \= FixOnlyLayout
 %           ->
-%               error("jumpopt.instr_list: pragma_c fix_only_layout")
+%               error("jump_opt_instr_list: pragma_c fix_only_layout")
 %           ;
 %               true
 %           ),
@@ -830,7 +832,7 @@
     ;
         NewPrevInstr = Uinstr0
     ),
-    jumpopt.instr_list(RecurseInstrs, NewPrevInstr, Instrmap, Blockmap,
+    jump_opt_instr_list(RecurseInstrs, NewPrevInstr, Instrmap, Blockmap,
         Lvalmap, Procmap, Sdprocmap, Forkmap, Succmap, LayoutLabels,
         Fulljumpopt, MayAlterRtti, !CheckedNondetTailCallInfo, !RevInstrs).
 
Index: compiler/lambda.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lambda.m,v
retrieving revision 1.123
diff -u -b -r1.123 lambda.m
--- compiler/lambda.m	1 Dec 2006 15:04:02 -0000	1.123
+++ compiler/lambda.m	4 Dec 2006 03:40:47 -0000
@@ -119,6 +119,7 @@
                 inst_varset,            % from the proc_info
                 rtti_varmaps,           % from the proc_info
                 pred_markers,           % from the pred_info
+                bool,                   % has_parallel_conj, from the proc_info
                 pred_or_func,
                 string,                 % pred/func name
                 module_info,
@@ -176,15 +177,16 @@
     proc_info_get_goal(!.ProcInfo, Goal0),
     proc_info_get_rtti_varmaps(!.ProcInfo, RttiVarMaps0),
     proc_info_get_inst_varset(!.ProcInfo, InstVarSet0),
+    proc_info_get_has_parallel_conj(!.ProcInfo, HasParallelConj),
     MustRecomputeNonLocals0 = no,
 
     % Process the goal.
     Info0 = lambda_info(VarSet0, VarTypes0, Constraints0, TypeVarSet0,
-        InstVarSet0, RttiVarMaps0, Markers, PredOrFunc,
+        InstVarSet0, RttiVarMaps0, Markers, HasParallelConj, PredOrFunc,
         PredName, !.ModuleInfo, MustRecomputeNonLocals0),
     process_goal(Goal0, Goal1, Info0, Info1),
     Info1 = lambda_info(VarSet1, VarTypes1, Constraints, TypeVarSet,
-        _, RttiVarMaps1, _, _, _, !:ModuleInfo, MustRecomputeNonLocals),
+        _, RttiVarMaps1, _, _, _, _, !:ModuleInfo, MustRecomputeNonLocals),
 
     % Check if we need to requantify.
     (
@@ -305,7 +307,7 @@
         OrigNonLocals0, LambdaGoal, Unification0, Functor,
         Unification, LambdaInfo0, LambdaInfo) :-
     LambdaInfo0 = lambda_info(VarSet, VarTypes, _PredConstraints, TVarSet,
-        InstVarSet, RttiVarMaps, Markers, POF, OrigPredName,
+        InstVarSet, RttiVarMaps, Markers, HasParallelConj, POF, OrigPredName,
         ModuleInfo0, MustRecomputeNonLocals0),
 
     % Calculate the constraints which apply to this lambda expression.
@@ -442,8 +444,8 @@
         goal_info_get_context(LambdaGoalInfo, LambdaContext),
         % The TVarSet is a superset of what it really ought be,
         % but that shouldn't matter.
-        % Existentially typed lambda expressions are not
-        % yet supported (see the documentation at top of this file)
+        % Existentially typed lambda expressions are not yet supported
+        % (see the documentation at top of this file).
         ExistQVars = [],
         uni_modes_to_modes(UniModes1, OrigArgModes),
 
@@ -463,19 +465,12 @@
         map.apply_to_list(ArgVars, ArgModesMap1, ArgModes1),
 
         % Recompute the uni_modes.
-        mode_util.modes_to_uni_modes(ModuleInfo1, ArgModes1, ArgModes1,
-            UniModes),
+        modes_to_uni_modes(ModuleInfo1, ArgModes1, ArgModes1, UniModes),
 
         list.append(ArgModes1, Modes, AllArgModes),
         map.apply_to_list(AllArgVars, VarTypes, ArgTypes),
 
-        purity_to_markers(Purity, LambdaMarkers0),
-        ( check_marker(Markers, marker_may_have_parallel_conj) ->
-            add_marker(marker_may_have_parallel_conj,
-                LambdaMarkers0, LambdaMarkers)
-        ;
-            LambdaMarkers = LambdaMarkers0
-        ),
+        purity_to_markers(Purity, LambdaMarkers),
 
         % Now construct the proc_info and pred_info for the new single-mode
         % predicate, using the information computed above.
@@ -486,15 +481,21 @@
         % The debugger ignores unnamed variables.
         ensure_all_headvars_are_named(ProcInfo0, ProcInfo1),
 
+        % If the original procedure contained parallel conjunctions, then the
+        % one we are creating here may have them as well. If it does not, then
+        % the value in the proc_info of the lambda predicate will be an
+        % overconservative estimate.
+        proc_info_set_has_parallel_conj(HasParallelConj, ProcInfo1, ProcInfo2),
+
         % If we previously already needed to recompute the nonlocals,
         % then we'd better to that recomputation for the procedure
         % that we just created.
         (
             MustRecomputeNonLocals0 = yes,
-            requantify_proc(ProcInfo1, ProcInfo)
+            requantify_proc(ProcInfo2, ProcInfo)
         ;
             MustRecomputeNonLocals0 = no,
-            ProcInfo = ProcInfo1
+            ProcInfo = ProcInfo2
         ),
         set.init(Assertions),
         pred_info_create(ModuleName, PredName, PredOrFunc, LambdaContext,
@@ -516,7 +517,7 @@
     Unification = construct(Var, ConsId, ArgVars, UniModes,
         construct_dynamically, cell_is_unique, no_construct_sub_info),
     LambdaInfo = lambda_info(VarSet, VarTypes, Constraints, TVarSet,
-        InstVarSet, RttiVarMaps, Markers, POF, OrigPredName,
+        InstVarSet, RttiVarMaps, Markers, HasParallelConj, POF, OrigPredName,
         ModuleInfo, MustRecomputeNonLocals).
 
 :- pred constraint_contains_vars(list(tvar)::in, prog_constraint::in)
Index: compiler/layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout.m,v
retrieving revision 1.31
diff -u -b -r1.31 layout.m
--- compiler/layout.m	29 Nov 2006 05:18:09 -0000	1.31
+++ compiler/layout.m	1 Dec 2006 07:12:39 -0000
@@ -45,6 +45,7 @@
 :- import_module bool.
 :- import_module list.
 :- import_module maybe.
+:- import_module pair.
 
 %-----------------------------------------------------------------------------%
 
@@ -78,7 +79,8 @@
                 trace_level             :: trace_level,
                 suppressed_events       :: int,
                 num_label_exec_count    :: int,
-                maybe_event_specs       :: maybe(string)
+                maybe_event_specs       :: maybe(pair(string, string))
+                                        % event set name, event specifications
             )
     ;       closure_proc_id_data(       % defines MR_ClosureId
                 caller_proc_label       :: proc_label,
@@ -106,7 +108,8 @@
                 user_event_num_attr     :: int,
                 user_event_locns        :: rval,
                 user_event_types        :: rval,
-                user_event_names        :: list(string)
+                user_event_names        :: list(string),
+                user_event_var_nums     :: list(int)
             ).
 
 :- type label_var_info
@@ -159,7 +162,7 @@
 
 :- type proc_layout_exec_trace          % defines MR_ExecTrace
     --->    proc_layout_exec_trace(
-                call_label_layout       :: layout_name,
+                maybe_call_label_layout :: maybe(label_layout_details),
                 proc_body_bytes         :: list(int),
                                         % The procedure body represented as
                                         % a list of bytecodes.
@@ -201,6 +204,7 @@
     --->    label_layout(proc_label, int, label_vars)
     ;       user_event_layout(proc_label, int)
     ;       user_event_attr_names(proc_label, int)
+    ;       user_event_attr_var_nums(proc_label, int)
     ;       proc_layout(rtti_proc_label, proc_layout_kind)
             % A proc layout structure for stack tracing, accurate gc,
             % deep profiling and/or execution tracing.
@@ -227,6 +231,9 @@
     ;       proc_static(rtti_proc_label)
     ;       proc_static_call_sites(rtti_proc_label).
 
+:- type label_layout_details
+    --->    label_layout_details(proc_label, int, label_vars).
+
 :- type label_vars
     --->    label_has_var_info
     ;       label_has_no_var_info.
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.79
diff -u -b -r1.79 layout_out.m
--- compiler/layout_out.m	1 Dec 2006 15:04:02 -0000	1.79
+++ compiler/layout_out.m	4 Dec 2006 03:40:47 -0000
@@ -139,10 +139,10 @@
     ;
         Data = module_layout_data(ModuleName, StringTableSize,
             StringTable, ProcLayoutNames, FileLayouts, TraceLevel,
-            SuppressedEvents, NumLabels, MaybeEventSpecs),
+            SuppressedEvents, NumLabels, MaybeEventSet),
         output_module_layout_data_defn(ModuleName, StringTableSize,
             StringTable, ProcLayoutNames, FileLayouts, TraceLevel,
-            SuppressedEvents, NumLabels, MaybeEventSpecs, !DeclSet, !IO)
+            SuppressedEvents, NumLabels, MaybeEventSet, !DeclSet, !IO)
     ;
         Data = table_io_decl_data(RttiProcLabel, Kind, NumPTIs,
             PTIVectorRval, TypeParamsRval),
@@ -245,6 +245,12 @@
         io.write_string(
             label_to_c_string(internal_label(LabelNum, ProcLabel), yes), !IO)
     ;
+        Data = user_event_attr_var_nums(ProcLabel, LabelNum),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_user_event_attr_var_nums__", !IO),
+        io.write_string(
+            label_to_c_string(internal_label(LabelNum, ProcLabel), yes), !IO)
+    ;
         Data = proc_layout(RttiProcLabel, _),
         io.write_string(mercury_data_prefix, !IO),
         io.write_string("_proc_layout__", !IO),
@@ -381,6 +387,11 @@
         output_layout_name(user_event_attr_names(ProcLabel, LabelNum), !IO),
         io.write_string("[]", !IO)
     ;
+        Data = user_event_attr_var_nums(ProcLabel, LabelNum),
+        io.write_string("static const MR_uint_least16_t ", !IO),
+        output_layout_name(user_event_attr_var_nums(ProcLabel, LabelNum), !IO),
+        io.write_string("[]", !IO)
+    ;
         Data = proc_layout(ProcLabel, Kind),
         ProcIsImported = ProcLabel ^ proc_is_imported,
         ProcIsExported = ProcLabel ^ proc_is_exported,
@@ -501,6 +512,7 @@
 layout_name_would_include_code_addr(label_layout(_, _, _)) = no.
 layout_name_would_include_code_addr(user_event_layout(_, _)) = no.
 layout_name_would_include_code_addr(user_event_attr_names(_, _)) = no.
+layout_name_would_include_code_addr(user_event_attr_var_nums(_, _)) = no.
 layout_name_would_include_code_addr(proc_layout(_, _)) = no.
 layout_name_would_include_code_addr(proc_layout_exec_trace(_)) = yes.
 layout_name_would_include_code_addr(proc_layout_head_var_nums(_)) = no.
@@ -569,16 +581,23 @@
         UserChars = "_U",
         UserData = user_event_data(UserEventNumber, UserEventName,
             UserNumAttributes, UserLocnsRval, UserTypesRval,
-            UserAttrNames),
+            UserAttrNames, UserAttrVarNums),
 
         AttrNamesLayoutName = user_event_attr_names(ProcLabel, LabelNum),
         AttrNamesDataAddr = layout_addr(AttrNamesLayoutName),
-        AttrNamesRval = const(llconst_data_addr(AttrNamesDataAddr, no)),
         decl_set_insert(decl_data_addr(AttrNamesDataAddr), !DeclSet),
         output_layout_name_storage_type_name(AttrNamesLayoutName, no, !IO),
         io.write_string(" = {\n", !IO),
         io.write_list(UserAttrNames, ", ", io.write, !IO),
-        io.write_string("};\n\n", !IO),
+        io.write_string("\n};\n\n", !IO),
+
+        AttrVarNumsLayoutName = user_event_attr_var_nums(ProcLabel, LabelNum),
+        AttrVarNumsDataAddr = layout_addr(AttrVarNumsLayoutName),
+        decl_set_insert(decl_data_addr(AttrVarNumsDataAddr), !DeclSet),
+        output_layout_name_storage_type_name(AttrVarNumsLayoutName, no, !IO),
+        io.write_string(" = {\n", !IO),
+        io.write_list(UserAttrVarNums, ", ", io.write, !IO),
+        io.write_string("\n};\n\n", !IO),
 
         UserLayoutName = user_event_layout(ProcLabel, LabelNum),
         UserDataAddr = layout_addr(UserLayoutName),
@@ -594,9 +613,11 @@
         output_rval_as_addr(UserLocnsRval, !IO),
         io.write_string(",\n(MR_TypeInfo *) ", !IO),
         output_rval_as_addr(UserTypesRval, !IO),
-        io.write_string(",\n(const char **)", !IO),
-        output_rval_as_addr(AttrNamesRval, !IO),
-        io.write_string("};\n\n", !IO)
+        io.write_string(",\n", !IO),
+        output_layout_name(AttrNamesLayoutName, !IO),
+        io.write_string(",\n", !IO),
+        output_layout_name(AttrVarNumsLayoutName, !IO),
+        io.write_string("\n};\n\n", !IO)
     ),
     (
         MaybeIsHidden = yes(yes),
@@ -712,7 +733,7 @@
         ( DataAddr = data_addr(_, scalar_common_ref(_TypeNum, _CellNum)) ->
             output_data_addr(DataAddr, !IO)
         ;
-            io.write_string(" &", !IO),
+            io.write_string("&", !IO),
             output_data_addr(DataAddr, !IO)
         )
     ;
@@ -914,14 +935,22 @@
     io::di, io::uo) is det.
 
 output_layout_exec_trace_decls(RttiProcLabel, ExecTrace, !DeclSet, !IO) :-
-    ExecTrace = proc_layout_exec_trace(CallLabelLayout, _ProcBodyBytes,
+    ExecTrace = proc_layout_exec_trace(MaybeCallLabelLayout, _ProcBodyBytes,
         MaybeTableInfo, _HeadVarNums, _VarNames, _MaxVarNum,
         _MaxRegNum, _MaybeFromFullSlot, _MaybeIoSeqSlot,
         _MaybeTrailSlot, _MaybeMaxfrSlot, _EvalMethod,
         _MaybeCallTableSlot, _EffTraceLevel, _Flags),
     ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
     ModuleName = get_defining_module_name(ProcLabel) ,
-    output_layout_decl(CallLabelLayout, !DeclSet, !IO),
+    (
+        MaybeCallLabelLayout = yes(CallLabelDetails),
+        CallLabelDetails = label_layout_details(CallProcLabel, LabelNum,
+            LabelVars),
+        CallLabelLayout = label_layout(CallProcLabel, LabelNum, LabelVars),
+        output_layout_decl(CallLabelLayout, !DeclSet, !IO)
+    ;
+        MaybeCallLabelLayout = no
+    ),
     output_layout_decl(module_layout(ModuleName), !DeclSet, !IO),
     (
         MaybeTableInfo = yes(TableInfo),
@@ -973,7 +1002,7 @@
     io::di, io::uo) is det.
 
 output_layout_exec_trace(RttiProcLabel, ExecTrace, !DeclSet, !IO) :-
-    ExecTrace = proc_layout_exec_trace(CallLabelLayout, ProcBodyBytes,
+    ExecTrace = proc_layout_exec_trace(MaybeCallLabelDetails, ProcBodyBytes,
         MaybeTableInfo, HeadVarNums, _VarNames, MaxVarNum,
         MaxRegNum, MaybeFromFullSlot, MaybeIoSeqSlot, MaybeTrailSlot,
         MaybeMaxfrSlot, EvalMethod, MaybeCallTableSlot, EffTraceLevel, Flags),
@@ -991,13 +1020,19 @@
     io.write_string("\n", !IO),
     output_layout_name_storage_type_name(
         proc_layout_exec_trace(RttiProcLabel), yes, !IO),
-    io.write_string(" = {\nMR_LABEL_LAYOUT_REF(", !IO),
-    ( CallLabelLayout = label_layout(CallProcLabel, CallLabelNum, _) ->
-        output_label(internal_label(CallLabelNum, CallProcLabel), no, !IO)
+    io.write_string(" = {\n", !IO),
+    (
+        MaybeCallLabelDetails = yes(CallLabelDetails),
+        io.write_string("MR_LABEL_LAYOUT_REF(", !IO),
+        CallLabelDetails = label_layout_details(CallProcLabel, CallLabelNum,
+            _),
+        output_label(internal_label(CallLabelNum, CallProcLabel), no, !IO),
+        io.write_string("),\n", !IO)
     ;
-        unexpected(this_file, "output_layout_exec_trace: bad call layout")
+        MaybeCallLabelDetails = no,
+        io.write_string("NULL,\n", !IO)
     ),
-    io.write_string("),\n(const MR_ModuleLayout *) &", !IO),
+    io.write_string("(const MR_ModuleLayout *) &", !IO),
     ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
     ModuleName = get_defining_module_name(ProcLabel),
     output_layout_name(module_layout(ModuleName), !IO),
@@ -1308,12 +1343,12 @@
 
 :- pred output_module_layout_data_defn(module_name::in, int::in,
     string_with_0s::in, list(layout_name)::in, list(file_layout_data)::in,
-    trace_level::in, int::in, int::in, maybe(string)::in,
+    trace_level::in, int::in, int::in, maybe(pair(string, string))::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 output_module_layout_data_defn(ModuleName, StringTableSize, StringTable,
         ProcLayoutNames, FileLayouts, TraceLevel, SuppressedEvents,
-        NumLabels, MaybeEventSpecs, !DeclSet, !IO) :-
+        NumLabels, MaybeEventSet, !DeclSet, !IO) :-
     output_module_string_table(ModuleName, StringTableSize, StringTable,
         !DeclSet, !IO),
     output_module_layout_proc_vector_defn(ModuleName, ProcLayoutNames,
@@ -1331,9 +1366,9 @@
     decl_set_insert(decl_data_addr(layout_addr(LabelExecCountName)), !DeclSet),
 
     (
-        MaybeEventSpecs = no
+        MaybeEventSet = no
     ;
-        MaybeEventSpecs = yes(EventSpecs),
+        MaybeEventSet = yes(_EventSetName - EventSpecs),
         output_event_specs_defn(ModuleName, EventSpecs, !DeclSet, !IO)
     ),
 
@@ -1369,10 +1404,13 @@
     output_layout_name(LabelExecCountName, !IO),
     io.write_string(",\n", !IO),
     (
-        MaybeEventSpecs = no,
+        MaybeEventSet = no,
+        io.write_string("NULL,\n", !IO),
         io.write_string("NULL", !IO)
     ;
-        MaybeEventSpecs = yes(_),
+        MaybeEventSet = yes(EventSetName - _),
+        quote_and_write_string(EventSetName, !IO),
+        io.write_string(",\n", !IO),
         EventSpecLayoutName = module_layout_event_specs(ModuleName),
         output_layout_name(EventSpecLayoutName, !IO)
     ),
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.152
diff -u -b -r1.152 liveness.m
--- compiler/liveness.m	1 Dec 2006 15:04:03 -0000	1.152
+++ compiler/liveness.m	4 Dec 2006 03:40:48 -0000
@@ -325,7 +325,10 @@
     ),
 
     globals.get_trace_level(Globals, TraceLevel),
-    ( eff_trace_level_is_none(PredInfo, !.ProcInfo, TraceLevel) = no ->
+    (
+        eff_trace_level_needs_fail_vars(ModuleInfo, PredInfo, !.ProcInfo,
+            TraceLevel) = yes
+    ->
         trace_fail_vars(ModuleInfo, !.ProcInfo, ResumeVars0)
     ;
         set.init(ResumeVars0)
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.416
diff -u -b -r1.416 mercury_compile.m
--- compiler/mercury_compile.m	1 Dec 2006 15:04:06 -0000	1.416
+++ compiler/mercury_compile.m	4 Dec 2006 03:40:48 -0000
@@ -1729,24 +1729,27 @@
     maybe_grab_optfiles(ModuleImports0, Verbose, MaybeTransOptDeps,
         ModuleImports1, IntermodError, !IO),
 
-    globals.lookup_string_option(Globals, event_spec_file_name,
-        EventSpecFileName),
-    ( EventSpecFileName = "" ->
+    globals.lookup_string_option(Globals, event_set_file_name,
+        EventSetFileName),
+    ( EventSetFileName = "" ->
+        EventSetName = "",
         EventSpecMap1 = map.init,
-        EventSpecErrors = no
+        EventSetErrors = no
     ;
-        read_event_specs(EventSpecFileName, EventSpecMap0, EventSpecErrorSpecs,
-            !IO),
+        read_event_set(EventSetFileName, EventSetName0, EventSpecMap0,
+            EventSetErrorSpecs, !IO),
         (
-            EventSpecErrorSpecs = [],
+            EventSetErrorSpecs = [],
+            EventSetName = EventSetName0,
             EventSpecMap1 = EventSpecMap0,
-            EventSpecErrors = no
+            EventSetErrors = no
         ;
-            EventSpecErrorSpecs = [_ | _],
+            EventSetErrorSpecs = [_ | _],
+            EventSetName = "",
             EventSpecMap1 = map.init,
-            EventSpecErrors = yes,
+            EventSetErrors = yes,
             % XXX _NumErrors
-            write_error_specs(EventSpecErrorSpecs, Globals,
+            write_error_specs(EventSetErrorSpecs, Globals,
                 0, _EventSpecNumWarnings, 0, _EventSpecNumErrors, !IO)
         )
     ),
@@ -1755,7 +1758,7 @@
     MaybeTimestamps = ModuleImports1 ^ maybe_timestamps,
 
     invoke_module_qualify_items(Items1, Items2, EventSpecMap1, EventSpecMap2,
-        ModuleName, EventSpecFileName, Verbose, Stats, MQInfo0,
+        ModuleName, EventSetFileName, Verbose, Stats, MQInfo0,
         MQUndefTypes, MQUndefModes, !IO),
 
     mq_info_get_recompilation_info(MQInfo0, RecompInfo0),
@@ -1774,11 +1777,12 @@
             0, _ExpandNumWarnings, 0, _ExpandNumErrors, !IO)
     ),
 
-    make_hlds(ModuleName, Items, EventSpecMap, MQInfo, EqvMap, UsedModules,
+    EventSet = event_set(EventSetName, EventSpecMap),
+    make_hlds(ModuleName, Items, EventSet, MQInfo, EqvMap, UsedModules,
         Verbose, Stats, HLDS0, QualInfo,
         MakeHLDSUndefTypes, MakeHLDSUndefModes, FoundError, !IO),
 
-    bool.or_list([MQUndefTypes, EventSpecErrors, CircularTypes,
+    bool.or_list([MQUndefTypes, EventSetErrors, CircularTypes,
         MakeHLDSUndefTypes], UndefTypes),
     bool.or(MQUndefModes, MakeHLDSUndefModes, UndefModes),
 
@@ -1929,19 +1933,19 @@
     maybe_write_string(Verbose, " done.\n", !IO),
     maybe_report_stats(Stats, !IO).
 
-:- pred make_hlds(module_name::in, item_list::in, event_spec_map::in,
+:- pred make_hlds(module_name::in, item_list::in, event_set::in,
     mq_info::in, eqv_map::in, used_modules::in, bool::in, bool::in,
     module_info::out, make_hlds_qual_info::out,
     bool::out, bool::out, bool::out, io::di, io::uo) is det.
 
-make_hlds(Module, Items, EventSpecMap, MQInfo, EqvMap, UsedModules,
+make_hlds(Module, Items, EventSet, MQInfo, EqvMap, UsedModules,
         Verbose, Stats, !:HLDS, QualInfo,
         UndefTypes, UndefModes, FoundSemanticError, !IO) :-
     maybe_write_string(Verbose, "% Converting parse tree to hlds...\n", !IO),
     Prog = unit_module(Module, Items),
     parse_tree_to_hlds(Prog, MQInfo, EqvMap, UsedModules, !:HLDS, QualInfo,
         UndefTypes, UndefModes, !IO),
-    module_info_set_event_spec_map(EventSpecMap, !HLDS),
+    module_info_set_event_set(EventSet, !HLDS),
     module_info_get_num_errors(!.HLDS, NumErrors),
     io.get_exit_status(Status, !IO),
     (
Index: compiler/modes.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/modes.m,v
retrieving revision 1.350
diff -u -b -r1.350 modes.m
--- compiler/modes.m	24 Nov 2006 03:48:04 -0000	1.350
+++ compiler/modes.m	1 Dec 2006 00:00:42 -0000
@@ -1522,7 +1522,8 @@
     ;
         GenericCall = event_call(EventName),
         mode_info_get_module_info(!.ModeInfo, ModuleInfo),
-        module_info_get_event_spec_map(ModuleInfo, EventSpecMap),
+        module_info_get_event_set(ModuleInfo, EventSet),
+        EventSpecMap = EventSet ^ event_set_spec_map,
         ( event_arg_modes(EventSpecMap, EventName, ModesPrime) ->
             Modes = ModesPrime
         ;
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.182
diff -u -b -r1.182 opt_debug.m
--- compiler/opt_debug.m	1 Dec 2006 15:04:12 -0000	1.182
+++ compiler/opt_debug.m	4 Dec 2006 03:40:49 -0000
@@ -462,6 +462,9 @@
 dump_layout_name(user_event_attr_names(ProcLabel, LabelNum)) = Str :-
     LabelStr = dump_label(internal_label(LabelNum, ProcLabel)),
     Str = "user_event_attr_names(" ++ LabelStr ++ ")".
+dump_layout_name(user_event_attr_var_nums(ProcLabel, LabelNum)) = Str :-
+    LabelStr = dump_label(internal_label(LabelNum, ProcLabel)),
+    Str = "user_event_attr_var_nums(" ++ LabelStr ++ ")".
 dump_layout_name(proc_layout(RttiProcLabel, _)) =
     "proc_layout(" ++ dump_rttiproclabel(RttiProcLabel) ++ ")".
 dump_layout_name(proc_layout_exec_trace(RttiProcLabel)) =
Index: compiler/optimize.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/optimize.m,v
retrieving revision 1.59
diff -u -b -r1.59 optimize.m
--- compiler/optimize.m	1 Dec 2006 15:04:12 -0000	1.59
+++ compiler/optimize.m	4 Dec 2006 03:40:49 -0000
@@ -336,9 +336,9 @@
         ;
             VeryVerbose = no
         ),
-        jumpopt_main(LayoutLabelSet, MayAlterRtti, ProcLabel, FullJumpopt,
-            Final, PessimizeTailCalls, CheckedNondetTailCalls, !C, !Instrs,
-            Mod1),
+        optimize_jumps_in_proc(LayoutLabelSet, MayAlterRtti, ProcLabel,
+            FullJumpopt, Final, PessimizeTailCalls, CheckedNondetTailCalls,
+            !C, !Instrs, Mod1),
         maybe_opt_debug(!.Instrs, !.C, "jump", "after jump opt",
             ProcLabel, !OptDebugInfo, !IO)
     ;
@@ -458,9 +458,9 @@
             ;
                 VeryVerbose = no
             ),
-            jumpopt_main(LayoutLabelSet, MayAlterRtti, ProcLabel, FullJumpopt,
-                Final, PessimizeTailCalls, CheckedNondetTailCalls, !C, !Instrs,
-                _Mod2),
+            optimize_jumps_in_proc(LayoutLabelSet, MayAlterRtti, ProcLabel,
+                FullJumpopt, Final, PessimizeTailCalls, CheckedNondetTailCalls,
+                !C, !Instrs, _Mod2),
             maybe_opt_debug(!.Instrs, !.C, "jump", "after jumps",
                 ProcLabel, !OptDebugInfo, !IO)
         ;
Index: compiler/options.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/options.m,v
retrieving revision 1.540
diff -u -b -r1.540 options.m
--- compiler/options.m	1 Dec 2006 15:04:13 -0000	1.540
+++ compiler/options.m	4 Dec 2006 03:40:49 -0000
@@ -241,7 +241,7 @@
     ;       infer_all
     ;       type_inference_iteration_limit
     ;       mode_inference_iteration_limit
-    ;       event_spec_file_name
+    ;       event_set_file_name
 
     % Compilation Model options
     ;       grade
@@ -1008,7 +1008,7 @@
     infer_all                           -   bool_special,
     type_inference_iteration_limit      -   int(60),
     mode_inference_iteration_limit      -   int(30),
-    event_spec_file_name                -   string("")
+    event_set_file_name                 -   string("")
 ]).
 option_defaults_2(compilation_model_option, [
     % Compilation model options (ones that affect binary compatibility).
@@ -1747,7 +1747,7 @@
 long_option("infer-det",            infer_det).
 long_option("type-inference-iteration-limit", type_inference_iteration_limit).
 long_option("mode-inference-iteration-limit", mode_inference_iteration_limit).
-long_option("event-spec-file-name", event_spec_file_name).
+long_option("event-set-file-name",  event_set_file_name).
 
 % compilation model options
 long_option("grade",                grade).
@@ -3312,7 +3312,7 @@
         "\tPerform at most <n> passes of type inference (default: 60).",
         "--mode-inference-iteration-limit <n>",
         "\tPerform at most <n> passes of mode inference (default: 30).",
-        "--event-spec-file-name <filename>",
+        "--event-set-file-name <filename>",
         "\tGet the specification of user-defined events from <filename>."
     ]).
 
Index: compiler/proc_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/proc_gen.m,v
retrieving revision 1.11
diff -u -b -r1.11 proc_gen.m
--- compiler/proc_gen.m	1 Dec 2006 15:04:15 -0000	1.11
+++ compiler/proc_gen.m	4 Dec 2006 04:46:51 -0000
@@ -347,9 +347,10 @@
     globals.get_trace_level(Globals, TraceLevel),
     code_info.get_created_temp_frame(CodeInfo, CreatedTempFrame),
 
-    EffTraceIsNone = eff_trace_level_is_none(PredInfo, ProcInfo, TraceLevel),
+    code_info.get_proc_trace_events(CodeInfo, ProcTraceEvents),
+    % You can have user trace events even if the effective trace level is none.
     (
-        EffTraceIsNone = no,
+        ProcTraceEvents =  yes,
         CreatedTempFrame = yes,
         CodeModel \= model_non
     ->
@@ -376,8 +377,7 @@
         % The set of recorded live values at calls (for value numbering)
         % and returns (for accurate gc and execution tracing) do not yet record
         % the stack slot holding the succip, so add it to those sets.
-        add_saved_succip(Instructions0,
-            SuccipSlot, Instructions)
+        add_saved_succip(Instructions0, SuccipSlot, Instructions)
     ;
         MaybeSuccipSlot = no,
         Instructions = Instructions0
@@ -390,8 +390,7 @@
         )
     ->
         % Create the procedure layout structure.
-        RttiProcLabel = rtti.make_rtti_proc_label(ModuleInfo,
-            PredId, ProcId),
+        RttiProcLabel = rtti.make_rtti_proc_label(ModuleInfo, PredId, ProcId),
         code_info.get_layout_info(CodeInfo, InternalMap),
         EntryLabel = make_local_entry_label(ModuleInfo, PredId, ProcId, no),
         proc_info_get_eval_method(ProcInfo, EvalMethod),
@@ -402,14 +401,14 @@
         proc_info_get_vartypes(ProcInfo, VarTypes),
         globals.get_trace_suppress(Globals, TraceSuppress),
         (
-            eff_trace_needs_proc_body_reps(PredInfo, ProcInfo,
+            eff_trace_needs_proc_body_reps(ModuleInfo, PredInfo, ProcInfo,
                 TraceLevel, TraceSuppress) = yes
         ->
             NeedGoalRep = yes
         ;
             NeedGoalRep = no
         ),
-        NeedsAllNames = eff_trace_needs_all_var_names(PredInfo,
+        NeedsAllNames = eff_trace_needs_all_var_names(ModuleInfo, PredInfo,
             ProcInfo, TraceLevel, TraceSuppress),
         proc_info_get_maybe_deep_profile_info(ProcInfo,
             MaybeHLDSDeepInfo),
@@ -422,7 +421,8 @@
             MaybeHLDSDeepInfo = no,
             MaybeDeepProfInfo = no
         ),
-        EffTraceLevel = eff_trace_level(PredInfo, ProcInfo, TraceLevel),
+        EffTraceLevel = eff_trace_level(ModuleInfo, PredInfo, ProcInfo,
+            TraceLevel),
         ProcLayout = proc_layout_info(RttiProcLabel, EntryLabel,
             Detism, TotalSlots, MaybeSuccipSlot, EvalMethod,
             EffTraceLevel, MaybeTraceCallLabel, MaxTraceReg,
@@ -446,11 +446,12 @@
     Arity = pred_info_orig_arity(PredInfo),
 
     code_info.get_label_counter(CodeInfo, LabelCounter),
+    % You can have user trace events even if the effective trace level is none.
     (
-        EffTraceIsNone = yes,
+        ProcTraceEvents = no,
         MayAlterRtti = may_alter_rtti
     ;
-        EffTraceIsNone = no,
+        ProcTraceEvents = yes,
         MayAlterRtti = must_not_alter_rtti
     ),
 
@@ -669,22 +670,12 @@
         code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
         (
             MaybeTraceInfo = yes(TraceInfo),
-            generate_external_event_code(external_port_call, TraceInfo,
-                ProcContext, MaybeCallExternalInfo, !CI),
-            (
-                MaybeCallExternalInfo = yes(CallExternalInfo),
-                CallExternalInfo = external_event_info(TraceCallLabel, _,
-                    TraceCallCode)
-            ;
-                MaybeCallExternalInfo = no,
-                unexpected(this_file,
-                    "generate_category_code: call events suppressed")
-            ),
-            MaybeTraceCallLabel = yes(TraceCallLabel)
+            generate_call_event(TraceInfo, ProcContext, MaybeTraceCallLabel,
+                TraceCallCode, !CI)
         ;
             MaybeTraceInfo = no,
-            TraceCallCode = empty,
-            MaybeTraceCallLabel = no
+            MaybeTraceCallLabel = no,
+            TraceCallCode = empty
         ),
         generate_goal(model_det, Goal, BodyCode, !CI),
         generate_entry(!.CI, model_det, Goal, ResumePoint, FrameInfo,
@@ -705,18 +696,8 @@
     code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
     (
         MaybeTraceInfo = yes(TraceInfo),
-        generate_external_event_code(external_port_call, TraceInfo,
-            ProcContext, MaybeCallExternalInfo, !CI),
-        (
-            MaybeCallExternalInfo = yes(CallExternalInfo),
-            CallExternalInfo = external_event_info(TraceCallLabel, _,
-                TraceCallCode)
-        ;
-            MaybeCallExternalInfo = no,
-            unexpected(this_file,
-                "generate_category_code: call events suppressed")
-        ),
-        MaybeTraceCallLabel = yes(TraceCallLabel),
+        generate_call_event(TraceInfo, ProcContext, MaybeTraceCallLabel,
+            TraceCallCode, !CI),
         generate_goal(model_semi, Goal, BodyCode, !CI),
         generate_entry(!.CI, model_semi, Goal, ResumePoint,
             FrameInfo, EntryCode),
@@ -758,18 +739,8 @@
     code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
     (
         MaybeTraceInfo = yes(TraceInfo),
-        generate_external_event_code(external_port_call, TraceInfo,
-            ProcContext, MaybeCallExternalInfo, !CI),
-        (
-            MaybeCallExternalInfo = yes(CallExternalInfo),
-            CallExternalInfo = external_event_info(TraceCallLabel, _,
-                TraceCallCode)
-        ;
-            MaybeCallExternalInfo = no,
-            unexpected(this_file,
-                "generate_category_code: call events suppressed")
-        ),
-        MaybeTraceCallLabel = yes(TraceCallLabel),
+        generate_call_event(TraceInfo, ProcContext, MaybeTraceCallLabel,
+            TraceCallCode, !CI),
         generate_goal(model_non, Goal, BodyCode, !CI),
         generate_entry(!.CI, model_non, Goal, ResumePoint,
             FrameInfo, EntryCode),
@@ -831,6 +802,26 @@
         Code = tree_list([EntryCode, BodyCode, ExitCode])
     ).
 
+:- pred generate_call_event(trace_info::in, prog_context::in,
+    maybe(label)::out, code_tree::out, code_info::in, code_info::out) is det.
+
+generate_call_event(TraceInfo, ProcContext, MaybeTraceCallLabel, TraceCallCode,
+        !CI) :-
+    generate_external_event_code(external_port_call, TraceInfo,
+        ProcContext, MaybeCallExternalInfo, !CI),
+    (
+        MaybeCallExternalInfo = yes(CallExternalInfo),
+        CallExternalInfo = external_event_info(TraceCallLabel, _,
+            TraceCallCode),
+        MaybeTraceCallLabel = yes(TraceCallLabel)
+    ;
+        MaybeCallExternalInfo = no,
+        % This can happen for procedures containing user events
+        % in shallow traced modules.
+        TraceCallCode = empty,
+        MaybeTraceCallLabel = no
+    ).
+
 %---------------------------------------------------------------------------%
 
     % Generate the prologue for a procedure.
Index: compiler/prog_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_data.m,v
retrieving revision 1.179
diff -u -b -r1.179 prog_data.m
--- compiler/prog_data.m	24 Nov 2006 03:48:08 -0000	1.179
+++ compiler/prog_data.m	30 Nov 2006 23:54:34 -0000
@@ -1582,6 +1582,12 @@
     % This type maps the name of an event to the event's specification.
 :- type event_spec_map == map(string, event_spec).
 
+:- type event_set
+    --->    event_set(
+                event_set_name              :: string,
+                event_set_spec_map          :: event_spec_map
+            ).
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
Index: compiler/prog_event.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_event.m,v
retrieving revision 1.4
diff -u -b -r1.4 prog_event.m
--- compiler/prog_event.m	26 Nov 2006 22:40:39 -0000	1.4
+++ compiler/prog_event.m	1 Dec 2006 04:41:58 -0000
@@ -23,13 +23,13 @@
 :- import_module io.
 :- import_module list.
 
-    % read_event_specs(FileName, EventSpecMap, ErrorSpecs, !IO):
+    % read_event_set(FileName, EventSetName, EventSpecMap, ErrorSpecs, !IO):
     %
     % Read in a set of event specifications from FileName, and return them
-    % in EventSpecMap. Set ErrorSpecs to a list of all the errors discovered
-    % during the process.
+    % in EventSetName and EventSpecMap. Set ErrorSpecs to a list of all the
+    % errors discovered during the process.
     %
-:- pred read_event_specs(string::in, event_spec_map::out,
+:- pred read_event_set(string::in, string::out, event_spec_map::out,
     list(error_spec)::out, io::di, io::uo) is det.
 
     % Return a description of the given event set.
@@ -76,7 +76,7 @@
 :- import_module svrelation.
 :- import_module term.
 
-read_event_specs(SpecsFileName, EventSpecMap, ErrorSpecs, !IO) :-
+read_event_set(SpecsFileName, EventSetName, EventSpecMap, ErrorSpecs, !IO) :-
     % Currently, we convert the event specification file into a Mercury term
     % by using the yacc parser in the trace directory to create a C data
     % structure to represent its contents, writing out that data structure
@@ -98,11 +98,13 @@
             TermOpenRes = ok(TermStream),
             io.read(TermStream, TermReadRes, !IO),
             (
-                TermReadRes = ok(EventSpecsTerm),
+                TermReadRes = ok(EventSetTerm),
+                EventSetTerm = event_set_spec(EventSetName, EventSpecsTerm),
                 convert_list_to_spec_map(TermFileName, EventSpecsTerm,
                     map.init, EventSpecMap, [], ErrorSpecs)
             ;
                 TermReadRes = eof,
+                EventSetName = "",
                 EventSpecMap = map.init,
                 Pieces = [words("eof in term specification file"), nl],
                 ErrorSpec = error_spec(severity_error,
@@ -111,6 +113,7 @@
                 ErrorSpecs = [ErrorSpec]
             ;
                 TermReadRes = error(TermReadMsg, LineNumber),
+                EventSetName = "",
                 EventSpecMap = map.init,
                 Pieces = [words(TermReadMsg), nl],
                 ErrorSpec = error_spec(severity_error,
@@ -122,6 +125,7 @@
             io.close_input(TermStream, !IO)
         ;
             TermOpenRes = error(TermOpenError),
+            EventSetName = "",
             EventSpecMap = map.init,
             Pieces = [words(io.error_message(TermOpenError)), nl],
             ErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
@@ -129,6 +133,7 @@
             ErrorSpecs = [ErrorSpec]
         )
     ;
+        EventSetName = "",
         EventSpecMap = map.init,
         Pieces = [words(Problem), nl],
         ErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
@@ -202,9 +207,12 @@
                     sprintf(buf, ""could not read in %s"", SpecsFileName);
                     MR_make_aligned_string_copy(Problem, buf);
                 } else {
+                    MR_EventSet event_set;
+
                     /* NULL terminate the string we have read in. */
                     spec_buf[num_bytes_read] = '\\0';
-                    if (! MR_read_event_specs(spec_buf)) {
+                    event_set = MR_read_event_set(spec_buf);
+                    if (event_set == NULL) {
                         char    buf[4096];
 
                         sprintf(buf, ""could not parse %s"", SpecsFileName);
@@ -218,7 +226,7 @@
                                 TermFileName, strerror(errno));
                             MR_make_aligned_string_copy(Problem, buf);
                         } else {
-                            MR_print_event_specs(term_fp);
+                            MR_print_event_set(term_fp, event_set);
                             fclose(term_fp);
 
                             /*
@@ -241,6 +249,12 @@
 
 %-----------------------------------------------------------------------------%
 
+:- type event_set_spec
+    --->    event_set_spec(
+                event_set_name  :: string,
+                event_set_specs :: list(event_spec_term)
+            ).
+
 :- type event_spec_term
     --->    event_spec_term(
                 event_name      :: string,
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.198
diff -u -b -r1.198 simplify.m
--- compiler/simplify.m	9 Nov 2006 00:47:24 -0000	1.198
+++ compiler/simplify.m	1 Dec 2006 13:14:33 -0000
@@ -59,7 +59,7 @@
 
 :- pred simplify_proc_return_msgs(simplifications::in, pred_id::in,
     proc_id::in, module_info::in, module_info::out,
-    proc_info::in, proc_info::out, list(error_spec)::out, bool::out,
+    proc_info::in, proc_info::out, list(error_spec)::out,
     io::di, io::uo) is det.
 
 :- pred simplify_process_clause_body_goal(hlds_goal::in, hlds_goal::out,
@@ -324,12 +324,32 @@
 simplify_procs(_, _, [], !ModuleInfo, !PredInfo, !MaybeSpecs, !IO).
 simplify_procs(Simplifications, PredId, [ProcId | ProcIds], !ModuleInfo,
         !PredInfo, !MaybeSpecs, !IO) :-
-    pred_info_get_procedures(!.PredInfo, Procs0),
-    map.lookup(Procs0, ProcId, Proc0),
+    pred_info_get_procedures(!.PredInfo, ProcTable0),
+    map.lookup(ProcTable0, ProcId, ProcInfo0),
     simplify_proc_return_msgs(Simplifications, PredId, ProcId,
-        !ModuleInfo, Proc0, Proc, ProcSpecs, MayHaveParallelConj, !IO),
-    map.det_update(Procs0, ProcId, Proc, Procs),
-    pred_info_set_procedures(Procs, !PredInfo),
+        !ModuleInfo, ProcInfo0, ProcInfo, ProcSpecs, !IO),
+    % This is ugly, but we want to avoid running the dependent parallel
+    % conjunction pass on predicates and even modules that do not contain
+    % parallel conjunctions (nearly all of them).  Since simplification
+    % is always done, we use it to mark modules and procedures containing
+    % parallel conjunctions.
+    proc_info_get_has_parallel_conj(ProcInfo, HasParallelConj),
+    (
+        HasParallelConj = yes,
+        module_info_set_contains_par_conj(!ModuleInfo)
+    ;
+        HasParallelConj = no
+    ),
+    proc_info_get_has_user_event(ProcInfo, HasUserEvent),
+    (
+        HasUserEvent = yes,
+        module_info_set_contains_user_event(!ModuleInfo)
+    ;
+        HasUserEvent = no
+    ),
+    map.det_update(ProcTable0, ProcId, ProcInfo, ProcTable),
+    pred_info_set_procedures(ProcTable, !PredInfo),
+
     list.filter((pred(error_spec(_, Phase, _)::in) is semidet :-
             Phase = phase_simplify(report_only_if_in_all_modes)
         ), ProcSpecs, ProcAllModeSpecs, ProcAnyModeSpecs),
@@ -344,34 +364,20 @@
         !.MaybeSpecs = no,
         !:MaybeSpecs = yes(ProcAnyModeSpecSet - ProcAllModeSpecSet)
     ),
-    % This is ugly, but we want to avoid running the dependent parallel
-    % conjunction pass on predicates and even modules that do not contain
-    % parallel conjunctions (nearly all of them).  Since simplification
-    % is always done, we use it to mark modules and predicates containing
-    % parallel conjunctions.
-    (
-        MayHaveParallelConj = yes,
-        module_info_set_contains_par_conj(!ModuleInfo),
-        pred_info_get_markers(!.PredInfo, Markers0),
-        add_marker(marker_may_have_parallel_conj, Markers0, Markers),
-        pred_info_set_markers(Markers, !PredInfo)
-    ;
-        MayHaveParallelConj = no
-    ),
     simplify_procs(Simplifications, PredId, ProcIds, !ModuleInfo, !PredInfo,
         !MaybeSpecs, !IO).
 
-simplify_proc(Simplifications, PredId, ProcId, !ModuleInfo, !Proc, !IO)  :-
+simplify_proc(Simplifications, PredId, ProcId, !ModuleInfo, !ProcInfo, !IO)  :-
     write_pred_progress_message("% Simplifying ", PredId, !.ModuleInfo, !IO),
     simplify_proc_return_msgs(Simplifications, PredId, ProcId, !ModuleInfo,
-        !Proc, _, _, !IO).
+        !ProcInfo, _, !IO).
 
 :- func turn_off_common_struct_threshold = int.
 
 turn_off_common_struct_threshold = 1000.
 
 simplify_proc_return_msgs(Simplifications0, PredId, ProcId, !ModuleInfo,
-        !ProcInfo, ErrorSpecs, MayHaveParallelConj, !IO) :-
+        !ProcInfo, ErrorSpecs, !IO) :-
     proc_info_get_vartypes(!.ProcInfo, VarTypes0),
     NumVars = map.count(VarTypes0),
     ( NumVars > turn_off_common_struct_threshold ->
@@ -413,6 +419,13 @@
     proc_info_set_vartypes(VarTypes, !ProcInfo),
     proc_info_set_goal(Goal, !ProcInfo),
     proc_info_set_rtti_varmaps(RttiVarMaps, !ProcInfo),
+
+    simplify_info_get_has_parallel_conj(Info, HasParallelConj),
+    proc_info_set_has_parallel_conj(HasParallelConj, !ProcInfo),
+
+    simplify_info_get_has_user_event(Info, HasUserEvent),
+    proc_info_set_has_user_event(HasUserEvent, !ProcInfo),
+
     simplify_info_get_module_info(Info, !:ModuleInfo),
     simplify_info_get_error_specs(Info, ErrorSpecs0),
     (
@@ -445,8 +458,7 @@
     ;
         IsDefinedHere = yes,
         ErrorSpecs = ErrorSpecs1
-    ),
-    simplify_info_get_may_have_parallel_conj(Info, MayHaveParallelConj).
+    ).
 
 simplify_process_clause_body_goal(Goal0, Goal, !Info, !IO) :-
     simplify_info_get_simplifications(!.Info, Simplifications0),
@@ -818,7 +830,7 @@
             GoalInfo = GoalInfo0,
             simplify_par_conj(Goals0, Goals, !.Info, !Info, !IO),
             Goal = conj(parallel_conj, Goals),
-            simplify_info_set_may_have_parallel_conj(yes, !Info)
+            simplify_info_set_has_parallel_conj(yes, !Info)
         )
     ).
 
@@ -985,10 +997,11 @@
 simplify_goal_2(Goal0, Goal, GoalInfo, GoalInfo, !Info, !IO) :-
     Goal0 = generic_call(GenericCall, Args, Modes, Det),
     (
+        GenericCall = higher_order(Closure, Purity, _, _),
+        (
         simplify_do_opt_duplicate_calls(!.Info),
         % XXX We should do duplicate call elimination for
         % class method calls here.
-        GenericCall = higher_order(Closure, Purity, _, _),
         % XXX Should we handle semipure higher-order calls too?
         Purity = purity_pure
     ->
@@ -996,7 +1009,6 @@
             GoalInfo, Goal0, Goal, !Info)
     ;
         simplify_do_warn_duplicate_calls(!.Info),
-        GenericCall = higher_order(Closure, Purity, _, _),
         % XXX Should we handle impure/semipure higher-order calls too?
         Purity = purity_pure
     ->
@@ -1007,6 +1019,16 @@
         Goal = Goal0
     ;
         Goal = Goal0
+        )
+    ;
+        GenericCall = event_call(_),
+        simplify_info_set_has_user_event(yes, !Info),
+        Goal = Goal0
+    ;
+        ( GenericCall = class_method(_, _, _, _)
+        ; GenericCall = cast(_)
+        ),
+        Goal = Goal0
     ).
 
 simplify_goal_2(Goal0, Goal, GoalInfo0, GoalInfo, !Info, !IO) :-
@@ -1569,7 +1591,8 @@
         Base = trace_trace_level(Level),
         globals.get_trace_level(Globals, TraceLevel),
         simplify_info_get_pred_proc_info(Info, PredInfo, ProcInfo),
-        EffTraceLevel = eff_trace_level(PredInfo, ProcInfo, TraceLevel),
+        EffTraceLevel = eff_trace_level(ModuleInfo, PredInfo, ProcInfo,
+            TraceLevel),
         (
             Level = trace_level_shallow,
             Result = at_least_at_shallow(EffTraceLevel)
@@ -2782,11 +2805,13 @@
                 inside_dupl_for_switch  :: bool,
                                         % Are we currently inside a goal
                                         % that was duplicated for a switch?
-                may_have_parallel_conj  :: bool,
+                has_parallel_conj       :: bool,
                                         % Have we seen a parallel conjunction?
-                found_contains_trace    :: bool
+                found_contains_trace    :: bool,
                                         % Have we seen a goal with a feature
                                         % that says it contains a trace goal?
+                has_user_event          :: bool
+                                        % Have we seen an event call?
             ).
 
 simplify_info_init(DetInfo, Simplifications, InstMap, ProcInfo, Info) :-
@@ -2795,7 +2820,7 @@
     proc_info_get_rtti_varmaps(ProcInfo, RttiVarMaps),
     Info = simplify_info(DetInfo, [], Simplifications,
         common_info_init, InstMap, VarSet, InstVarSet,
-        no, no, no, 0, 0, RttiVarMaps, no, no, no, no).
+        no, no, no, 0, 0, RttiVarMaps, no, no, no, no, no).
 
     % Reinitialise the simplify_info before reprocessing a goal.
     %
@@ -2810,7 +2835,8 @@
     !:Info = !.Info ^ recompute_atomic := no,
     !:Info = !.Info ^ rerun_det := no,
     !:Info = !.Info ^ lambdas := 0,
-    !:Info = !.Info ^ may_have_parallel_conj := no.
+    !:Info = !.Info ^ has_parallel_conj := no,
+    !:Info = !.Info ^ has_user_event := no.
 
     % exported for common.m
 :- interface.
@@ -2865,10 +2891,11 @@
 :- pred simplify_info_get_format_calls(simplify_info::in, bool::out) is det.
 :- pred simplify_info_get_inside_duplicated_for_switch(simplify_info::in,
     bool::out) is det.
-:- pred simplify_info_get_may_have_parallel_conj(simplify_info::in, bool::out)
+:- pred simplify_info_get_has_parallel_conj(simplify_info::in, bool::out)
     is det.
 :- pred simplify_info_get_found_contains_trace(simplify_info::in, bool::out)
     is det.
+:- pred simplify_info_get_has_user_event(simplify_info::in, bool::out) is det.
 
 simplify_info_get_det_info(Info, Info ^ det_info).
 simplify_info_get_error_specs(Info, Info ^ error_specs).
@@ -2889,8 +2916,9 @@
 simplify_info_get_format_calls(Info, Info ^ format_calls).
 simplify_info_get_inside_duplicated_for_switch(Info,
     Info ^ inside_dupl_for_switch).
-simplify_info_get_may_have_parallel_conj(Info, Info ^ may_have_parallel_conj).
+simplify_info_get_has_parallel_conj(Info, Info ^ has_parallel_conj).
 simplify_info_get_found_contains_trace(Info, Info ^ found_contains_trace).
+simplify_info_get_has_user_event(Info, Info ^ has_user_event).
 
 simplify_info_get_module_info(Info, ModuleInfo) :-
     simplify_info_get_det_info(Info, DetInfo),
@@ -2928,10 +2956,12 @@
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_inside_duplicated_for_switch(bool::in,
     simplify_info::in, simplify_info::out) is det.
-:- pred simplify_info_set_may_have_parallel_conj(bool::in,
+:- pred simplify_info_set_has_parallel_conj(bool::in,
     simplify_info::in, simplify_info::out) is det.
 :- pred simplify_info_set_found_contains_trace(bool::in,
     simplify_info::in, simplify_info::out) is det.
+:- pred simplify_info_set_has_user_event(bool::in,
+    simplify_info::in, simplify_info::out) is det.
 
 :- pred simplify_info_add_error_spec(error_spec::in,
     simplify_info::in, simplify_info::out) is det.
@@ -2963,10 +2993,11 @@
 simplify_info_set_format_calls(FC, Info, Info ^ format_calls := FC).
 simplify_info_set_inside_duplicated_for_switch(IDFS, Info,
     Info ^ inside_dupl_for_switch := IDFS).
-simplify_info_set_may_have_parallel_conj(MHPC, Info,
-    Info ^ may_have_parallel_conj := MHPC).
+simplify_info_set_has_parallel_conj(MHPC, Info,
+    Info ^ has_parallel_conj := MHPC).
 simplify_info_set_found_contains_trace(FCT, Info,
     Info ^ found_contains_trace := FCT).
+simplify_info_set_has_user_event(HUE, Info, Info ^ has_user_event := HUE).
 
 simplify_info_incr_cost_delta(Incr, Info,
     Info ^ cost_delta := Info ^ cost_delta + Incr).
Index: compiler/size_prof.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/size_prof.m,v
retrieving revision 1.49
diff -u -b -r1.49 size_prof.m
--- compiler/size_prof.m	1 Dec 2006 15:04:20 -0000	1.49
+++ compiler/size_prof.m	4 Dec 2006 03:40:50 -0000
@@ -237,7 +237,7 @@
 process_proc(Transform, PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
     Simplifications = list_to_simplifications([]),
     simplify_proc_return_msgs(Simplifications, PredId, ProcId,
-        !ModuleInfo, !ProcInfo, _Msgs, _MayHaveParallelConj, !IO),
+        !ModuleInfo, !ProcInfo, _Msgs, !IO),
 
     proc_info_get_goal(!.ProcInfo, Goal0),
     proc_info_get_varset(!.ProcInfo, VarSet0),
Index: compiler/stack_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_alloc.m,v
retrieving revision 1.21
diff -u -b -r1.21 stack_alloc.m
--- compiler/stack_alloc.m	1 Dec 2006 15:04:20 -0000	1.21
+++ compiler/stack_alloc.m	4 Dec 2006 03:40:51 -0000
@@ -69,8 +69,8 @@
     module_info_get_globals(ModuleInfo, Globals),
     globals.get_trace_level(Globals, TraceLevel),
     (
-        eff_trace_level_needs_input_vars(PredInfo, !.ProcInfo, TraceLevel)
-            = yes
+        eff_trace_level_needs_fail_vars(ModuleInfo, PredInfo, !.ProcInfo,
+            TraceLevel) = yes
     ->
         trace_fail_vars(ModuleInfo, !.ProcInfo, FailVars)
     ;
@@ -90,7 +90,7 @@
     proc_info_set_goal(Goal, !ProcInfo),
     SimpleStackAlloc = stack_alloc(LiveSets0),
 
-    do_we_need_maxfr_slot(Globals, PredInfo, !ProcInfo),
+    do_we_need_maxfr_slot(Globals, ModuleInfo, PredInfo, !ProcInfo),
     trace_reserved_slots(ModuleInfo, PredInfo, !.ProcInfo, Globals,
         NumReservedSlots, MaybeReservedVarInfo),
     (
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.127
diff -u -b -r1.127 stack_layout.m
--- compiler/stack_layout.m	1 Dec 2006 15:04:20 -0000	1.127
+++ compiler/stack_layout.m	4 Dec 2006 03:40:51 -0000
@@ -171,16 +171,17 @@
         HasUserEvent = LayoutInfo ^ has_user_event,
         (
             HasUserEvent = no,
-            MaybeEventSpecs = no
+            MaybeEventSet = no
         ;
             HasUserEvent = yes,
-            module_info_get_event_spec_map(ModuleInfo, EventSpecMap),
+            module_info_get_event_set(ModuleInfo, EventSet),
+            EventSet = event_set(EventSetName, EventSpecMap),
             EventSpecs = event_set_description(EventSpecMap),
-            MaybeEventSpecs = yes(EventSpecs)
+            MaybeEventSet = yes(EventSetName - EventSpecs)
         ),
         ModuleLayout = module_layout_data(ModuleName,
             StringOffset, ConcatStrings, ProcLayoutNames, SourceFileLayouts,
-            TraceLevel, SuppressedEvents, NumLabels, MaybeEventSpecs),
+            TraceLevel, SuppressedEvents, NumLabels, MaybeEventSet),
         Layouts = [ModuleLayout | Layouts0]
     ;
         TraceLayout = no,
@@ -204,6 +205,7 @@
     % concat_string_list appends a list of strings together,
     % appending a null character after each string.
     % The resulting string will contain embedded null characters,
+    %
 :- pred concat_string_list(list(string)::in, int::in,
     string_with_0s::out) is det.
 
@@ -379,7 +381,7 @@
 %---------------------------------------------------------------------------%
 
     % Add the given label layout to the module-wide label tables.
-
+    %
 :- pred update_label_table(
     {proc_label, int, label_vars, internal_layout_info}::in,
     map(string, label_table)::in, map(string, label_table)::out) is det.
@@ -540,7 +542,7 @@
         _ForceProcIdLayout,
         VarSet,
         VarTypes,
-        _InternalMap,
+        InternalMap,
         MaybeTableInfo,
         NeedsAllNames,
         MaybeProcStatic),
@@ -554,7 +556,7 @@
         get_trace_stack_layout(!.Info, TraceStackLayout),
         (
             TraceStackLayout = yes,
-            given_trace_level_is_none(EffTraceLevel) = no,
+            not map.is_empty(InternalMap),
             valid_proc_layout(ProcLayoutInfo)
         ->
             construct_trace_layout(RttiProcLabel, EvalMethod, EffTraceLevel,
@@ -606,16 +608,10 @@
         prog_rep.represent_proc(HeadVars, Goal, InstMap, VarTypes, VarNumMap,
             ModuleInfo, !Info, ProcBytes)
     ),
-    (
-        MaybeCallLabel = yes(CallLabelPrime),
-        CallLabel = CallLabelPrime
-    ;
-        MaybeCallLabel = no,
-        unexpected(this_file,
-            "construct_trace_layout: call label not present")
-    ),
     TraceSlotInfo = trace_slot_info(MaybeFromFullSlot, MaybeIoSeqSlot,
         MaybeTrailSlots, MaybeMaxfrSlot, MaybeCallTableSlot),
+    (
+        MaybeCallLabel = yes(CallLabel),
     % The label associated with an event must have variable info.
     (
         CallLabel = internal_label(CallLabelNum, CallProcLabel)
@@ -624,8 +620,13 @@
         unexpected(this_file,
             "construct_trace_layout: entry call label")
     ),
-    CallLabelLayout = label_layout(CallProcLabel, CallLabelNum,
+        CallLabelDetails = label_layout_details(CallProcLabel, CallLabelNum,
         label_has_var_info),
+        MaybeCallLabelDetails = yes(CallLabelDetails)
+    ;
+        MaybeCallLabel = no,
+        MaybeCallLabelDetails = no
+    ),
     (
         MaybeTableInfo = no,
         MaybeTableDataAddr = no
@@ -644,7 +645,7 @@
     ),
     encode_exec_trace_flags(ModuleInfo, HeadVars, ArgModes, VarTypes,
         0, Flags),
-    ExecTrace = proc_layout_exec_trace(CallLabelLayout, ProcBytes,
+    ExecTrace = proc_layout_exec_trace(MaybeCallLabelDetails, ProcBytes,
         MaybeTableDataAddr, HeadVarNumVector, VarNameVector,
         MaxVarNum, MaxTraceReg, MaybeFromFullSlot, MaybeIoSeqSlot,
         MaybeTrailSlots, MaybeMaxfrSlot, EvalMethod,
@@ -728,20 +729,29 @@
             !VarNumMap, !Counter),
         list.foldl2(add_var_to_var_number_map(VarSet), HeadVars,
             !VarNumMap, !Counter),
-        list.foldl2(internal_var_number_map, Internals, !VarNumMap,
+        list.foldl2(internal_var_number_map(VarSet), Internals, !VarNumMap,
             !.Counter, _),
         VarNumMap = !.VarNumMap
     ).
 
-:- pred internal_var_number_map(pair(int, internal_layout_info)::in,
+:- pred internal_var_number_map(prog_varset::in,
+    pair(int, internal_layout_info)::in,
     var_num_map::in, var_num_map::out, counter::in, counter::out) is det.
 
-internal_var_number_map(_Label - Internal, !VarNumMap, !Counter) :-
+internal_var_number_map(VarSet, _Label - Internal, !VarNumMap, !Counter) :-
     Internal = internal_layout_info(MaybeTrace, MaybeResume, MaybeReturn),
     (
         MaybeTrace = yes(Trace),
-        Trace = trace_port_layout_info(_, _, _, _, _, TraceLayout),
-        label_layout_var_number_map(TraceLayout, !VarNumMap, !Counter)
+        Trace = trace_port_layout_info(_, _, _, _, MaybeUser, TraceLayout),
+        label_layout_var_number_map(TraceLayout, !VarNumMap, !Counter),
+        (
+            MaybeUser = no
+        ;
+            MaybeUser = yes(UserEvent),
+            UserEvent = user_event_info(_PortNum, _PortName, Attributes),
+            list.foldl2(user_attribute_var_num_map(VarSet), Attributes,
+                !VarNumMap, !Counter)
+        )
     ;
         MaybeTrace = no
     ),
@@ -773,6 +783,13 @@
     list.foldl2(add_named_var_to_var_number_map, VarsNames,
         !VarNumMap, !Counter).
 
+:- pred user_attribute_var_num_map(prog_varset::in, user_attribute::in,
+    var_num_map::in, var_num_map::out, counter::in, counter::out) is det.
+
+user_attribute_var_num_map(VarSet, Attribute, !VarNumMap, !Counter) :-
+    Attribute = user_attribute(_Locn, _Type, _Name, Var),
+    add_var_to_var_number_map(VarSet, Var, !VarNumMap, !Counter).
+
 :- pred add_var_to_var_number_map(prog_varset::in, prog_var::in,
     var_num_map::in, var_num_map::out, counter::in, counter::out) is det.
 
@@ -923,8 +940,9 @@
         UserInfo = user_event_info(UserEventNumber, UserEventName,
             Attributes),
         list.length(Attributes, NumAttributes),
-        construct_user_data_array(Attributes,
-            UserLocnsArray, UserTypesArray, UserAttrNames, !Info),
+        construct_user_data_array(VarNumMap, Attributes,
+            UserLocnsArray, UserTypesArray, UserAttrNames, UserAttrVarNums,
+            !Info),
 
         get_static_cell_info(!.Info, StaticCellInfo0),
         add_scalar_static_cell(UserLocnsArray, UserLocnsDataAddr,
@@ -936,7 +954,8 @@
         UserLocnsRval = const(llconst_data_addr(UserLocnsDataAddr, no)),
         UserTypesRval = const(llconst_data_addr(UserTypesDataAddr, no)),
         UserData = user_event_data(UserEventNumber, UserEventName,
-            NumAttributes, UserLocnsRval, UserTypesRval, UserAttrNames),
+            NumAttributes, UserLocnsRval, UserTypesRval, UserAttrNames,
+            UserAttrVarNums),
         MaybeUserData = yes(UserData)
     ),
 
@@ -963,15 +982,18 @@
     add_internal_layout_data(LayoutData, Label, LayoutName, !Info),
     LabelLayout = {ProcLabel, LabelNum, LabelVars, Internal}.
 
-:- pred construct_user_data_array(list(user_attribute)::in,
+:- pred construct_user_data_array(var_num_map::in, list(user_attribute)::in,
     assoc_list(rval, llds_type)::out, assoc_list(rval, llds_type)::out,
-    list(string)::out, stack_layout_info::in, stack_layout_info::out) is det.
+    list(string)::out, list(int)::out,
+    stack_layout_info::in, stack_layout_info::out) is det.
 
-construct_user_data_array([], [], [], [], !Info).
-construct_user_data_array([Attr | Attrs],
+construct_user_data_array(_, [], [], [], [], [], !Info).
+construct_user_data_array(VarNumMap, [Attr | Attrs],
         [LocnRvalAndType | LocnRvalAndTypes],
-        [TypeRvalAndType | TypeRvalAndTypes], [Name | Names], !Info) :-
-    Attr = user_attribute(Locn, Type, Name),
+        [TypeRvalAndType | TypeRvalAndTypes], [Name | Names],
+        [VarNum | VarNums], !Info) :-
+    Attr = user_attribute(Locn, Type, Name, Var),
+    convert_var_to_int(VarNumMap, Var, VarNum),
     represent_locn_or_const_as_int_rval(Locn, LocnRval, LocnRvalType, !Info),
     LocnRvalAndType = LocnRval - LocnRvalType,
 
@@ -984,8 +1006,8 @@
     set_static_cell_info(StaticCellInfo, !Info),
     TypeRvalAndType = TypeRval - TypeRvalType,
 
-    construct_user_data_array(Attrs, LocnRvalAndTypes, TypeRvalAndTypes,
-        Names, !Info).
+    construct_user_data_array(VarNumMap, Attrs, LocnRvalAndTypes,
+        TypeRvalAndTypes, Names, VarNums, !Info).
 
 %---------------------------------------------------------------------------%
 
Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.102
diff -u -b -r1.102 store_alloc.m
--- compiler/store_alloc.m	1 Dec 2006 15:04:21 -0000	1.102
+++ compiler/store_alloc.m	4 Dec 2006 03:40:51 -0000
@@ -89,7 +89,10 @@
     initial_liveness(!.ProcInfo, PredId, ModuleInfo, Liveness0),
     globals.get_trace_level(Globals, TraceLevel),
     module_info_pred_info(ModuleInfo, PredId, PredInfo),
-    ( eff_trace_level_is_none(PredInfo, !.ProcInfo, TraceLevel) = no ->
+    (
+        eff_trace_level_needs_fail_vars(ModuleInfo, PredInfo, !.ProcInfo,
+            TraceLevel) = yes
+    ->
         trace_fail_vars(ModuleInfo, !.ProcInfo, ResumeVars0)
     ;
         set.init(ResumeVars0)
Index: compiler/table_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/table_gen.m,v
retrieving revision 1.125
diff -u -b -r1.125 table_gen.m
--- compiler/table_gen.m	1 Dec 2006 15:04:22 -0000	1.125
+++ compiler/table_gen.m	4 Dec 2006 03:40:51 -0000
@@ -1895,7 +1895,6 @@
 keep_marker(marker_check_termination) = no.
 keep_marker(marker_calls_are_fully_qualified) = yes.
 keep_marker(marker_mode_check_clauses) = yes.
-keep_marker(marker_may_have_parallel_conj) = yes.
 keep_marker(marker_mutable_access_pred) = yes.
 
 %-----------------------------------------------------------------------------%
Index: compiler/trace_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/trace_gen.m,v
retrieving revision 1.9
diff -u -b -r1.9 trace_gen.m
--- compiler/trace_gen.m	24 Nov 2006 03:48:09 -0000	1.9
+++ compiler/trace_gen.m	1 Dec 2006 13:42:28 -0000
@@ -145,8 +145,8 @@
     % Figure out whether we need a slot for storing the value of maxfr
     % on entry, and record the result in the proc info.
     %
-:- pred do_we_need_maxfr_slot(globals::in, pred_info::in, proc_info::in,
-    proc_info::out) is det.
+:- pred do_we_need_maxfr_slot(globals::in, module_info::in, pred_info::in,
+    proc_info::in, proc_info::out) is det.
 
     % Return the number of slots reserved for tracing information.
     % If there are N slots, the reserved slots will be 1 through N.
@@ -296,11 +296,12 @@
         unexpected(this_file, "length mismatch in trace.fail_vars")
     ).
 
-do_we_need_maxfr_slot(Globals, PredInfo0, !ProcInfo) :-
+do_we_need_maxfr_slot(Globals, ModuleInfo, PredInfo0, !ProcInfo) :-
     globals.get_trace_level(Globals, TraceLevel),
     proc_info_interface_code_model(!.ProcInfo, CodeModel),
     (
-        eff_trace_level_is_none(PredInfo0, !.ProcInfo, TraceLevel) = no,
+        eff_trace_level_is_none(ModuleInfo, PredInfo0, !.ProcInfo, TraceLevel)
+            = no,
         CodeModel \= model_non,
         proc_info_get_goal(!.ProcInfo, Goal),
         code_util.goal_may_alloc_temp_frame(Goal, yes)
@@ -385,13 +386,13 @@
     % exist or not. This is why setup returns TraceSlotInfo, which answers
     % such questions, for later inclusion in the procedure's layout structure.
 
-trace_reserved_slots(_ModuleInfo, PredInfo, ProcInfo, Globals, ReservedSlots,
+trace_reserved_slots(ModuleInfo, PredInfo, ProcInfo, Globals, ReservedSlots,
         MaybeTableVarInfo) :-
     globals.get_trace_level(Globals, TraceLevel),
     globals.get_trace_suppress(Globals, TraceSuppress),
     globals.lookup_bool_option(Globals, trace_table_io, TraceTableIo),
-    FixedSlots = eff_trace_level_needs_fixed_slots(PredInfo, ProcInfo,
-        TraceLevel),
+    FixedSlots = eff_trace_level_needs_fixed_slots(ModuleInfo, PredInfo,
+        ProcInfo, TraceLevel),
     (
         FixedSlots = no,
         ReservedSlots = 0,
@@ -401,7 +402,7 @@
         Fixed = 3, % event#, call#, call depth
         (
             proc_info_interface_code_model(ProcInfo, model_non),
-            eff_trace_needs_port(PredInfo, ProcInfo, TraceLevel,
+            eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo, TraceLevel,
                 TraceSuppress, port_redo) = yes
         ->
             RedoLayout = 1
@@ -409,7 +410,7 @@
             RedoLayout = 0
         ),
         (
-            eff_trace_level_needs_from_full_slot(PredInfo,
+            eff_trace_level_needs_from_full_slot(ModuleInfo, PredInfo,
                 ProcInfo, TraceLevel) = yes
         ->
             FromFull = 1
@@ -452,14 +453,14 @@
         )
     ).
 
-trace_setup(_ModuleInfo, PredInfo, ProcInfo, Globals, TraceSlotInfo, TraceInfo,
+trace_setup(ModuleInfo, PredInfo, ProcInfo, Globals, TraceSlotInfo, TraceInfo,
         !CI) :-
     CodeModel = code_info.get_proc_model(!.CI),
     globals.get_trace_level(Globals, TraceLevel),
     globals.get_trace_suppress(Globals, TraceSuppress),
     globals.lookup_bool_option(Globals, trace_table_io, TraceTableIo),
-    TraceRedo = eff_trace_needs_port(PredInfo, ProcInfo, TraceLevel,
-        TraceSuppress, port_redo),
+    TraceRedo = eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo,
+        TraceLevel, TraceSuppress, port_redo),
     (
         TraceRedo = yes,
         CodeModel = model_non
@@ -471,7 +472,7 @@
         MaybeRedoLayoutLabel = no,
         NextSlotAfterRedoLayout = 4
     ),
-    FromFullSlot = eff_trace_level_needs_from_full_slot(PredInfo,
+    FromFullSlot = eff_trace_level_needs_from_full_slot(ModuleInfo, PredInfo,
         ProcInfo, TraceLevel),
     (
         FromFullSlot = no,
@@ -708,9 +709,10 @@
             unexpected(this_file, "generate_internal_event_code: bad path")
         ),
         (
+            code_info.get_module_info(!.CI, ModuleInfo),
             code_info.get_pred_info(!.CI, PredInfo),
             code_info.get_proc_info(!.CI, ProcInfo),
-            eff_trace_needs_port(PredInfo, ProcInfo,
+            eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo,
                 TraceInfo ^ trace_level,
                 TraceInfo ^ trace_suppress_items, Port) = yes
         ->
@@ -745,9 +747,10 @@
             NegPort = neg_success,
             Port = port_neg_success
         ),
+        code_info.get_module_info(!.CI, ModuleInfo),
         code_info.get_pred_info(!.CI, PredInfo),
         code_info.get_proc_info(!.CI, ProcInfo),
-        eff_trace_needs_port(PredInfo, ProcInfo,
+        eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo,
             TraceInfo ^ trace_level,
             TraceInfo ^ trace_suppress_items, Port) = yes
     ->
@@ -770,9 +773,10 @@
     (
         MaybeTraceInfo = yes(TraceInfo),
         Port = convert_nondet_pragma_port_type(PragmaPort),
+        code_info.get_module_info(!.CI, ModuleInfo),
         code_info.get_pred_info(!.CI, PredInfo),
         code_info.get_proc_info(!.CI, ProcInfo),
-        eff_trace_needs_port(PredInfo, ProcInfo,
+        eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo,
             TraceInfo ^ trace_level,
             TraceInfo ^ trace_suppress_items, Port) = yes
     ->
@@ -796,9 +800,10 @@
         MaybeExternalInfo, !CI) :-
     Port = convert_external_port_type(ExternalPort),
     (
+        code_info.get_module_info(!.CI, ModuleInfo),
         code_info.get_pred_info(!.CI, PredInfo),
         code_info.get_proc_info(!.CI, ProcInfo),
-        eff_trace_needs_port(PredInfo, ProcInfo,
+        eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo,
             TraceInfo ^ trace_level,
             TraceInfo ^ trace_suppress_items, Port) = yes
     ->
@@ -886,6 +891,7 @@
     ),
     code_info.add_trace_layout_for_label(Label, Context, Port, HideEvent,
         Path, MaybeUserInfo, LayoutLabelInfo, !CI),
+    code_info.set_proc_trace_events(yes, !CI),
     (
         Port = port_fail,
         MaybeTraceInfo = yes(TraceInfo),
Index: compiler/trace_params.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/trace_params.m,v
retrieving revision 1.38
diff -u -b -r1.38 trace_params.m
--- compiler/trace_params.m	1 Dec 2006 15:04:25 -0000	1.38
+++ compiler/trace_params.m	4 Dec 2006 04:10:31 -0000
@@ -36,6 +36,7 @@
 :- interface.
 
 :- import_module hlds.
+:- import_module hlds.hlds_module.
 :- import_module hlds.hlds_pred.
 :- import_module mdbcomp.prim_data.
 
@@ -80,29 +81,33 @@
     % These functions check for various properties of the given procedure's
     % effective trace level.
     %
-:- func eff_trace_level_is_none(pred_info, proc_info, trace_level) = bool.
-:- func eff_trace_level_needs_input_vars(pred_info, proc_info, trace_level)
-    = bool.
-:- func eff_trace_level_needs_fixed_slots(pred_info, proc_info, trace_level)
-    = bool.
-:- func eff_trace_level_needs_from_full_slot(pred_info, proc_info, trace_level)
-    = bool.
-:- func eff_trace_needs_all_var_names(pred_info, proc_info, trace_level,
-    trace_suppress_items) = bool.
-:- func eff_trace_needs_proc_body_reps(pred_info, proc_info, trace_level,
-    trace_suppress_items) = bool.
-:- func eff_trace_needs_port(pred_info, proc_info, trace_level,
+:- func eff_trace_level_is_none(module_info, pred_info, proc_info,
+    trace_level) = bool.
+:- func eff_trace_level_needs_input_vars(module_info, pred_info, proc_info,
+    trace_level) = bool.
+:- func eff_trace_level_needs_fail_vars(module_info, pred_info, proc_info,
+    trace_level) = bool.
+:- func eff_trace_level_needs_fixed_slots(module_info, pred_info, proc_info,
+    trace_level) = bool.
+:- func eff_trace_level_needs_from_full_slot(module_info, pred_info, proc_info,
+    trace_level) = bool.
+:- func eff_trace_needs_all_var_names(module_info, pred_info, proc_info,
+    trace_level, trace_suppress_items) = bool.
+:- func eff_trace_needs_proc_body_reps(module_info, pred_info, proc_info,
+    trace_level, trace_suppress_items) = bool.
+:- func eff_trace_needs_port(module_info, pred_info, proc_info, trace_level,
     trace_suppress_items, trace_port) = bool.
 
-:- func eff_trace_level(pred_info, proc_info, trace_level) = trace_level.
+:- func eff_trace_level(module_info, pred_info, proc_info, trace_level)
+    = trace_level.
 
 :- func trace_level_none = trace_level.
 
 :- func at_least_at_shallow(trace_level) = bool.
 :- func at_least_at_deep(trace_level) = bool.
 
-    % Given a trace level for a module, return the trace level we should
-    % use for compiler-generated unify, index and compare predicates.
+    % Given a trace level for a module, return the trace level we should use
+    % for compiler-generated unify, index and compare predicates.
     %
 :- func trace_level_for_unify_compare(trace_level) = trace_level.
 
@@ -130,8 +135,28 @@
 
 %-----------------------------------------------------------------------------%
 
+% The trace levels none, shallow, deep and decl_rep correspond to the similarly
+% named options. The trace levels basic and basic_user cannot be specified on
+% the command line; they can only be effective trace levels.
+%
+% Basic_user is the effective trace level for procedures in shallow traced
+% modules that contain a user defined event. This event requires, among other
+% things, the preservation of variables in the procedure in which it occurs.
+% It also requires the transmission of depth information through all procedures
+% in the module that otherwise wouldn't be traced, which is what trace level
+% basic does.
+%
+% In theory, in a shallow traced module, we could set the trace level of
+% a procedure to none if that procedure is not the ancestor of any procedure
+% containing a user event. However, that test is not one that can be
+% implemented easily or at all, given that the call trees of procedures may
+% cross module boundaries, and, in particular, may cross out of this module
+% and then back again through a different entry point.
+
 :- type trace_level
     --->    none
+    ;       basic
+    ;       basic_user
     ;       shallow
     ;       deep
     ;       decl_rep.
@@ -147,16 +172,22 @@
 trace_level_none = none.
 
 trace_level_for_unify_compare(none) = none.
+trace_level_for_unify_compare(basic) = none.
+trace_level_for_unify_compare(basic_user) = none.
 trace_level_for_unify_compare(shallow) = shallow.
 trace_level_for_unify_compare(deep) = shallow.
 trace_level_for_unify_compare(decl_rep) = shallow.
 
 at_least_at_shallow(none) = no.
+at_least_at_shallow(basic) = no.
+at_least_at_shallow(basic_user) = no.
 at_least_at_shallow(shallow) = yes.
 at_least_at_shallow(deep) = yes.
 at_least_at_shallow(decl_rep) = yes.
 
 at_least_at_deep(none) = no.
+at_least_at_deep(basic) = no.
+at_least_at_deep(basic_user) = no.
 at_least_at_deep(shallow) = no.
 at_least_at_deep(deep) = yes.
 at_least_at_deep(decl_rep) = yes.
@@ -174,7 +205,7 @@
 convert_trace_level("default", yes, no,  yes(deep)).
 convert_trace_level("default", _,   yes, yes(decl_rep)).
 
-eff_trace_level(PredInfo, ProcInfo, TraceLevel) = EffTraceLevel :-
+eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel) = EffTraceLevel :-
     ( TraceLevel = none ->
         EffTraceLevel = none
     ;
@@ -218,7 +249,22 @@
                 status_is_exported(Status) = no,
                 proc_info_get_is_address_taken(ProcInfo, address_is_not_taken)
             ->
+                proc_info_get_has_user_event(ProcInfo, ProcHasUserEvent),
+                (
+                    ProcHasUserEvent = yes,
+                    EffTraceLevel = basic_user
+                ;
+                    ProcHasUserEvent = no,
+                    module_info_get_contains_user_event(ModuleInfo,
+                        ModuleHasUserEvent),
+                    (
+                        ModuleHasUserEvent = yes,
+                        EffTraceLevel = basic
+                    ;
+                        ModuleHasUserEvent = no,
                 EffTraceLevel = none
+                    )
+                )
             ;
                 EffTraceLevel = TraceLevel
             )
@@ -228,29 +274,41 @@
 given_trace_level_is_none(TraceLevel) =
     trace_level_is_none(TraceLevel).
 
-eff_trace_level_is_none(PredInfo, ProcInfo, TraceLevel) =
-    trace_level_is_none(eff_trace_level(PredInfo, ProcInfo, TraceLevel)).
-eff_trace_level_needs_input_vars(PredInfo, ProcInfo, TraceLevel) =
+eff_trace_level_is_none(ModuleInfo, PredInfo, ProcInfo, TraceLevel) =
+    trace_level_is_none(
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel)).
+eff_trace_level_needs_input_vars(ModuleInfo, PredInfo, ProcInfo, TraceLevel) =
     trace_level_needs_input_vars(
-        eff_trace_level(PredInfo, ProcInfo, TraceLevel)).
-eff_trace_level_needs_fixed_slots(PredInfo, ProcInfo, TraceLevel) =
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel)).
+eff_trace_level_needs_fail_vars(ModuleInfo, PredInfo, ProcInfo, TraceLevel) =
+    trace_level_needs_fail_vars(
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel)).
+eff_trace_level_needs_fixed_slots(ModuleInfo, PredInfo, ProcInfo, TraceLevel) =
     trace_level_needs_fixed_slots(
-        eff_trace_level(PredInfo, ProcInfo, TraceLevel)).
-eff_trace_level_needs_from_full_slot(PredInfo, ProcInfo, TraceLevel) =
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel)).
+eff_trace_level_needs_from_full_slot(ModuleInfo, PredInfo, ProcInfo,
+        TraceLevel) =
     trace_level_needs_from_full_slot(
-        eff_trace_level(PredInfo, ProcInfo, TraceLevel)).
-eff_trace_needs_all_var_names(PredInfo, ProcInfo, TraceLevel, SuppressItems) =
-    trace_needs_all_var_names(eff_trace_level(PredInfo, ProcInfo, TraceLevel),
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel)).
+eff_trace_needs_all_var_names(ModuleInfo, PredInfo, ProcInfo, TraceLevel,
+        SuppressItems) =
+    trace_needs_all_var_names(
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel),
         SuppressItems).
-eff_trace_needs_proc_body_reps(PredInfo, ProcInfo, TraceLevel, SuppressItems) =
-    trace_needs_proc_body_reps(eff_trace_level(PredInfo, ProcInfo, TraceLevel),
+eff_trace_needs_proc_body_reps(ModuleInfo, PredInfo, ProcInfo, TraceLevel,
+        SuppressItems) =
+    trace_needs_proc_body_reps(
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel),
         SuppressItems).
-eff_trace_needs_port(PredInfo, ProcInfo, TraceLevel, SuppressItems, Port) =
-    trace_needs_port(eff_trace_level(PredInfo, ProcInfo, TraceLevel),
+eff_trace_needs_port(ModuleInfo, PredInfo, ProcInfo, TraceLevel, SuppressItems,
+        Port) =
+    trace_needs_port(
+        eff_trace_level(ModuleInfo, PredInfo, ProcInfo, TraceLevel),
         SuppressItems, Port).
 
 :- func trace_level_is_none(trace_level) = bool.
 :- func trace_level_needs_input_vars(trace_level) = bool.
+:- func trace_level_needs_fail_vars(trace_level) = bool.
 :- func trace_level_needs_fixed_slots(trace_level) = bool.
 :- func trace_level_needs_from_full_slot(trace_level) = bool.
 :- func trace_needs_all_var_names(trace_level, trace_suppress_items) = bool.
@@ -258,31 +316,50 @@
 :- func trace_needs_port(trace_level, trace_suppress_items, trace_port) = bool.
 
 trace_level_is_none(none) = yes.
+trace_level_is_none(basic) = no.
+trace_level_is_none(basic_user) = no.
 trace_level_is_none(shallow) = no.
 trace_level_is_none(deep) = no.
 trace_level_is_none(decl_rep) = no.
 
 trace_level_needs_input_vars(none) = no.
+trace_level_needs_input_vars(basic) = no.
+trace_level_needs_input_vars(basic_user) = no.
 trace_level_needs_input_vars(shallow) = yes.
 trace_level_needs_input_vars(deep) = yes.
 trace_level_needs_input_vars(decl_rep) = yes.
 
+trace_level_needs_fail_vars(none) = no.
+trace_level_needs_fail_vars(basic) = no.
+trace_level_needs_fail_vars(basic_user) = yes.
+trace_level_needs_fail_vars(shallow) = yes.
+trace_level_needs_fail_vars(deep) = yes.
+trace_level_needs_fail_vars(decl_rep) = yes.
+
 trace_level_needs_fixed_slots(none) = no.
+trace_level_needs_fixed_slots(basic) = yes.
+trace_level_needs_fixed_slots(basic_user) = yes.
 trace_level_needs_fixed_slots(shallow) = yes.
 trace_level_needs_fixed_slots(deep) = yes.
 trace_level_needs_fixed_slots(decl_rep) = yes.
 
 trace_level_needs_from_full_slot(none) = no.
+trace_level_needs_from_full_slot(basic) = no.
+trace_level_needs_from_full_slot(basic_user) = no.
 trace_level_needs_from_full_slot(shallow) = yes.
 trace_level_needs_from_full_slot(deep) = no.
 trace_level_needs_from_full_slot(decl_rep) = no.
 
 trace_level_allows_delay_death(none) = no.
+trace_level_allows_delay_death(basic) = no.
+trace_level_allows_delay_death(basic_user) = yes.
 trace_level_allows_delay_death(shallow) = no.
 trace_level_allows_delay_death(deep) = yes.
 trace_level_allows_delay_death(decl_rep) = yes.
 
 trace_level_needs_meaningful_var_names(none) = no.
+trace_level_needs_meaningful_var_names(basic) = no.
+trace_level_needs_meaningful_var_names(basic_user) = yes.
 trace_level_needs_meaningful_var_names(shallow) = no.
 trace_level_needs_meaningful_var_names(deep) = yes.
 trace_level_needs_meaningful_var_names(decl_rep) = yes.
@@ -322,16 +399,22 @@
 :- func trace_level_has_proc_body_reps(trace_level) = bool.
 
 trace_level_has_return_info(none) = no.
+trace_level_has_return_info(basic) = yes.
+trace_level_has_return_info(basic_user) = yes.
 trace_level_has_return_info(shallow) = yes.
 trace_level_has_return_info(deep) = yes.
 trace_level_has_return_info(decl_rep) = yes.
 
 trace_level_has_all_var_names(none) = no.
+trace_level_has_all_var_names(basic) = no.
+trace_level_has_all_var_names(basic_user) = no.
 trace_level_has_all_var_names(shallow) = no.
 trace_level_has_all_var_names(deep) = no.
 trace_level_has_all_var_names(decl_rep) = yes.
 
 trace_level_has_proc_body_reps(none) = no.
+trace_level_has_proc_body_reps(basic) = no.
+trace_level_has_proc_body_reps(basic_user) = no.
 trace_level_has_proc_body_reps(shallow) = no.
 trace_level_has_proc_body_reps(deep) = no.
 trace_level_has_proc_body_reps(decl_rep) = yes.
@@ -422,6 +505,8 @@
     % If this is modified, then the corresponding code in
     % runtime/mercury_stack_layout.h needs to be updated.
 trace_level_rep(none)     = "MR_TRACE_LEVEL_NONE".
+trace_level_rep(basic)      = "MR_TRACE_LEVEL_BASIC".
+trace_level_rep(basic_user) = "MR_TRACE_LEVEL_BASIC_USER".
 trace_level_rep(shallow)  = "MR_TRACE_LEVEL_SHALLOW".
 trace_level_rep(deep)     = "MR_TRACE_LEVEL_DEEP".
 trace_level_rep(decl_rep) = "MR_TRACE_LEVEL_DECL_REP".
@@ -467,6 +552,8 @@
 :- func trace_level_port_categories(trace_level) = list(port_category).
 
 trace_level_port_categories(none) = [].
+trace_level_port_categories(basic) = [].
+trace_level_port_categories(basic_user) = [port_cat_user].
 trace_level_port_categories(shallow) = [port_cat_interface].
 trace_level_port_categories(deep) =
     [port_cat_interface, port_cat_internal, port_cat_context, port_cat_user].
@@ -476,6 +563,8 @@
 :- func trace_level_allows_port_suppression(trace_level) = bool.
 
 trace_level_allows_port_suppression(none) = no.     % no ports exist
+trace_level_allows_port_suppression(basic) = yes.
+trace_level_allows_port_suppression(basic_user) = yes.
 trace_level_allows_port_suppression(shallow) = yes.
 trace_level_allows_port_suppression(deep) = yes.
 trace_level_allows_port_suppression(decl_rep) = no.
Index: compiler/typecheck.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/typecheck.m,v
retrieving revision 1.413
diff -u -b -r1.413 typecheck.m
--- compiler/typecheck.m	1 Dec 2006 15:04:26 -0000	1.413
+++ compiler/typecheck.m	4 Dec 2006 03:40:52 -0000
@@ -1514,7 +1514,8 @@
 
 typecheck_event_call(EventName, Args, !Info) :-
     typecheck_info_get_module_info(!.Info, ModuleInfo),
-    module_info_get_event_spec_map(ModuleInfo, EventSpecMap),
+    module_info_get_event_set(ModuleInfo, EventSet),
+    EventSpecMap = EventSet ^ event_set_spec_map,
     ( event_arg_types(EventSpecMap, EventName, EventArgTypes) ->
         ( list.same_length(Args, EventArgTypes) ->
             typecheck_var_has_type_list(Args, EventArgTypes, 1, !Info)
cvs diff: Diffing compiler/notes
cvs diff: Diffing debian
cvs diff: Diffing debian/patches
cvs diff: Diffing deep_profiler
cvs diff: Diffing deep_profiler/notes
cvs diff: Diffing doc
Index: doc/mdb_categories
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/doc/mdb_categories,v
retrieving revision 1.35
diff -u -b -r1.35 mdb_categories
--- doc/mdb_categories	24 Nov 2006 03:48:15 -0000	1.35
+++ doc/mdb_categories	1 Dec 2006 16:46:15 -0000
@@ -46,10 +46,11 @@
 parameter  - Commands that let users access debugger parameters.
              The parameter commands are `mmc_options', `printlevel', `scroll',
              `stack_default_limit', `goal_paths' `scope', `echo', 
-             `context', `list_context_lines', `list_path', `push_list_dir',
-             `pop_list_dir', `fail_trace_counts', `pass_trace_counts',
-	     `max_io_actions', `xml_browser_cmd', `xml_tmp_filename',
-	     `format', `format_param', `alias' and `unalias'.
+             `context', `user_event_context', `list_context_lines',
+	     `list_path', `push_list_dir', `pop_list_dir', `fail_trace_counts',
+	     `pass_trace_counts', `max_io_actions', `xml_browser_cmd',
+	     `xml_tmp_filename', `format', `format_param', `alias'
+	     and `unalias'.
 
 end
 document_category 800 help
Index: doc/user_guide.texi
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/doc/user_guide.texi,v
retrieving revision 1.500
diff -u -b -r1.500 user_guide.texi
--- doc/user_guide.texi	28 Nov 2006 11:02:32 -0000	1.500
+++ doc/user_guide.texi	4 Dec 2006 04:44:41 -0000
@@ -1421,11 +1421,11 @@
 Most of the menu commands also have keyboard short-cuts,
 which are displayed on the menu.
 
-Note that mdb's @samp{context} command should not be used if
-you are using the Emacs interface, otherwise the Emacs
-interface won't be able to parse the file names and
-line numbers that mdb outputs, and so it won't be able to
-highlight the correct location in the source code.
+Note that mdb's @samp{context} and @samp{user_event_context} commands
+should not be used if you are using the Emacs interface,
+otherwise the Emacs interface won't be able to parse
+the file names and line numbers that mdb outputs,
+and so it won't be able to highlight the correct location in the source code.
 
 @node Tracing of Mercury programs
 @section Tracing of Mercury programs
@@ -2158,12 +2158,15 @@
 of each kind of user defined event,
 by giving the name of an event set specification file to the compiler
 when compiling that program
-as the argument of the @samp{event-spec-file-name} option.
-This file should contain a sequence of one or more event specifications,
+as the argument of the @samp{event-set-file-name} option.
+This file should contain a header giving the event set's name,
+followed by a sequence of one or more event specifications,
 like this:
 
 @c XXX replace with more realistic example
 @example
+	event set queens
+
 	event nodiag_fail(
 		test_failed:	string,
 		arg_b:		int,
@@ -2178,6 +2181,8 @@
 	event noargs
 @end example
 
+The header consists of the keywords @samp{event set}
+and an identifier giving the event set name.
 Each event specification consists of the keyword @samp{event},
 the name of the event, and,
 if the event has any attributes, a parenthesized list of those attributes.
@@ -3447,6 +3452,26 @@
 @item context
 Reports where contexts are being printed.
 @sp 1
+ at item user_event_context none
+ at kindex user_event_context (mdb command)
+When reporting user-defined events,
+does not print either filename/line number pairs or procedure ids.
+ at sp 1
+ at item user_event_context file
+When reporting user-defined events,
+prints only filename/line number pairs, not procedure ids.
+ at sp 1
+ at item user_event_context proc
+When reporting user-defined events,
+prints only procedure ids, not filename/line number pairs.
+ at sp 1
+ at item user_event_context full
+When reporting user-defined events,
+prints both filename/line number pairs and procedure ids.
+ at sp 1
+ at item user_event_context
+Reports what parts of the context are being printed at user events.
+ at sp 1
 @item list_context_lines @var{num}
 @kindex list_context_lines (mdb command)
 Sets the number of lines to be printed by the @samp{list} command
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_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/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/stream
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
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
Index: runtime/mercury_stack_layout.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_layout.h,v
retrieving revision 1.103
diff -u -b -r1.103 mercury_stack_layout.h
--- runtime/mercury_stack_layout.h	29 Nov 2006 05:18:25 -0000	1.103
+++ runtime/mercury_stack_layout.h	4 Dec 2006 03:53:05 -0000
@@ -257,16 +257,22 @@
 ** The next three fields all point to an array whose length is the number of
 ** attributes.
 **
-** user_event->MR_ue_attr_locns[i] gives the location where we can find
-** the value of the (i+1)th attribute (since we start counting attributes at
-** one). This field will stay.
-**
-** user_event->MR_ue_attr_types[i] is the typeinfo giving the type of the
-** (i+1)th attribute. If we find that all attributes of all events have
-** a fixed type, this field may disappear.
+** MR_ue_attr_locns[i] gives the location where we can find the value of the
+** (i+1)th attribute (since we start counting attributes at one).
 **
-** user_event->MR_ue_attr_names[i] gives the name of the (i+1)th attribute.
-** In the future, this field may disappear.
+** MR_ue_attr_types[i] is the typeinfo giving the type of the (i+1)th
+** attribute.
+**
+** MR_ue_attr_names[i] gives the name of the (i+1)th attribute.
+** (In the future, this field may disappear.)
+** 
+** user_event->MR_ue_attr_var_nums[i] gives the variable number of the (i+1)th
+** attribute. This field is used by the debugger to display the associated
+** value just once (not twice, as both attribute and variable value) with
+** "print *". (Note that We don't delete the variables that are also attributes
+** from the set of live variables in layout structures, because that would
+** require any native garbage collector to look at the list of attributes
+** as well as the list of other variables, slowing it down.)
 */
 
 struct MR_UserEvent_Struct {
@@ -276,6 +282,7 @@
 	MR_LongLval			*MR_ue_attr_locns;
 	MR_TypeInfo			*MR_ue_attr_types;
 	const char			**MR_ue_attr_names;
+	const MR_uint_least16_t		*MR_ue_attr_var_nums;
 };
 
 /*-------------------------------------------------------------------------*/
@@ -867,6 +874,8 @@
 
 typedef enum {
 	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_NONE),
+	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_BASIC),
+	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_BASIC_USER),
 	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_SHALLOW),
 	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_DEEP),
 	MR_DEFINE_MERCURY_ENUM_CONST(MR_TRACE_LEVEL_DECL_REP)
@@ -1293,8 +1302,9 @@
 ** compiler/layout_out.m.
 */
 
-#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__USER_DEFINED
+#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__EVENTSETNAME
 #define	MR_LAYOUT_VERSION__USER_DEFINED	1
+#define	MR_LAYOUT_VERSION__EVENTSETNAME	2
 
 struct MR_ModuleLayout_Struct {
 	MR_uint_least8_t                MR_ml_version_number;
@@ -1309,6 +1319,7 @@
 	MR_int_least32_t		MR_ml_suppressed_events;
 	MR_int_least32_t		MR_ml_num_label_exec_counts;
 	MR_Unsigned			*MR_ml_label_exec_count;
+	const char			*MR_ml_event_set_name;
 	const char			*MR_ml_event_specs;
 };
 
Index: runtime/mercury_stack_trace.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_trace.c,v
retrieving revision 1.76
diff -u -b -r1.76 mercury_stack_trace.c
--- runtime/mercury_stack_trace.c	29 Nov 2006 05:18:26 -0000	1.76
+++ runtime/mercury_stack_trace.c	1 Dec 2006 16:43:33 -0000
@@ -73,27 +73,29 @@
 static  int         MR_dump_stack_record_frame(FILE *fp,
                         const MR_LabelLayout *label_layout,
                         MR_Word *base_sp, MR_Word *base_curfr,
-                        MR_Print_Stack_Record print_stack_record,
+                        MR_PrintStackRecord print_stack_record,
                         MR_bool at_line_limit);
 static  void        MR_dump_stack_record_flush(FILE *fp,
-                        MR_Print_Stack_Record print_stack_record);
+                        MR_PrintStackRecord print_stack_record);
 
 static  void        MR_print_proc_id_internal(FILE *fp,
-                        const MR_ProcLayout *entry, MR_bool spec,
+                        const MR_ProcLayout *proc_layout, MR_bool spec,
                         MR_bool print_mode, MR_bool separate);
 
-static  void        MR_maybe_print_context(FILE *fp,
+static  void        MR_maybe_print_proc_id(FILE *fp, MR_bool print_proc_id,
+                        const MR_ProcLayout *proc_layout, const char *path);
+static  void        MR_maybe_print_context(FILE *fp, MR_bool print_context,
                         const char *filename, int lineno);
 static  void        MR_maybe_print_parent_context(FILE *fp,
                         MR_bool print_parent, MR_bool verbose,
                         const char *filename, int lineno);
 
-static  MR_bool     MR_call_details_are_valid(const MR_ProcLayout *entry,
+static  MR_bool     MR_call_details_are_valid(const MR_ProcLayout *proc_layout,
                         MR_Word *base_sp, MR_Word *base_curfr);
 static  MR_bool     MR_call_is_before_event_or_seq(
                         MR_FindFirstCallSeqOrEvent seq_or_event,
                         MR_Unsigned seq_no_or_event_no,
-                        const MR_ProcLayout *entry, MR_Word *base_sp,
+                        const MR_ProcLayout *proc_layout, MR_Word *base_sp,
                         MR_Word *base_curfr);
 
 /* see comments in mercury_stack_trace.h */
@@ -105,7 +107,7 @@
     MR_Word *current_frame, MR_bool include_trace_data)
 {
     const MR_Internal       *label;
-    const MR_LabelLayout    *layout;
+    const MR_LabelLayout    *label_layout;
     const char              *result;
     MR_bool                 stack_dump_available;
     char                    *env_suppress;
@@ -129,8 +131,8 @@
         if (label == NULL) {
             fprintf(stderr, "internal label not found\n");
         } else {
-            layout = label->i_layout;
-            result = MR_dump_stack_from_layout(stderr, layout,
+            label_layout = label->i_layout;
+            result = MR_dump_stack_from_layout(stderr, label_layout,
                 det_stack_pointer, current_frame, include_trace_data,
                 MR_TRUE, 0, 0, &MR_dump_stack_record_print);
 
@@ -147,10 +149,10 @@
 MR_dump_stack_from_layout(FILE *fp, const MR_LabelLayout *label_layout,
     MR_Word *det_stack_pointer, MR_Word *current_frame,
     MR_bool include_trace_data, MR_bool include_contexts,
-    int frame_limit, int line_limit, MR_Print_Stack_Record print_stack_record)
+    int frame_limit, int line_limit, MR_PrintStackRecord print_stack_record)
 {
     MR_StackWalkStepResult          result;
-    const MR_ProcLayout             *entry_layout;
+    const MR_ProcLayout             *proc_layout;
     const MR_LabelLayout            *cur_label_layout;
     const MR_LabelLayout            *prev_label_layout;
     const char                      *problem;
@@ -184,13 +186,13 @@
             return NULL;
         }
 
-        entry_layout = cur_label_layout->MR_sll_entry;
+        proc_layout = cur_label_layout->MR_sll_entry;
         prev_label_layout = cur_label_layout;
 
         old_trace_sp    = stack_trace_sp;
         old_trace_curfr = stack_trace_curfr;
 
-        result = MR_stack_walk_step(entry_layout, &cur_label_layout,
+        result = MR_stack_walk_step(proc_layout, &cur_label_layout,
             &stack_trace_sp, &stack_trace_curfr, &problem);
         if (result == MR_STEP_ERROR_BEFORE) {
             MR_dump_stack_record_flush(fp, print_stack_record);
@@ -250,7 +252,7 @@
 }
 
 MR_StackWalkStepResult
-MR_stack_walk_step(const MR_ProcLayout *entry_layout,
+MR_stack_walk_step(const MR_ProcLayout *proc_layout,
     const MR_LabelLayout **return_label_layout,
     MR_Word **stack_trace_sp_ptr, MR_Word **stack_trace_curfr_ptr,
     const char **problem_ptr)
@@ -263,7 +265,7 @@
 
     *return_label_layout = NULL;
 
-    determinism = entry_layout->MR_sle_detism;
+    determinism = proc_layout->MR_sle_detism;
     if (determinism < 0) {
         /*
         ** This means we have reached some handwritten code that has
@@ -274,7 +276,7 @@
         return MR_STEP_ERROR_BEFORE;
     }
 
-    location = entry_layout->MR_sle_succip_locn;
+    location = proc_layout->MR_sle_succip_locn;
     if (MR_DETISM_DET_STACK(determinism)) {
         type = MR_LONG_LVAL_TYPE(location);
         number = MR_LONG_LVAL_NUMBER(location);
@@ -286,7 +288,7 @@
 
         success = (MR_Code *) MR_based_stackvar(*stack_trace_sp_ptr, number);
         *stack_trace_sp_ptr = *stack_trace_sp_ptr -
-            entry_layout->MR_sle_stack_slots;
+            proc_layout->MR_sle_stack_slots;
     } else {
         /* succip is always saved in succip_slot */
         assert(location.MR_long_lval == -1);
@@ -1065,7 +1067,7 @@
 static int
 MR_dump_stack_record_frame(FILE *fp, const MR_LabelLayout *label_layout,
     MR_Word *base_sp, MR_Word *base_curfr,
-    MR_Print_Stack_Record print_stack_record, MR_bool at_line_limit)
+    MR_PrintStackRecord print_stack_record, MR_bool at_line_limit)
 {
     const MR_ProcLayout     *entry_layout;
     const char              *filename;
@@ -1122,7 +1124,7 @@
 }
 
 static void
-MR_dump_stack_record_flush(FILE *fp, MR_Print_Stack_Record print_stack_record)
+MR_dump_stack_record_flush(FILE *fp, MR_PrintStackRecord print_stack_record)
 {
     if (prev_entry_layout != NULL) {
         print_stack_record(fp, prev_entry_layout,
@@ -1134,7 +1136,7 @@
 }
 
 void
-MR_dump_stack_record_print(FILE *fp, const MR_ProcLayout *entry_layout,
+MR_dump_stack_record_print(FILE *fp, const MR_ProcLayout *proc_layout,
     int count, int start_level, MR_Word *base_sp, MR_Word *base_curfr,
     const char *filename, int linenumber, const char *goal_path,
     MR_bool context_mismatch)
@@ -1153,9 +1155,9 @@
         */
     }
 
-    MR_maybe_print_call_trace_info(fp, trace_data_enabled, entry_layout,
+    MR_maybe_print_call_trace_info(fp, trace_data_enabled, proc_layout,
             base_sp, base_curfr);
-    MR_print_proc_id(fp, entry_layout);
+    MR_print_proc_id(fp, proc_layout);
     if (MR_strdiff(filename, "") && linenumber > 0) {
         fprintf(fp, " (%s:%d%s)", filename, linenumber,
             context_mismatch ? " and others" : "");
@@ -1203,10 +1205,10 @@
 
 void
 MR_maybe_print_call_trace_info(FILE *fp, MR_bool include_trace_data,
-    const MR_ProcLayout *entry, MR_Word *base_sp, MR_Word *base_curfr)
+    const MR_ProcLayout *proc_layout, MR_Word *base_sp, MR_Word *base_curfr)
 {
     if (include_trace_data) {
-        MR_print_call_trace_info(fp, entry, base_sp, base_curfr);
+        MR_print_call_trace_info(fp, proc_layout, base_sp, base_curfr);
     }
 }
 
@@ -1216,12 +1218,12 @@
 */
 
 void
-MR_print_call_trace_info(FILE *fp, const MR_ProcLayout *entry,
+MR_print_call_trace_info(FILE *fp, const MR_ProcLayout *proc_layout,
     MR_Word *base_sp, MR_Word *base_curfr)
 {
     MR_bool print_details;
 
-    if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+    if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
         if (base_sp == NULL) {
             return;
         }
@@ -1231,14 +1233,15 @@
         }
     }
 
-    print_details = MR_call_details_are_valid(entry, base_sp, base_curfr);
+    print_details =
+        MR_call_details_are_valid(proc_layout, base_sp, base_curfr);
 
     if (print_details) {
         unsigned long event_num;
         unsigned long call_num;
         unsigned long depth;
 
-        if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+        if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
             event_num = MR_event_num_stackvar(base_sp) + 1;
             call_num = MR_call_num_stackvar(base_sp);
             depth = MR_call_depth_stackvar(base_sp);
@@ -1269,7 +1272,7 @@
 #if !defined(MR_HIGHLEVEL_CODE) && defined(MR_TABLE_DEBUG)
   #if 0
     /* reenable this code if you need to */
-    if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+    if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
         MR_print_detstackptr(fp, base_sp);
     } else {
         MR_print_nondetstackptr(fp, base_curfr);
@@ -1417,75 +1420,94 @@
 
 void
 MR_print_proc_id_trace_and_context(FILE *fp, MR_bool include_trace_data,
-    MR_ContextPosition pos, const MR_ProcLayout *entry, MR_Word *base_sp,
-    MR_Word *base_curfr, const char *path, const char *filename, int lineno,
-    MR_bool print_parent, const char *parent_filename, int parent_lineno,
-    int indent)
+    MR_ContextPosition pos, MR_UserEventContext user_event_context,
+    const MR_ProcLayout *proc_layout, const char *maybe_user_event_name,
+    MR_Word *base_sp, MR_Word *base_curfr,
+    const char *path, const char *filename, int lineno, MR_bool print_parent,
+    const char *parent_filename, int parent_lineno, int indent)
 {
+    MR_bool             print_context;
+    MR_bool             print_proc_id;
+
+    if (maybe_user_event_name != NULL) {
+        switch (user_event_context) {
+            case MR_USER_EVENT_CONTEXT_NONE:
+                print_context = MR_FALSE;
+                print_proc_id = MR_FALSE;
+                break;
+
+            case MR_USER_EVENT_CONTEXT_FILE:
+                print_context = MR_TRUE;
+                print_proc_id = MR_FALSE;
+                break;
+
+            case MR_USER_EVENT_CONTEXT_PROC:
+                print_context = MR_FALSE;
+                print_proc_id = MR_TRUE;
+                break;
+
+            case MR_USER_EVENT_CONTEXT_FULL:
+            default:
+                print_context = MR_TRUE;
+                print_proc_id = MR_TRUE;
+                break;
+        }
+
+        print_parent = MR_FALSE;
+    } else {
+        print_context = MR_TRUE;
+        print_proc_id = MR_TRUE;
+    }
+
     switch (pos) {
         case MR_CONTEXT_NOWHERE:
             fprintf(fp, " ");
-            MR_maybe_print_call_trace_info(fp, include_trace_data, entry,
-                base_sp, base_curfr);
-            MR_print_proc_id(fp, entry);
-            if (strlen(path) > 0) {
-                fprintf(fp, " %s", path);
-            }
+            MR_maybe_print_call_trace_info(fp, include_trace_data,
+                proc_layout, base_sp, base_curfr);
+            MR_maybe_print_proc_id(fp, print_proc_id, proc_layout, path);
             fprintf(fp, "\n");
             break;
 
         case MR_CONTEXT_BEFORE:
-            MR_maybe_print_context(fp, filename, lineno);
+            MR_maybe_print_context(fp, print_context, filename, lineno);
             MR_maybe_print_parent_context(fp, print_parent, MR_FALSE,
                 parent_filename, parent_lineno);
             fprintf(fp, " ");
             MR_maybe_print_call_trace_info(fp, include_trace_data,
-                entry, base_sp, base_curfr);
-            MR_print_proc_id(fp, entry);
-            if (strlen(path) > 0) {
-                fprintf(fp, " %s", path);
-            }
+                proc_layout, base_sp, base_curfr);
+            MR_maybe_print_proc_id(fp, print_proc_id, proc_layout, path);
             fprintf(fp, "\n");
             break;
 
         case MR_CONTEXT_AFTER:
             fprintf(fp, " ");
             MR_maybe_print_call_trace_info(fp, include_trace_data,
-                entry, base_sp, base_curfr);
-            MR_print_proc_id(fp, entry);
-            if (strlen(path) > 0) {
-                fprintf(fp, " %s", path);
-            }
-            MR_maybe_print_context(fp, filename, lineno);
+                proc_layout, base_sp, base_curfr);
+            MR_maybe_print_proc_id(fp, print_proc_id, proc_layout, path);
+            MR_maybe_print_context(fp, print_context, filename, lineno);
             MR_maybe_print_parent_context(fp, print_parent, MR_FALSE,
                 parent_filename, parent_lineno);
             fprintf(fp, "\n");
             break;
 
         case MR_CONTEXT_PREVLINE:
-            MR_maybe_print_context(fp, filename, lineno);
+            MR_maybe_print_context(fp, print_context, filename, lineno);
             MR_maybe_print_parent_context(fp, print_parent, MR_TRUE,
                 parent_filename, parent_lineno);
             fprintf(fp, "\n%*s ", indent, "");
-            MR_maybe_print_call_trace_info(fp, include_trace_data, entry,
-                base_sp, base_curfr);
-            MR_print_proc_id(fp, entry);
-            if (strlen(path) > 0) {
-                fprintf(fp, " %s", path);
-            }
+            MR_maybe_print_call_trace_info(fp, include_trace_data,
+                proc_layout, base_sp, base_curfr);
+            MR_maybe_print_proc_id(fp, print_proc_id, proc_layout, path);
             fprintf(fp, "\n");
             break;
 
         case MR_CONTEXT_NEXTLINE:
             fprintf(fp, " ");
-            MR_maybe_print_call_trace_info(fp, include_trace_data, entry,
-                base_sp, base_curfr);
-            MR_print_proc_id(fp, entry);
-            if (strlen(path) > 0) {
-                fprintf(fp, " %s", path);
-            }
+            MR_maybe_print_call_trace_info(fp, include_trace_data,
+                proc_layout, base_sp, base_curfr);
+            MR_maybe_print_proc_id(fp, print_proc_id, proc_layout, path);
             fprintf(fp, "\n%*s", indent, "");
-            MR_maybe_print_context(fp, filename, lineno);
+            MR_maybe_print_context(fp, print_context, filename, lineno);
             MR_maybe_print_parent_context(fp, print_parent, MR_TRUE,
                 parent_filename, parent_lineno);
             fprintf(fp, "\n");
@@ -1497,9 +1519,22 @@
 }
 
 static void
-MR_maybe_print_context(FILE *fp, const char *filename, int lineno)
+MR_maybe_print_proc_id(FILE *fp, MR_bool print_proc_id,
+    const MR_ProcLayout *proc_layout, const char *path)
+{
+    if (print_proc_id) {
+        MR_print_proc_id(fp, proc_layout);
+        if (strlen(path) > 0) {
+            fprintf(fp, " %s", path);
+        }
+    }
+}
+
+static void
+MR_maybe_print_context(FILE *fp, MR_bool print_context, const char *filename,
+    int lineno)
 {
-    if (MR_strdiff(filename, "") && lineno != 0) {
+    if (print_context && MR_strdiff(filename, "") && lineno != 0) {
         fprintf(fp, " %s:%d", filename, lineno);
     }
 }
@@ -1518,11 +1553,11 @@
 }
 
 static  MR_bool
-MR_call_details_are_valid(const MR_ProcLayout *entry, MR_Word *base_sp,
+MR_call_details_are_valid(const MR_ProcLayout *proc_layout, MR_Word *base_sp,
     MR_Word *base_curfr)
 {
-    if (MR_PROC_LAYOUT_HAS_EXEC_TRACE(entry)) {
-        MR_Integer maybe_from_full = entry->MR_sle_maybe_from_full;
+    if (MR_PROC_LAYOUT_HAS_EXEC_TRACE(proc_layout)) {
+        MR_Integer maybe_from_full = proc_layout->MR_sle_maybe_from_full;
         if (maybe_from_full > 0) {
             /*
             ** For procedures compiled with shallow
@@ -1530,7 +1565,7 @@
             ** if the value of MR_from_full saved in
             ** the appropriate stack slot was MR_TRUE.
             */
-            if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+            if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
                 return MR_based_stackvar(base_sp, maybe_from_full);
             } else {
                 return MR_based_framevar(base_curfr, maybe_from_full);
@@ -1546,12 +1581,12 @@
 static MR_bool
 MR_call_is_before_event_or_seq(MR_FindFirstCallSeqOrEvent seq_or_event,
     MR_Unsigned seq_no_or_event_no,
-    const MR_ProcLayout *entry, MR_Word *base_sp, MR_Word *base_curfr)
+    const MR_ProcLayout *proc_layout, MR_Word *base_sp, MR_Word *base_curfr)
 {
     MR_Unsigned     call_event_num;
     MR_Unsigned     call_seq_num;
 
-    if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+    if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
         if (base_sp == NULL) {
             return MR_FALSE;
         }
@@ -1561,8 +1596,8 @@
         }
     }
 
-    if (MR_call_details_are_valid(entry, base_sp, base_curfr)) {
-        if (MR_DETISM_DET_STACK(entry->MR_sle_detism)) {
+    if (MR_call_details_are_valid(proc_layout, base_sp, base_curfr)) {
+        if (MR_DETISM_DET_STACK(proc_layout->MR_sle_detism)) {
             call_event_num = MR_event_num_stackvar(base_sp) + 1;
             call_seq_num = MR_call_num_stackvar(base_sp);
         } else {
Index: runtime/mercury_stack_trace.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_stack_trace.h,v
retrieving revision 1.39
diff -u -b -r1.39 mercury_stack_trace.h
--- runtime/mercury_stack_trace.h	29 Nov 2006 05:18:26 -0000	1.39
+++ runtime/mercury_stack_trace.h	1 Dec 2006 16:25:26 -0000
@@ -61,7 +61,7 @@
 ** why the dump was cut short.
 */
 
-typedef	void		(*MR_Print_Stack_Record)(FILE *fp,
+typedef	void		(*MR_PrintStackRecord)(FILE *fp,
 				const MR_ProcLayout *proc_layout,
 				int count, int level,
 				MR_Word *base_sp, MR_Word * base_curfr,
@@ -76,7 +76,7 @@
 				MR_bool include_trace_data,
 				MR_bool include_contexts,
 				int frame_limit, int line_limit,
-				MR_Print_Stack_Record print_stack_record);
+				MR_PrintStackRecord print_stack_record);
 
 /*
 ** MR_dump_nondet_stack
@@ -232,12 +232,12 @@
 */
 
 extern	void	MR_print_call_trace_info(FILE *fp,
-			const MR_ProcLayout *entry,
+			const MR_ProcLayout *proc_layout,
 			MR_Word *base_sp, MR_Word *base_curfr);
 
 extern	void	MR_maybe_print_call_trace_info(FILE *fp,
 			MR_bool include_trace_data,
-			const MR_ProcLayout *entry,
+			const MR_ProcLayout *proc_layout,
 			MR_Word *base_sp, MR_Word *base_curfr);
 
 /*
@@ -275,7 +275,9 @@
 ** MR_print_proc_id_trace_and_context prints an identification of the given
 ** procedure, together with call trace information (if available), a context
 ** within the procedure, and possibly a context identifying the caller.
-** The position argument says where (if anywhere) the contexts should appear.
+** The pos argument says where (if anywhere) the contexts should appear;
+** the user_event_context argument says what parts of the context (if any)
+** to print for user defined events.
 */
 
 typedef	enum {
@@ -286,12 +288,22 @@
 	MR_CONTEXT_NEXTLINE
 } MR_ContextPosition;
 
+typedef	enum {
+	MR_USER_EVENT_CONTEXT_NONE,
+	MR_USER_EVENT_CONTEXT_FILE,
+	MR_USER_EVENT_CONTEXT_PROC,
+	MR_USER_EVENT_CONTEXT_FULL
+} MR_UserEventContext;
+
 extern	void	MR_print_proc_id_trace_and_context(FILE *fp,
 			MR_bool include_trace_data, MR_ContextPosition pos,
-			const MR_ProcLayout *entry,
+			MR_UserEventContext user_event_context,
+			const MR_ProcLayout *proc_layout,
+			const char *maybe_user_event_name,
 			MR_Word *base_sp, MR_Word *base_curfr,
 			const char *path, const char *filename, int lineno,
-			MR_bool print_parent, const char *parent_filename,
+			MR_bool print_parent,
+			const char *parent_filename,
 			int parent_lineno, int indent);
 
 /*
@@ -299,7 +311,7 @@
 */
 
 extern	void	MR_dump_stack_record_print(FILE *fp,
-			const MR_ProcLayout *entry_layout, int count,
+			const MR_ProcLayout *proc_layout, int count,
 			int start_level, MR_Word *base_sp, MR_Word *base_curfr,
 			const char *filename, int linenumber,
 			const char *goal_path, MR_bool context_mismatch);
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/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
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
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
Index: tests/debugger/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/Mercury.options,v
retrieving revision 1.19
diff -u -b -r1.19 Mercury.options
--- tests/debugger/Mercury.options	24 Nov 2006 03:48:22 -0000	1.19
+++ tests/debugger/Mercury.options	1 Dec 2006 04:53:35 -0000
@@ -41,7 +41,9 @@
 # asm_fast.gc.debug.tr.
 MCFLAGS-uci_index = --compare-specialization 2 --intermodule-optimization
 
-MCFLAGS-user_event = --event-spec-file-name user_event_spec
+MCFLAGS-user_event = --event-set-file-name user_event_spec
+
+MCFLAGS-user_event_shallow = --event-set-file-name user_event_spec --trace shallow
 
 # The solver_test test case exercises the printing of a procedure name, and
 # that procedure is dead, so we must prevent it being optimized away.
Index: tests/debugger/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/Mmakefile,v
retrieving revision 1.127
diff -u -b -r1.127 Mmakefile
--- tests/debugger/Mmakefile	24 Nov 2006 03:48:22 -0000	1.127
+++ tests/debugger/Mmakefile	4 Dec 2006 04:02:52 -0000
@@ -52,7 +52,8 @@
 	solver_test			\
 	type_desc_test			\
 	uci_index			\
-	user_event
+	user_event			\
+	user_event_shallow
 
 # We currently don't pass this test.
 #	deeply_nested_typeinfo
@@ -527,9 +528,14 @@
 uci_index.out: uci_index uci_index.inp
 	$(MDB_STD) ./uci_index < uci_index.inp 2>&1 > uci_index.out 2>&1
 
-user_event.out: user_event user_event.inp
+user_event.out: user_event user_event.inp user_event_spec
 	$(MDB_STD) ./user_event < user_event.inp 2>&1 > user_event.out 2>&1
 
+user_event_shallow.out: user_event_shallow user_event_shallow.inp \
+		user_event_spec
+	$(MDB_STD) ./user_event_shallow < user_event_shallow.inp 2>&1 \
+		> user_event_shallow.out 2>&1
+
 # When WORKSPACE is set, use $(WORKSPACE)/tools/lmc to compile the query.
 ifneq ($(origin WORKSPACE), undefined)
 export WORKSPACE
Index: tests/debugger/completion.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/completion.exp,v
retrieving revision 1.34
diff -u -b -r1.34 completion.exp
--- tests/debugger/completion.exp	24 Nov 2006 03:48:22 -0000	1.34
+++ tests/debugger/completion.exp	2 Dec 2006 02:15:41 -0000
@@ -35,13 +35,13 @@
 disable              modules              untrust
 document             next                 up
 document_category    nondet_stack         user
-down                 open                 v
-dump                 p                    var_details
-e                    pass_trace_counts    vars
-echo                 pneg_stack           view
-enable               pop_list_dir         xml_browser_cmd
-exception            print                xml_tmp_filename
-excp                 print_optionals      
+down                 open                 user_event_context
+dump                 p                    v
+e                    pass_trace_counts    var_details
+echo                 pneg_stack           vars
+enable               pop_list_dir         view
+exception            print                xml_browser_cmd
+excp                 print_optionals      xml_tmp_filename
 h              help           histogram_exp  
 held_vars      histogram_all  hold           
 var_details  vars         view         
Index: tests/debugger/mdb_command_test.inp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/mdb_command_test.inp,v
retrieving revision 1.52
diff -u -b -r1.52 mdb_command_test.inp
--- tests/debugger/mdb_command_test.inp	24 Nov 2006 03:48:23 -0000	1.52
+++ tests/debugger/mdb_command_test.inp	2 Dec 2006 02:13:16 -0000
@@ -69,6 +69,7 @@
 scope                xyzzy xyzzy xyzzy xyzzy xyzzy
 echo                 xyzzy xyzzy xyzzy xyzzy xyzzy
 context              xyzzy xyzzy xyzzy xyzzy xyzzy
+user_event_context   xyzzy xyzzy xyzzy xyzzy xyzzy
 list_context_lines   xyzzy xyzzy xyzzy xyzzy xyzzy
 list_path            xyzzy xyzzy xyzzy xyzzy xyzzy
 push_list_dir        xyzzy xyzzy xyzzy xyzzy xyzzy
Index: tests/debugger/user_event.exp
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/user_event.exp,v
retrieving revision 1.1
diff -u -b -r1.1 user_event.exp
--- tests/debugger/user_event.exp	24 Nov 2006 03:48:23 -0000	1.1
+++ tests/debugger/user_event.exp	1 Dec 2006 18:33:29 -0000
@@ -3,11 +3,10 @@
 Command echo enabled.
 mdb> register --quiet
 mdb> user
-      E2:     C2 USER pred user_event.queen/2-0 (nondet) c3; user_event.m:32
+      E2:     C2 USER <safe_test> pred user_event.queen/2-0 (nondet) c3; user_event.m:32
 mdb> print *
-       test_list (attr 0)     	[1, 2, 3, 4, 5]
+       test_list (attr 0, Out)	[1, 2, 3, 4, 5]
        Data (arg 1)           	[1, 2, 3, 4, 5]
-       Out (arg 2)            	[1, 2, 3, 4, 5]
 mdb> browse !test_list
 browser> p
 [1, 2, 3, 4, 5]
@@ -16,12 +15,12 @@
 2
 browser> quit
 mdb> user
-      E3:     C3 USER pred user_event.nodiag/3-0 (semidet) s2;c6;t;c2; user_event.m:64
+      E3:     C3 USER <nodiag_fail> pred user_event.nodiag/3-0 (semidet) s2;c6;t;c2; user_event.m:64
 mdb> vars
         1 test_failed (attr 0)
-        2 arg_b (attr 1)
-        3 arg_d (attr 2)
-        4 arg_list (attr 3)
+        2 arg_b (attr 1, B)
+        3 arg_d (attr 2, N)
+        4 arg_list (attr 3, HeadVar__3)
         5 HeadVar__1
         6 HeadVar__2
         7 HeadVar__3
@@ -33,25 +32,21 @@
        13 NmB
 mdb> print *
        test_failed (attr 0)   	"N - B"
-       arg_b (attr 1)         	1
-       arg_d (attr 2)         	2
-       arg_list (attr 3)      	[2, 3, 4, 5]
+       arg_b (attr 1, B)      	1
+       arg_d (attr 2, N)      	2
+       arg_list (attr 3, HeadVar__3)	[2, 3, 4, 5]
        HeadVar__1             	1
        HeadVar__2             	1
-       HeadVar__3             	[2, 3, 4, 5]
-       B                      	1
        BmN                    	-1
        D                      	1
        L                      	[3, 4, 5]
-       N                      	2
        NmB                    	1
 mdb> print !arg_b
-       arg_b (attr 1)         	1
+       arg_b (attr 1, B)      	1
 mdb> user
-      E4:     C2 USER pred user_event.queen/2-0 (nondet) c3; user_event.m:32
+      E4:     C2 USER <safe_test> pred user_event.queen/2-0 (nondet) c3; user_event.m:32
 mdb> print *
-       test_list (attr 0)     	[1, 2, 3, 5, 4]
+       test_list (attr 0, Out)	[1, 2, 3, 5, 4]
        Data (arg 1)           	[1, 2, 3, 4, 5]
-       Out (arg 2)            	[1, 2, 3, 5, 4]
 mdb> continue
 [1, 3, 5, 2, 4]
Index: tests/debugger/user_event_shallow.exp
===================================================================
RCS file: tests/debugger/user_event_shallow.exp
diff -N tests/debugger/user_event_shallow.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/user_event_shallow.exp	4 Dec 2006 05:24:03 -0000
@@ -0,0 +1,61 @@
+      E1:     C1 CALL pred user_event_shallow.main/2-0 (cc_multi) user_event_shallow.m:16
+mdb> echo on
+Command echo enabled.
+mdb> register --quiet
+mdb> user
+      E2:     C2 USER <safe_test> pred user_event_shallow.queen/2-0 (nondet) c3; user_event_shallow.m:32
+mdb> retry
+Cannot perform retry because information about the input arguments is not available.
+mdb> print *
+       test_list (attr 0, Out)	[1, 2, 3, 4, 5]
+       Data (arg 1)           	[1, 2, 3, 4, 5]
+mdb> browse !test_list
+browser> p
+[1, 2, 3, 4, 5]
+browser> ^2^1
+browser> p
+2
+browser> quit
+mdb> user_event_context proc
+User events will get only procedure contexts printed.
+mdb> user
+      E3:     C3 USER <nodiag_fail> pred user_event_shallow.nodiag/3-0 (semidet) s2;c4;t;c2;
+mdb> user_event_context none
+User events will get no contexts printed.
+mdb> current
+      E3:     C3 USER <nodiag_fail> 
+mdb> user_event_context
+User events get no contexts printed.
+mdb> user_event_context full
+User events will get full contexts printed.
+mdb> current
+      E3:     C3 USER <nodiag_fail> pred user_event_shallow.nodiag/3-0 (semidet) s2;c4;t;c2; user_event_shallow.m:64
+mdb> user_event_context file
+User events will get only file contexts printed.
+mdb> current
+      E3:     C3 USER <nodiag_fail>  user_event_shallow.m:64
+mdb> vars
+        1 test_failed (attr 0)
+        2 arg_b (attr 1, HeadVar__1)
+        3 arg_d (attr 2, N)
+        4 arg_list (attr 3, HeadVar__3)
+        5 HeadVar__1
+        6 HeadVar__2
+        7 HeadVar__3
+        8 L
+mdb> print *
+       test_failed (attr 0)   	"N - B"
+       arg_b (attr 1, HeadVar__1)	1
+       arg_d (attr 2, N)      	2
+       arg_list (attr 3, HeadVar__3)	[2, 3, 4, 5]
+       HeadVar__2             	1
+       L                      	[3, 4, 5]
+mdb> print !arg_b
+       arg_b (attr 1, HeadVar__1)	1
+mdb> user
+      E4:     C2 USER <safe_test>  user_event_shallow.m:32
+mdb> print *
+       test_list (attr 0, Out)	[1, 2, 3, 5, 4]
+       Data (arg 1)           	[1, 2, 3, 4, 5]
+mdb> continue
+[1, 3, 5, 2, 4]
Index: tests/debugger/user_event_shallow.inp
===================================================================
RCS file: tests/debugger/user_event_shallow.inp
diff -N tests/debugger/user_event_shallow.inp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/user_event_shallow.inp	4 Dec 2006 05:18:15 -0000
@@ -0,0 +1,25 @@
+echo on
+register --quiet
+user
+retry
+print *
+browse !test_list
+p
+^2^1
+p
+quit
+user_event_context proc
+user
+user_event_context none
+current
+user_event_context
+user_event_context full
+current
+user_event_context file
+current
+vars
+print *
+print !arg_b
+user
+print *
+continue
Index: tests/debugger/user_event_shallow.m
===================================================================
RCS file: tests/debugger/user_event_shallow.m
diff -N tests/debugger/user_event_shallow.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/user_event_shallow.m	1 Dec 2006 04:51:35 -0000
@@ -0,0 +1,99 @@
+:- module user_event_shallow.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is cc_multi.
+
+:- implementation.
+
+:- import_module list.
+:- import_module int.
+
+:- type listint == list(int).
+
+main(!IO) :-
+	data(Data),
+	( queen(Data, Out) ->
+		print_list(Out, !IO)
+	;
+		io.write_string("No solution\n", !IO)
+	).
+
+:- pred data(list(int)::out) is det.
+
+data([1,2,3,4,5]).
+
+:- pred queen(list(int)::in, list(int)::out) is nondet.
+
+queen(Data, Out) :-
+	qperm(Data, Out),
+	event safe_test(Out),
+	safe(Out).
+
+:- pred qperm(list(T)::in, list(T)::out) is nondet.
+
+qperm([], []).
+qperm(L, K) :-
+	L = [_ | _],
+	qdelete(U, L, Z),
+	K = [U | V],
+	qperm(Z, V).
+
+:- pred qdelete(T::out, list(T)::in, list(T)::out) is nondet.
+
+qdelete(A, [A | L], L).
+qdelete(X, [A | Z], [A | R]) :-
+	qdelete(X, Z, R).
+
+:- pred safe(list(int)::in) is semidet.
+
+safe([]).
+safe([N | L]) :-
+	nodiag(N, 1, L),
+	safe(L).
+
+:- pred nodiag(int::in, int::in, list(int)::in) is semidet.
+
+nodiag(_, _, []).
+nodiag(B, D, [N | L]) :-
+	NmB = N - B,
+	BmN = B - N,
+	( D = NmB ->
+		event nodiag_fail("N - B", B, N, [N | L]),
+		fail
+	; D = BmN ->
+		event nodiag_fail("B - N", B, N, [N | L]),
+		fail
+	;
+		true
+	),
+	D1 = D + 1,
+	nodiag(B, D1, L).
+
+:- pred print_list(list(int)::in, io::di, io::uo) is det.
+
+print_list(Xs, !IO) :-
+	(
+		Xs = [],
+		io.write_string("[]\n", !IO)
+	;
+		Xs = [_ | _],
+		io.write_string("[", !IO),
+		print_list_2(Xs, !IO),
+		io.write_string("]\n", !IO)
+	).
+
+:- pred print_list_2(list(int)::in, io::di, io::uo) is det.
+
+print_list_2([], !IO).
+print_list_2([X | Xs], !IO) :-
+	io.write_int(X, !IO),
+	(
+		Xs = []
+	;
+		Xs = [_ | _],
+		io__write_string(", ", !IO),
+		print_list_2(Xs, !IO)
+	).
Index: tests/debugger/user_event_spec
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/user_event_spec,v
retrieving revision 1.1
diff -u -b -r1.1 user_event_spec
--- tests/debugger/user_event_spec	24 Nov 2006 03:48:24 -0000	1.1
+++ tests/debugger/user_event_spec	4 Dec 2006 04:02:59 -0000
@@ -1,3 +1,5 @@
+event set queens
+
 event nodiag_fail(
 	test_failed:	string,
 	arg_b:		int,
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: [05:25:29] waiting for uid20308's lock in /home/mercury/mercury1/repository/tests/general/accumulator
cvs diff: [05:25:59] obtained lock in /home/mercury/mercury1/repository/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: [05:25:59] waiting for uid20308's lock in /home/mercury/mercury1/repository/tests/hard_coded
cvs diff: [05:26:29] obtained lock in /home/mercury/mercury1/repository/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: [05:26:32] waiting for uid20308's lock in /home/mercury/mercury1/repository/tests/invalid
cvs diff: [05:27:02] obtained lock in /home/mercury/mercury1/repository/tests/invalid
Index: tests/invalid/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/invalid/Mercury.options,v
retrieving revision 1.17
diff -u -b -r1.17 Mercury.options
--- tests/invalid/Mercury.options	28 Nov 2006 06:17:20 -0000	1.17
+++ tests/invalid/Mercury.options	2 Dec 2006 01:00:26 -0000
@@ -41,7 +41,7 @@
 MCFLAGS-impure_method_impl =	--no-intermodule-optimization \
 				--no-automatic-intermodule-optimization \
 				--verbose-error-messages
-MCFLAGS-invalid_event =		--event-spec-file-name invalid_event_spec
+MCFLAGS-invalid_event =		--event-set-file-name invalid_event_spec
 MCFLAGS-loopcheck =		--warn-inferred-erroneous \
 				--verbose-error-messages
 MCFLAGS-method_impl =		--no-intermodule-optimization \
Index: tests/invalid/invalid_event_spec
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/invalid/invalid_event_spec,v
retrieving revision 1.1
diff -u -b -r1.1 invalid_event_spec
--- tests/invalid/invalid_event_spec	28 Nov 2006 06:17:21 -0000	1.1
+++ tests/invalid/invalid_event_spec	2 Dec 2006 01:00:44 -0000
@@ -1,3 +1,5 @@
+event set invalid_event
+
 event nodiag_fail(
 	test_failed:	string,
 	arg_b:		int,
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: [05:27:05] waiting for uid20308's lock in /home/mercury/mercury1/repository/tests/par_conj
cvs diff: [05:27:35] obtained lock in /home/mercury/mercury1/repository/tests/par_conj
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: [05:27:36] waiting for uid20308's lock in /home/mercury/mercury1/repository/tests/term
cvs diff: [05:28:06] obtained lock in /home/mercury/mercury1/repository/tests/term
cvs diff: Diffing tests/trailing
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
cvs diff: Diffing trace
Index: trace/mercury_event_parser.y
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_parser.y,v
retrieving revision 1.1
diff -u -b -r1.1 mercury_event_parser.y
--- trace/mercury_event_parser.y	24 Nov 2006 03:48:25 -0000	1.1
+++ trace/mercury_event_parser.y	30 Nov 2006 23:34:29 -0000
@@ -25,7 +25,7 @@
 #include "mercury_event_parser.h"
 #include "mercury_event_scanner.h"          /* for mercury_event_lex etc */
 
-MR_EventSpecs       mercury_event_parsetree;
+MR_EventSet         mercury_event_parsetree;
 static  unsigned    mercury_event_next_num = 0;
 static  void        mercury_event_error(const char *s);
 %}
@@ -36,6 +36,7 @@
 {
     int                 Uline;
     char                *Uid;
+    MR_EventSet         Ufile;
     MR_EventSpecs       Uevents;
     MR_EventSpec        Uevent;
     MR_EventAttrs       Uattrs;
@@ -48,6 +49,7 @@
 }
 
 %token  <Uline>     TOKEN_EVENT
+%token              TOKEN_SET
 %token              TOKEN_FUNCTION
 %token              TOKEN_SYNTHESIZED
 %token              TOKEN_BY
@@ -62,6 +64,7 @@
 
 %token              GARBAGE
 
+%type   <Ufile>     file
 %type   <Uevents>   events
 %type   <Uevent>    event
 %type   <Uattrs>    maybe_attrs
@@ -78,9 +81,15 @@
 
 /**********************************************************************/
 
-file        :   events
+file        :   TOKEN_EVENT TOKEN_SET TOKEN_ID events
                 {
-                    mercury_event_parsetree = $1;
+                    $$ = MR_NEW(struct MR_EventSet_Struct);
+                    $$->MR_event_set_name = $3;
+                    $$->MR_event_set_spec_list = $4;
+                    /* The following fields are filled in later. */
+                    $$->MR_event_set_specs = NULL;
+                    $$->MR_event_set_num_events = 0;
+                    mercury_event_parsetree = $$;
                 }
             ;
 
Index: trace/mercury_event_scanner.l
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_scanner.l,v
retrieving revision 1.1
diff -u -b -r1.1 mercury_event_scanner.l
--- trace/mercury_event_scanner.l	24 Nov 2006 03:48:26 -0000	1.1
+++ trace/mercury_event_scanner.l	30 Nov 2006 23:20:10 -0000
@@ -92,6 +92,7 @@
                         mercury_event_lval.Uline = mercury_event_linenum;
                         return TOKEN_EVENT;
                     }
+"set"               { return TOKEN_SET;                 }
 "function"          { return TOKEN_FUNCTION;            }
 "synthesized"       { return TOKEN_SYNTHESIZED;         }
 "by"                { return TOKEN_BY;                  }
Index: trace/mercury_event_spec.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_spec.c,v
retrieving revision 1.2
diff -u -b -r1.2 mercury_event_spec.c
--- trace/mercury_event_spec.c	1 Dec 2006 04:53:43 -0000	1.2
+++ trace/mercury_event_spec.c	4 Dec 2006 03:41:05 -0000
@@ -34,10 +34,6 @@
 ** free slot and how many slots are allocated.
 */
 
-MR_EventSpec        *MR_event_specs = NULL;
-int                 MR_event_spec_next = 0;
-int                 MR_event_spec_max = 0;
-
 static const char   *MR_event_spec_chars;
 static unsigned     MR_event_spec_char_next;
 static unsigned     MR_event_spec_char_max;
@@ -78,10 +74,13 @@
     return num_copied;
 }
 
-MR_bool
-MR_read_event_specs(const char *input_data)
+MR_EventSet
+MR_read_event_set(const char *input_data)
 {
+    MR_EventSet     event_set;
     MR_EventSpecs cur;
+    MR_Unsigned     num_events;
+    MR_Unsigned     i;
 
     /*
     ** Set these globals up for calls to MR_event_get_input by the scanner.
@@ -93,22 +92,30 @@
     MR_event_spec_char_next = 0;
 
     if (mercury_event_parse() != 0) {
-        return MR_FALSE;
+        return NULL;
     }
 
-    MR_event_spec_max = 0;
-    for (cur = mercury_event_parsetree; cur != NULL; cur = cur->MR_events_tail)
+    event_set = MR_NEW(struct MR_EventSet_Struct);
+    event_set->MR_event_set_name = mercury_event_parsetree->MR_event_set_name;
+    event_set->MR_event_set_spec_list =
+        mercury_event_parsetree->MR_event_set_spec_list;
+
+    num_events = 0;
+    for (cur = event_set->MR_event_set_spec_list;
+        cur != NULL; cur = cur->MR_events_tail)
     {
-        MR_event_spec_max++;
+        num_events++;
     }
 
-    MR_event_specs = MR_NEW_ARRAY(MR_EventSpec, MR_event_spec_max);
+    event_set->MR_event_set_num_events = num_events;
+    event_set->MR_event_set_specs = MR_NEW_ARRAY(MR_EventSpec, num_events);
 
-    MR_event_spec_next = 0;
-    for (cur = mercury_event_parsetree; cur != NULL; cur = cur->MR_events_tail)
+    i = 0;
+    for (cur = event_set->MR_event_set_spec_list;
+        cur != NULL; cur = cur->MR_events_tail)
     {
-        MR_event_specs[MR_event_spec_next] = cur->MR_events_head;
-        MR_event_spec_next++;
+        event_set->MR_event_set_specs[i] = cur->MR_events_head;
+        i++;
     }
 
     /*
@@ -122,7 +129,7 @@
         MR_compare_event_specs);
 #endif
 
-    return MR_TRUE;
+    return event_set;
 }
 
 static int
@@ -138,17 +145,22 @@
 }
 
 void
-MR_print_event_specs(FILE *fp)
+MR_print_event_set(FILE *fp, MR_EventSet event_set)
 {
     int             event_num;
     MR_EventSpec    event;
+    MR_EventSpecs   events;
     MR_EventAttr    attr;
     MR_EventAttrs   attrs;
 
+    fprintf(fp, "event_set_spec(\"%s\",\n", event_set->MR_event_set_name);
     fprintf(fp, "[\n");
 
-    for (event_num = 0; event_num < MR_event_spec_max; event_num++) {
-        event = MR_event_specs[event_num];
+    for (event_num = 0, events = event_set->MR_event_set_spec_list;
+        events != NULL;
+        event_num++, events = events->MR_events_tail)
+    {
+        event = events->MR_events_head;
         fprintf(fp, "event_spec_term(\"%s\", %d, %d, [\n",
             event->MR_event_name, event->MR_event_num, event->MR_event_lineno);
 
@@ -188,14 +200,14 @@
             }
         }
 
-        if (event_num == MR_event_spec_max - 1) {
-            fprintf(fp, "])\n");
-        } else {
+        if (events->MR_events_tail != NULL) {
             fprintf(fp, "]),\n");
+        } else {
+            fprintf(fp, "])\n");
         }
     }
 
-    fprintf(fp, "].\n");
+    fprintf(fp, "]).\n");
 }
 
 static void
Index: trace/mercury_event_spec.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_spec.h,v
retrieving revision 1.1
diff -u -b -r1.1 mercury_event_spec.h
--- trace/mercury_event_spec.h	24 Nov 2006 03:48:26 -0000	1.1
+++ trace/mercury_event_spec.h	30 Nov 2006 23:58:13 -0000
@@ -20,12 +20,29 @@
 #include "mercury_std.h"            /* for MR_bool */
 #include "mercury_trace_term.h"     /* for MR_CTerm and MR_FlatTerm */
 
+typedef struct MR_EventSet_Struct       *MR_EventSet;
 typedef struct MR_EventSpecs_Struct     *MR_EventSpecs;
 typedef struct MR_EventSpec_Struct      *MR_EventSpec;
 typedef struct MR_EventAttrs_Struct     *MR_EventAttrs;
 typedef struct MR_EventAttr_Struct      *MR_EventAttr;
 typedef struct MR_EventAttrType_Struct  *MR_EventAttrType;
 
+/*
+** The event_set_name field gives the name of an event set. The
+** event_set_spec_list field gives a list of the specifications of all the
+** events in that event set. The event_set_specs field has the same
+** information, only in the form of an array indexable by event number.
+** The event_set_num_events field gives the number of different event kinds
+** in the event set, which is also the size of the event_set_specs array.
+*/
+
+struct MR_EventSet_Struct {
+    const char          *MR_event_set_name;
+    MR_EventSpecs       MR_event_set_spec_list;
+    MR_EventSpec        *MR_event_set_specs;
+    MR_Unsigned         MR_event_set_num_events;
+};
+
 struct MR_EventSpecs_Struct {
     MR_EventSpec        MR_events_head;
     MR_EventSpecs       MR_events_tail;
@@ -61,15 +78,6 @@
 };
 
 /*
-** Read the specification of a set of event types from the given string, which
-** should be the contents of the event set specification file. Record the
-** result in the module's private data structures. Return true if the operation
-** succeeded; otherwise, return false.
-*/
-
-extern  MR_bool         MR_read_event_specs(const char *event_spec);
-
-/*
 ** The flex-generated scanner uses this function to read its input directly
 ** from the consensus event set specification. It reads up to buf_size bytes
 ** into buf, and returns the number of bytes read.
@@ -78,20 +86,18 @@
 extern  int             MR_event_get_input(char *buf, int buf_size);
 
 /*
-** Print out the set of event specifications recorded in the module's private
-** data structures to the given stream as a single Mercury term.
+** Read the specification of a set of event types from the given string, which
+** should be the contents of the event set specification file. If the operation
+** succeeded, return the result; otherwise, return NULL.
 */
 
-extern  void            MR_print_event_specs(FILE *fp);
-
+extern  MR_EventSet     MR_read_event_set(const char *event_set);
 
 /*
-** The table of event specifications, with counters saying which is the next
-** free slot and how many slots are allocated.
+** Print out the set of event specifications given by event_set to the given
+** stream as a single Mercury term.
 */
 
-extern  MR_EventSpec    *MR_event_specs;
-extern  int             MR_event_spec_next;
-extern  int             MR_event_spec_max;
+extern  void            MR_print_event_set(FILE *fp, MR_EventSet event_set);
 
 #endif  /* not MERCURY_TRACE_EVENT_H */
Index: trace/mercury_event_spec_missing.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_spec_missing.h,v
retrieving revision 1.1
diff -u -b -r1.1 mercury_event_spec_missing.h
--- trace/mercury_event_spec_missing.h	24 Nov 2006 03:48:26 -0000	1.1
+++ trace/mercury_event_spec_missing.h	30 Nov 2006 23:19:29 -0000
@@ -24,7 +24,7 @@
 extern  const char      *mercury_event_filename;
 extern  int             mercury_event_linenum;
 
-extern  MR_EventSpecs   mercury_event_parsetree;
+extern  MR_EventSet     mercury_event_parsetree;
 extern  int             mercury_event_parse(void);
 
 #endif  /* not MERCURY_TRACE_EVENT_MISSING_H */
Index: trace/mercury_trace.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace.c,v
retrieving revision 1.100
diff -u -b -r1.100 mercury_trace.c
--- trace/mercury_trace.c	29 Nov 2006 05:18:32 -0000	1.100
+++ trace/mercury_trace.c	4 Dec 2006 04:42:24 -0000
@@ -698,7 +698,7 @@
     }
 
     call_label = level_layout->MR_sle_call_label;
-    if (call_label->MR_sll_var_count < 0) {
+    if (call_label == NULL || call_label->MR_sll_var_count < 0) {
         *problem = "Cannot perform retry because information about "
             "the input arguments is not available.";
         goto report_problem;
@@ -1092,6 +1092,10 @@
     const MR_ProcLayout     *level_layout;
     MR_Unsigned             saved_io_counter;
 
+    if (call_label == NULL) {
+        return MR_FALSE;
+    }
+
     level_layout = call_label->MR_sll_entry;
     if (level_layout->MR_sle_maybe_io_seq <= 0) {
         return MR_FALSE;
Index: trace/mercury_trace_cmd_browsing.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_cmd_browsing.c,v
retrieving revision 1.4
diff -u -b -r1.4 mercury_trace_cmd_browsing.c
--- trace/mercury_trace_cmd_browsing.c	29 Nov 2006 05:18:34 -0000	1.4
+++ trace/mercury_trace_cmd_browsing.c	1 Dec 2006 15:32:21 -0000
@@ -674,8 +674,9 @@
         }
 
         MR_print_proc_id_trace_and_context(MR_mdb_out, MR_FALSE,
-            MR_context_position, entry, base_sp, base_curfr, "",
-            filename, lineno, MR_FALSE, "", 0, indent);
+            MR_context_position, MR_user_event_context, entry, MR_FALSE,
+            base_sp, base_curfr, "", filename, lineno, MR_FALSE,
+            "", 0, indent);
     } else {
         fflush(MR_mdb_out);
         fprintf(MR_mdb_err, "%s.\n", problem);
Index: trace/mercury_trace_cmd_parameter.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_cmd_parameter.c,v
retrieving revision 1.5
diff -u -b -r1.5 mercury_trace_cmd_parameter.c
--- trace/mercury_trace_cmd_parameter.c	29 Nov 2006 05:18:36 -0000	1.5
+++ trace/mercury_trace_cmd_parameter.c	2 Dec 2006 01:33:47 -0000
@@ -58,6 +58,8 @@
 
 MR_ContextPosition      MR_context_position = MR_CONTEXT_AFTER;
 
+MR_UserEventContext     MR_user_event_context = MR_USER_EVENT_CONTEXT_FULL;
+
 MR_bool                 MR_print_goal_paths = MR_TRUE;
 
 MR_Word                 MR_listing_path;
@@ -293,6 +295,63 @@
     return KEEP_INTERACTING;
 }
 
+static const char   *MR_user_event_context_set_msg[] = {
+    "User events will get no contexts printed.",
+    "User events will get only file contexts printed.",
+    "User events will get only procedure contexts printed.",
+    "User events will get full contexts printed.",
+};
+
+static const char   *MR_user_event_context_report_msg[] = {
+    "User events get no contexts printed.",
+    "User events get only file contexts printed.",
+    "User events get only procedure contexts printed.",
+    "User events get full contexts printed.",
+};
+
+MR_Next
+MR_trace_cmd_user_event_context(char **words, int word_count,
+    MR_TraceCmdInfo *cmd, MR_EventInfo *event_info, MR_Code **jumpaddr)
+{
+    if (word_count == 2) {
+        if (MR_streq(words[1], "none")) {
+            MR_user_event_context = MR_USER_EVENT_CONTEXT_NONE;
+        } else if (MR_streq(words[1], "file")) {
+            MR_user_event_context = MR_USER_EVENT_CONTEXT_FILE;
+        } else if (MR_streq(words[1], "proc")) {
+            MR_user_event_context = MR_USER_EVENT_CONTEXT_PROC;
+        } else if (MR_streq(words[1], "full")) {
+            MR_user_event_context = MR_USER_EVENT_CONTEXT_FULL;
+        } else {
+            MR_trace_usage_cur_cmd();
+            return KEEP_INTERACTING;
+        }
+
+        if (MR_trace_internal_interacting) {
+            fprintf(MR_mdb_out, "%s\n",
+                MR_user_event_context_set_msg[MR_user_event_context]);
+        }
+    } else if (word_count == 1) {
+        switch (MR_user_event_context) {
+            case MR_USER_EVENT_CONTEXT_NONE:
+            case MR_USER_EVENT_CONTEXT_FILE:
+            case MR_USER_EVENT_CONTEXT_PROC:
+            case MR_USER_EVENT_CONTEXT_FULL:
+
+                fprintf(MR_mdb_out, "%s\n",
+                    MR_user_event_context_report_msg[MR_user_event_context]);
+                break;
+
+            default:
+                MR_fatal_error("invalid MR_user_event_context");
+        }
+    } else {
+        MR_trace_usage_cur_cmd();
+    }
+
+    return KEEP_INTERACTING;
+}
+
 MR_Next
 MR_trace_cmd_goal_paths(char **words, int word_count, MR_TraceCmdInfo *cmd,
     MR_EventInfo *event_info, MR_Code **jumpaddr)
@@ -861,6 +920,9 @@
 const char *const    MR_trace_context_cmd_args[] =
     { "none", "before", "after", "prevline", "nextline", NULL };
         
+const char *const    MR_trace_user_event_context_cmd_args[] =
+    { "none", "file", "proc", "full", NULL };
+
 const char *const    MR_trace_scope_cmd_args[] =
     { "all", "interface", "entry", NULL };
 
Index: trace/mercury_trace_cmd_parameter.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_cmd_parameter.h,v
retrieving revision 1.2
diff -u -b -r1.2 mercury_trace_cmd_parameter.h
--- trace/mercury_trace_cmd_parameter.h	29 Nov 2006 05:18:36 -0000	1.2
+++ trace/mercury_trace_cmd_parameter.h	1 Dec 2006 16:33:19 -0000
@@ -83,6 +83,12 @@
 extern  MR_ContextPosition  MR_context_position;
 
 /*
+** MR_user_event_context specifies what context to print at user events.
+*/
+
+extern  MR_UserEventContext MR_user_event_context;
+
+/*
 ** MR_print_goal_paths specifies whether we print goal paths at events.
 */
 
@@ -111,6 +117,7 @@
 extern  MR_TraceCmdFunc     MR_trace_cmd_scroll;
 extern  MR_TraceCmdFunc     MR_trace_cmd_stack_default_limit;
 extern  MR_TraceCmdFunc     MR_trace_cmd_context;
+extern  MR_TraceCmdFunc     MR_trace_cmd_user_event_context;
 extern  MR_TraceCmdFunc     MR_trace_cmd_goal_paths;
 extern  MR_TraceCmdFunc     MR_trace_cmd_scope;
 extern  MR_TraceCmdFunc     MR_trace_cmd_echo;
@@ -131,6 +138,7 @@
 extern  const char *const   MR_trace_printlevel_cmd_args[];
 extern  const char *const   MR_trace_on_off_args[];
 extern  const char *const   MR_trace_context_cmd_args[];
+extern  const char *const   MR_trace_user_event_context_cmd_args[];
 extern  const char *const   MR_trace_scope_cmd_args[];
 extern  const char *const   MR_trace_format_cmd_args[];
 extern  const char *const   MR_trace_format_param_cmd_args[];
Index: trace/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
retrieving revision 1.228
diff -u -b -r1.228 mercury_trace_internal.c
--- trace/mercury_trace_internal.c	29 Nov 2006 05:18:39 -0000	1.228
+++ trace/mercury_trace_internal.c	1 Dec 2006 16:39:45 -0000
@@ -300,6 +300,7 @@
     if (! MR_trace_internal_initialized) {
         char        *env;
         int         n;
+        int         i;
 
         if (MR_mdb_benchmark_silent) {
             (void) close(1);
@@ -357,15 +358,21 @@
         MR_io_tabling_start = MR_IO_ACTION_MAX;
         MR_io_tabling_end = MR_IO_ACTION_MAX;
 
-        if (MR_event_specs_have_conflict) {
+        for (i = 0; i < MR_trace_event_set_next; i++) {
+            if (! MR_trace_event_sets[i].MR_tes_is_consistent) {
             fprintf(MR_mdb_out,
                 "The executable's modules were compiled with "
-                "an inconsistent set of user event specifications.\n");
-        } else if (MR_consensus_event_specs != NULL) {
-            if (! MR_read_event_specs(MR_consensus_event_specs)) {
+                    "inconsistent definitions of user event set %s.\n",
+                    MR_trace_event_sets[i].MR_tes_name);
+            } else {
+                MR_trace_event_sets[i].MR_tes_event_set =
+                    MR_read_event_set(MR_trace_event_sets[i].MR_tes_string);
+                if (MR_trace_event_sets[i].MR_tes_event_set == NULL) {
                 fprintf(MR_mdb_out,
-                    "Internal error: "
-                    "could not parse the event set specification.\n");
+                        "Internal error: could not parse "
+                        "the specification of event set %s.\n",
+                        MR_trace_event_sets[i].MR_tes_name);
+                }
             }
         }
 
@@ -1442,6 +1449,7 @@
 void
 MR_trace_event_print_internal_report(MR_EventInfo *event_info)
 {
+    const MR_LabelLayout    *label_layout;
     const MR_LabelLayout    *parent;
     const char              *filename;
     const char              *parent_filename;
@@ -1451,6 +1459,7 @@
     MR_Word                 *base_sp;
     MR_Word                 *base_curfr;
     int                     indent;
+    const char              *maybe_user_event_name;
 
     lineno = 0;
     parent_lineno = 0;
@@ -1477,23 +1486,34 @@
             MR_port_names[event_info->MR_trace_port]);
     }
 
-    /* the printf printed 24 characters */
+    /* The printf printed 24 characters. */
     indent = 24;
 
-    (void) MR_find_context(event_info->MR_event_sll, &filename, &lineno);
+    label_layout = event_info->MR_event_sll;
+    (void) MR_find_context(label_layout, &filename, &lineno);
     if (MR_port_is_interface(event_info->MR_trace_port)) {
         base_sp = MR_saved_sp(event_info->MR_saved_regs);
         base_curfr = MR_saved_curfr(event_info->MR_saved_regs);
-        parent = MR_find_nth_ancestor(event_info->MR_event_sll, 1,
-            &base_sp, &base_curfr, &problem);
+        parent = MR_find_nth_ancestor(label_layout, 1, &base_sp, &base_curfr,
+            &problem);
         if (parent != NULL) {
             (void) MR_find_context(parent, &parent_filename, &parent_lineno);
         }
     }
 
+    if (label_layout->MR_sll_port >= 0 &&
+        (MR_TracePort) label_layout->MR_sll_port == MR_PORT_USER)
+    {
+        maybe_user_event_name =
+            label_layout->MR_sll_user_event->MR_ue_port_name;
+        fprintf(MR_mdb_out, " <%s>", maybe_user_event_name);
+    } else {
+        maybe_user_event_name = NULL;
+    }
+
     MR_print_proc_id_trace_and_context(MR_mdb_out, MR_FALSE,
-        MR_context_position, event_info->MR_event_sll->MR_sll_entry,
-        base_sp, base_curfr,
+        MR_context_position, MR_user_event_context, label_layout->MR_sll_entry,
+        maybe_user_event_name, base_sp, base_curfr,
         ( MR_print_goal_paths ? event_info->MR_event_path : "" ),
         filename, lineno, MR_port_is_interface(event_info->MR_trace_port),
         parent_filename, parent_lineno, indent);
@@ -1612,6 +1632,8 @@
         MR_trace_on_off_args, MR_trace_null_completer },
     { "parameter", "context", MR_trace_cmd_context,
         MR_trace_context_cmd_args, MR_trace_null_completer },
+    { "parameter", "user_event_context", MR_trace_cmd_user_event_context,
+        MR_trace_user_event_context_cmd_args, MR_trace_null_completer },
     { "parameter", "list_context_lines", MR_trace_cmd_list_context_lines,
         NULL, MR_trace_null_completer },
     { "parameter", "list_path", MR_trace_cmd_list_path,
Index: trace/mercury_trace_tables.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_tables.c,v
retrieving revision 1.45
diff -u -b -r1.45 mercury_trace_tables.c
--- trace/mercury_trace_tables.c	29 Nov 2006 05:18:41 -0000	1.45
+++ trace/mercury_trace_tables.c	1 Dec 2006 02:55:16 -0000
@@ -30,9 +30,11 @@
 #include <string.h>
 #include <ctype.h>
 
-const char      *MR_consensus_event_specs = NULL;
-MR_bool         MR_event_specs_have_conflict = MR_FALSE;
+MR_TraceEventSet    *MR_trace_event_sets = NULL;
+int                 MR_trace_event_set_next = 0;
+int                 MR_trace_event_set_max = 0;
 
+MR_bool             MR_trace_event_sets_are_all_consistent = MR_TRUE;
 
 /*
 ** We record module layout structures in two tables. The MR_module_infos
@@ -155,6 +157,8 @@
     }
 }
 
+#define MR_INIT_EVENT_SET_TABLE_SIZE    10
+
 void
 MR_register_module_layout_real(const MR_ModuleLayout *module)
 {
@@ -168,16 +172,40 @@
     if (MR_search_module_info_by_name(module->MR_ml_name) == NULL) {
         MR_insert_module_info(module);
 
-        if (module->MR_ml_version_number >= MR_LAYOUT_VERSION__USER_DEFINED) {
+        if (module->MR_ml_version_number >= MR_LAYOUT_VERSION__EVENTSETNAME) {
             if (module->MR_ml_event_specs != NULL) {
-                if (MR_consensus_event_specs == NULL) {
-                    MR_consensus_event_specs = module->MR_ml_event_specs;
-                } else {
-                    if (MR_strdiff(MR_consensus_event_specs,
+                int                 i;
+                MR_bool             found;
+                const char          *event_set_name;
+                MR_TraceEventSet    *trace_event_set;
+                
+                event_set_name = module->MR_ml_event_set_name;
+
+                for (i = 0; i < MR_trace_event_set_next; i++) {
+                    if (MR_streq(MR_trace_event_sets[i].MR_tes_name,
+                        event_set_name))
+                    {
+                        trace_event_set = &MR_trace_event_sets[i];
+                        if (MR_strdiff(trace_event_set->MR_tes_string,
                         module->MR_ml_event_specs))
                     {
-                        MR_event_specs_have_conflict = MR_TRUE;
-                    } /* else this module has the same specs as the consensus */
+                            trace_event_set->MR_tes_is_consistent = MR_FALSE;
+                        }
+
+                        found = MR_TRUE;
+                        break;
+                    }
+                }
+
+                if (!found) {
+                    MR_ensure_room_for_next(MR_trace_event_set,
+                        MR_TraceEventSet, MR_INIT_EVENT_SET_TABLE_SIZE);
+                    trace_event_set =
+                        &MR_trace_event_sets[MR_trace_event_set_next];
+                    trace_event_set->MR_tes_name = event_set_name;
+                    trace_event_set->MR_tes_string = module->MR_ml_event_specs;
+                    trace_event_set->MR_tes_is_consistent = MR_TRUE;
+                    MR_trace_event_set_next++;
                 }
             }
         }
Index: trace/mercury_trace_tables.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_tables.h,v
retrieving revision 1.26
diff -u -b -r1.26 mercury_trace_tables.h
--- trace/mercury_trace_tables.h	29 Nov 2006 05:18:41 -0000	1.26
+++ trace/mercury_trace_tables.h	1 Dec 2006 02:55:14 -0000
@@ -19,6 +19,7 @@
 
 #include    "mercury_stack_layout.h"
 #include    "mercury_trace_completion.h"
+#include    "mercury_event_spec.h"          /* for MR_EventSet */
 #include    <stdio.h>
 
 /*
@@ -44,20 +45,34 @@
 ** Every module that generates user defined events has a specification of the
 ** set of user events it was compiled with in its module layout structure.
 ** The debugger needs to know what these specifications are, and if they
-** are consistent (which in this case means identical).
+** are consistent (which means that any two event sets with the same name
+** must be identical).
 **
-** If no modules have user defined events, MR_event_specs_have_conflict will
-** be false and MR_consensus_event_specs will be NULL. If there are some user
-** defined events in some modules and the modules are consistent, then
-** MR_event_specs_have_conflict will still be false and the string will contain
-** a copy of the original specification file in a canonical form (standard
-** indentation, comments stripped). If there is an inconsistency, then
-** MR_event_specs_have_conflict will be TRUE, and MR_consensus_event_specs
-** will not be meaningful.
+** MR_trace_event_sets points to dynamically resizable array of
+** MR_TraceEventSets, with MR_trace_event_set_max giving the current size
+** of the array and MR_trace_event_set_next giving the number of elements
+** currently filled in. The array is not sorted.
+**
+** The name field of an MR_TraceEventSet gives the name of the event set, while
+** the string field will contain the string representation of the event set.
+** The is_consistent field will be true iff all modules that use the event set
+** with the same name have the same representation. The event_set field
+** contains the parsed form of the string field; it is meaningful only if
+** is_consistent is true.
 */
 
-extern  const char      *MR_consensus_event_specs;
-extern  MR_bool         MR_event_specs_have_conflict;
+typedef struct {
+    const char      *MR_tes_name;
+    const char      *MR_tes_string;
+    MR_bool         MR_tes_is_consistent;
+    MR_EventSet     MR_tes_event_set;
+} MR_TraceEventSet;
+
+extern  MR_TraceEventSet    *MR_trace_event_sets;
+extern  int                 MR_trace_event_set_next;
+extern  int                 MR_trace_event_set_max;
+
+extern  MR_bool             MR_trace_event_sets_are_all_consistent;
 
 /*
 ** MR_process_file_line_layouts searches all the module layout structures
Index: trace/mercury_trace_vars.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_vars.c,v
retrieving revision 1.71
diff -u -b -r1.71 mercury_trace_vars.c
--- trace/mercury_trace_vars.c	29 Nov 2006 05:18:42 -0000	1.71
+++ trace/mercury_trace_vars.c	1 Dec 2006 12:34:43 -0000
@@ -71,13 +71,14 @@
     MR_bool             MR_var_has_suffix;
     int                 MR_var_is_headvar;
     MR_bool             MR_var_is_ambiguous;
-    int                 MR_var_hlds_number;
+    MR_uint_least16_t   MR_var_hlds_number;
     int                 MR_var_seq_num_in_label;
 } MR_ProgVarDetails;
 
 typedef struct {
     unsigned            MR_attr_num;
     char                *MR_attr_name;
+    MR_uint_least16_t   MR_attr_var_hlds_number;
 } MR_AttributeDetails;
 
 typedef union {
@@ -129,6 +130,10 @@
 ** point. This many of the elements of the vars array are valid.
 ** The number of elements of the vars array for which space has been
 ** reserved is held in var_max.
+**
+** The attr_var_max field gives the hlds number of the highest numbered
+** variable that is also an attribute of an user defined event. If there are
+** no such attributes, attr_var_max will be negative.
 */
 
 typedef struct {
@@ -144,6 +149,7 @@
     MR_Word                 *MR_point_level_base_curfr;
     int                     MR_point_var_count;
     int                     MR_point_var_max;
+    int                     MR_point_attr_var_max;
     MR_ValueDetails         *MR_point_vars;
 } MR_Point;
 
@@ -177,8 +183,11 @@
 static  char            *MR_trace_var_completer_next(const char *word,
                             size_t word_len, MR_CompleterData *data);
 static  int             MR_trace_print_var_name(FILE *out,
-                            MR_ValueDetails *var);
-static  const char      *MR_trace_printed_var_name(MR_ValueDetails *var);
+                            const MR_ProcLayout *proc,
+                            const MR_ValueDetails *var);
+static  const char      *MR_trace_printed_var_name(
+                            const MR_ProcLayout *proc,
+                            const MR_ValueDetails *var);
 static  const char      *MR_trace_valid_var_number(int var_number);
 
 #define MR_INIT_VAR_DETAIL_COUNT        20
@@ -467,6 +476,7 @@
     MR_proc_id_arity_addedargs_predfunc(entry, &arity, &num_added_args,
         &pred_or_func);
 
+    MR_point.MR_point_attr_var_max = -1;
     slot = 0;
     for (i = 0; i < attr_count; i++) {
         succeeded = MR_FALSE;
@@ -486,11 +496,18 @@
         MR_point.MR_point_vars[slot].MR_value_value = value;
         MR_point.MR_point_vars[slot].MR_value_attr.MR_attr_num = i;
         MR_point.MR_point_vars[slot].MR_value_attr.MR_attr_name = attr_name;
+        MR_point.MR_point_vars[slot].MR_value_attr.MR_attr_var_hlds_number =
+            user->MR_ue_attr_var_nums[i];
+
+        if (user->MR_ue_attr_var_nums[i] > MR_point.MR_point_attr_var_max) {
+            MR_point.MR_point_attr_var_max = user->MR_ue_attr_var_nums[i];
+        }
+
         slot++;
     }
 
     for (i = 0; i < var_count; i++) {
-        int     hlds_var_num;
+        MR_uint_least16_t   hlds_var_num;
         int     head_var_num;
         int     start_of_num;
         char    *num_addr;
@@ -757,7 +774,8 @@
 
     for (i = 0; i < MR_point.MR_point_var_count; i++) {
         fprintf(out, "%9d ", i + 1);
-        MR_trace_print_var_name(out, &MR_point.MR_point_vars[i]);
+        MR_trace_print_var_name(out, MR_point.MR_point_level_entry,
+            &MR_point.MR_point_vars[i]);
         fprintf(out, "\n");
     }
 
@@ -783,8 +801,9 @@
                 attr = &value->MR_value_attr;
                 fprintf(out, "\n");
                 fprintf(out,
-                    "slot %d, attr number %d, attribute name %s\n",
-                    i, attr->MR_attr_num, attr->MR_attr_name);
+                    "slot %d, attr number %d, attribute name %s, hlds %d\n",
+                    i, attr->MR_attr_num, attr->MR_attr_name,
+                    attr->MR_attr_var_hlds_number);
                 break;
 
             case MR_VALUE_PROG_VAR:
@@ -1379,7 +1398,11 @@
 const char *
 MR_trace_browse_all(FILE *out, MR_Browser browser, MR_BrowseFormat format)
 {
+    MR_bool             *already_printed;
+    MR_int_least16_t    attr_hlds_num;
+    MR_int_least16_t    var_hlds_num;
     int var_num;
+    int                 i;
 
     if (MR_point.MR_point_problem != NULL) {
         return MR_point.MR_point_problem;
@@ -1389,14 +1412,53 @@
         fprintf(out, "mdb: there are no live variables.\n");
     }
 
+    already_printed = NULL;
+    if (MR_point.MR_point_attr_var_max >= 0) {
+        already_printed = MR_NEW_ARRAY(MR_bool, 
+            MR_point.MR_point_attr_var_max + 1);
+
+        for (i = 0; i <= MR_point.MR_point_attr_var_max; i++) {
+            already_printed[i] = MR_FALSE;
+        }
+    }
+
     for (var_num = 0; var_num < MR_point.MR_point_var_count; var_num++) {
+        switch (MR_point.MR_point_vars[var_num].MR_value_kind) {
+            case MR_VALUE_ATTRIBUTE:
+                attr_hlds_num = MR_point.MR_point_vars[var_num].
+                    MR_value_attr.MR_attr_var_hlds_number;
+
+                /*
+                ** We are about to print the value of the variable with HLDS
+                ** number attr_var_num, so mark it as not to be printed again.
+                */
+
+                MR_assert(attr_hlds_num <= MR_point.MR_point_attr_var_max);
+                already_printed[attr_hlds_num] = MR_TRUE;
+                break;
+
+            case MR_VALUE_PROG_VAR:
+                var_hlds_num = MR_point.MR_point_vars[var_num].
+                    MR_value_var.MR_var_hlds_number;
+                if (var_hlds_num <= MR_point.MR_point_attr_var_max &&
+                    already_printed[var_hlds_num])
+                {
+                    /* We have already printed this variable; skip it */
+                    continue;
+                }
+
+                break;
+        }
+
         (void) MR_trace_browse_var(out, MR_TRUE,
             MR_point.MR_point_vars[var_num].MR_value_type,
             MR_point.MR_point_vars[var_num].MR_value_value,
-            MR_trace_printed_var_name(&MR_point.MR_point_vars[var_num]),
+            MR_trace_printed_var_name(MR_point.MR_point_level_entry,
+                &MR_point.MR_point_vars[var_num]),
             NULL, browser, MR_BROWSE_CALLER_PRINT_ALL, format);
     }
 
+    MR_free(already_printed);
     return NULL;
 }
 
@@ -1578,7 +1640,9 @@
             *var_index_ptr = vn;
             *type_info_ptr = MR_point.MR_point_vars[vn].MR_value_type;
             *value_ptr = MR_point.MR_point_vars[vn].MR_value_value;
-            *name_ptr = MR_trace_printed_var_name(&MR_point.MR_point_vars[vn]);
+            *name_ptr =
+                MR_trace_printed_var_name(MR_point.MR_point_level_entry,
+                    &MR_point.MR_point_vars[vn]);
             *is_ambiguous_ptr = MR_FALSE;
             return NULL;
 
@@ -1602,7 +1666,9 @@
             *var_index_ptr = vn;
             *type_info_ptr = MR_point.MR_point_vars[vn].MR_value_type;
             *value_ptr = MR_point.MR_point_vars[vn].MR_value_value;
-            *name_ptr = MR_trace_printed_var_name(value);
+            *name_ptr =
+                MR_trace_printed_var_name(MR_point.MR_point_level_entry,
+                    value);
             if (value->MR_value_var.MR_var_is_ambiguous) {
                 *is_ambiguous_ptr = MR_TRUE;
             } else {
@@ -1631,7 +1697,9 @@
             *var_index_ptr = vn;
             *type_info_ptr = MR_point.MR_point_vars[vn].MR_value_type;
             *value_ptr = MR_point.MR_point_vars[vn].MR_value_value;
-            *name_ptr = MR_trace_printed_var_name(value);
+            *name_ptr =
+                MR_trace_printed_var_name(MR_point.MR_point_level_entry,
+                    value);
             *is_ambiguous_ptr = MR_FALSE;
 
             return NULL;
@@ -1692,12 +1760,13 @@
 }
 
 static int
-MR_trace_print_var_name(FILE *out, MR_ValueDetails *value)
+MR_trace_print_var_name(FILE *out, const MR_ProcLayout *proc,
+    const MR_ValueDetails *value)
 {
     const char  *buf;
     int         len;
 
-    buf = MR_trace_printed_var_name(value);
+    buf = MR_trace_printed_var_name(proc, value);
     len = strlen(buf);
     fputs(buf, out);
     return len;
@@ -1708,20 +1777,38 @@
 static  char    MR_var_name_buf[MR_TRACE_VAR_NAME_BUF_SIZE];
 
 static const char *
-MR_trace_printed_var_name(MR_ValueDetails *value)
+MR_trace_printed_var_name(const MR_ProcLayout *proc,
+    const MR_ValueDetails *value)
 {
-    MR_ProgVarDetails   *var;
-    MR_AttributeDetails *attr;
+    const MR_ProgVarDetails     *var;
+    const MR_AttributeDetails   *attr;
+    MR_ConstString              attr_var_name;
 
     switch (value->MR_value_kind) {
         case MR_VALUE_ATTRIBUTE:
             attr = &value->MR_value_attr;
+            attr_var_name =
+                MR_hlds_var_name(proc, attr->MR_attr_var_hlds_number);
 #ifdef  MR_HAVE_SNPRINTF
+            if (attr_var_name != NULL) {
+                snprintf(MR_var_name_buf, MR_TRACE_VAR_NAME_BUF_SIZE,
+                    "%s (attr %d, %s)", attr->MR_attr_name,
+                    attr->MR_attr_num, attr_var_name);
+            } else {
             snprintf(MR_var_name_buf, MR_TRACE_VAR_NAME_BUF_SIZE,
-                "%s (attr %d)", attr->MR_attr_name, attr->MR_attr_num);
+                    "%s (attr %d)", attr->MR_attr_name,
+                    attr->MR_attr_num);
+            }
 #else
-            sprintf(MR_var_name_buf, "%s (attr %d)",
-                attr->MR_attr_name, attr->MR_attr_num);
+            if (attr_var_name != NULL) {
+                sprintf(MR_var_name_buf,
+                    "%s (attr %d, %s)", attr->MR_attr_name,
+                    attr->MR_attr_num, attr_var_name);
+            } else {
+                sprintf(MR_var_name_buf,
+                    "%s (attr %d)", attr->MR_attr_name,
+                    attr->MR_attr_num);
+            }
 #endif
             break;
 
cvs diff: Diffing util
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