[m-rev.] for review by Mark: synthesized attributes

Zoltan Somogyi zs at csse.unimelb.edu.au
Mon Dec 11 14:10:13 AEDT 2006


Implement synthesized attributes at user events.

doc/user_guide.texi:
	Document synthesized attributes.

runtime/mercury_stack_layout.h:
	Include information about synthesized attributes in layout structures.

	Move the the information about user events that is not specific to a
	given event occurrence to a central table of user event specifications
	in the module layout structure, to reduce the space overhead, and allow
	a future Ducasse style execution monitor to look up information about
	each event without having to search all label layout structures (e.g.
	when compiling a set of user commands about what to do at each event
	into a state machine).

	Update the current layout structure version number.

	Introduce a named type to represent HLDS variable numbers in layout
	structures.

runtime/mercury_types.h:
	Add typedefs for the new types in mercury_stack_layout.h.

compiler/prog_data.m:
compiler/prog_event.m:
	Record the call that synthesizes synthesized attributes in terms of
	attribute numbers (needed by the layout structures) as well as in terms
	of attribute names (the user-friendly notation). Record some other 
	information now needed by the layout structures, e.g. the evaluation
	order of synthesized attributes. (Previously, we computed this order
	-in reverse- but then threw it away.)

	Do not separate out non-synthesized attributes, now that we can handle
	even synthesized ones. Return *all* attributes to call_gen.m.

	Pass the filename of the event set specification file to the event
	spec parser, for use in error messages.

	Generate better error messages for semantic errors in event set
	specifications.

compiler/continuation_info.m:
compiler/layout.m:
compiler/layout_out.m:
compiler/stack_layout.m:
	Generate the new layout structures, the main changes being the
	inclusion of synthesized attributes, and generating information about
	event attribute names, types and maybe synthesis calls for all possible
	events at once (for the module layout) instead of separately at each
	user event occurrence.

	In stack_layout.m, rename a couple of predicates to avoid ambiguities.

	In layout_out.m, eliminate some repetitions of terms.

compiler/call_gen.m:
	When processing event calls, match the supplied attributes against the
	list of all attributes, and include information about the synthesized
	attributes in the generated layout structures.

compiler/equiv_type.m:
compiler/module_qual.m:
	Conform to the change in prog_data.m.

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

compiler/hlds_out.m:
	Generate valid Mercury for event calls.

doc/user_guide.texi:
	Document synthesized attributes.

trace/mercury_event_spec.[ch]:
	Record the name of the file being parsed, for use in syntax error
	messages when the parser is invoked by the compiler.

	Add a field for recording the line numbers of attributes, for use in
	better error messages.

trace/mercury_event_parser.y:
trace/mercury_event_scanner.l:
	Record the line numbers of attributes.

	Modify the grammar for event set specifications to allow C-style
	comments.

trace/mercury_trace_cmd_internal.c
	Pass a dummy filename to mercury_event_spec. (The event set
	specifications recorded in layout structures should be free of errors,
	since the compiler generates them and it checked the original version
	for errors.)

trace/mercury_trace_tables.[ch]:
	Conform to the new design of layout structures, and record the extra
	information now available.

trace/mercury_trace_vars.[ch]:
	Record the values of attributes in two passes: first the
	non-synthesized attributes, then the synthesized attributes
	in the evaluation order recorded in the user event specification.

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/synth_attr.{m,inp,exp}:
tests/debugger/synth_attr_spec:
	New test case to test the debugger's handling of synthesized
	attributes.

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

tests/invalid/syntax_error_event.{m,err_exp}:
tests/invalid/syntax_error_event_spec:
	New test case to test the handling of syntax errors in event set
	specifications.

tests/invalid/synth_attr_error.{m,err_exp}:
tests/invalid/synth_attr_error_spec:
	New test case to test the handling of semantic errors in event set
	specifications.

tests/invalid/Mmakefile:
	Enable the new test cases.

Zoltan.

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.187
diff -u -b -r1.187 call_gen.m
--- compiler/call_gen.m	5 Dec 2006 03:50:47 -0000	1.187
+++ compiler/call_gen.m	8 Dec 2006 07:36:28 -0000
@@ -78,6 +78,7 @@
 
 :- import_module bool.
 :- import_module int.
+:- import_module maybe.
 :- import_module pair.
 :- import_module set.
 :- import_module string.
@@ -241,33 +242,49 @@
     module_info_get_event_set(ModuleInfo, EventSet),
     EventSpecMap = EventSet ^ event_set_spec_map,
     (
-        event_arg_names(EventSpecMap, EventName, AttributeNames),
+        event_attributes(EventSpecMap, EventName, Attributes),
         event_number(EventSpecMap, EventName, EventNumber)
     ->
-        generate_event_attributes(AttributeNames, Args, Attributes, AttrCodes,
-            !CI),
-        UserEventInfo = user_event_info(EventNumber, EventName, Attributes),
+        generate_event_attributes(Attributes, Args, MaybeUserAttributes,
+            AttrCodes, !CI),
+        UserEventInfo = user_event_info(EventNumber, MaybeUserAttributes),
         generate_user_event_code(UserEventInfo, GoalInfo, EventCode, !CI),
         Code = tree(tree_list(AttrCodes), EventCode)
     ;
         unexpected(this_file, "generate_event_call: bad event name")
     ).
 
-:- pred generate_event_attributes(list(string)::in, list(prog_var)::in,
-    list(user_attribute)::out, list(code_tree)::out,
+:- pred generate_event_attributes(list(event_attribute)::in,
+    list(prog_var)::in, list(maybe(user_attribute))::out, list(code_tree)::out,
     code_info::in, code_info::out) is det.
 
-generate_event_attributes([], [], [], [], !CI).
-generate_event_attributes([], [_ | _], _, _, !CI) :-
-    unexpected(this_file, "generate_event_attributes: list length mismatch").
-generate_event_attributes([_ | _], [], _, _, !CI) :-
-    unexpected(this_file, "generate_event_attributes: list length mismatch").
-generate_event_attributes([Name | Names], [Var | Vars], [Attr | Attrs],
-        [Code | Codes], !CI) :-
+generate_event_attributes([], !.Vars, [], [], !CI) :-
+    (
+        !.Vars = [_ | _],
+        unexpected(this_file, "generate_event_attributes: var")
+    ;
+        !.Vars = []
+    ).
+generate_event_attributes([Attribute | Attributes], !.Vars,
+        [MaybeUserAttr | MaybeUserAttrs], [Code | Codes], !CI) :-
+    SynthCall = Attribute ^ attr_maybe_synth_call,
+    (
+        SynthCall = no,
+        (
+            !.Vars = [Var | !:Vars],
     produce_variable(Var, Code, Rval, !CI),
-    Type = variable_type(!.CI, Var),
-    Attr = user_attribute(Rval, Type, Name, Var),
-    generate_event_attributes(Names, Vars, Attrs, Codes, !CI).
+            UserAttr = user_attribute(Rval, Var),
+            MaybeUserAttr = yes(UserAttr)
+        ;
+            !.Vars = [],
+            unexpected(this_file, "generate_event_attributes: no var")
+        )
+    ;
+        SynthCall = yes(_),
+        MaybeUserAttr = no,
+        Code = empty
+    ),
+    generate_event_attributes(Attributes, !.Vars, MaybeUserAttrs, Codes, !CI).
 
 %---------------------------------------------------------------------------%
 
Index: compiler/continuation_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/continuation_info.m,v
retrieving revision 1.84
diff -u -b -r1.84 continuation_info.m
--- compiler/continuation_info.m	5 Dec 2006 03:50:49 -0000	1.84
+++ compiler/continuation_info.m	8 Dec 2006 07:23:18 -0000
@@ -275,16 +275,13 @@
 :- type user_attribute
     --->    user_attribute(
                 attr_locn               :: rval,
-                attr_type               :: mer_type,
-                attr_name               :: string,
                 attr_var                :: prog_var
             ).
 
 :- type user_event_info
     --->    user_event_info(
                 user_port_number      :: int,
-                user_port_name        :: string,
-                user_attributes       :: list(user_attribute)
+                user_attributes       :: list(maybe(user_attribute))
             ).
 
 :- type closure_layout_info
Index: compiler/equiv_type.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/equiv_type.m,v
retrieving revision 1.76
diff -u -b -r1.76 equiv_type.m
--- compiler/equiv_type.m	1 Dec 2006 15:03:55 -0000	1.76
+++ compiler/equiv_type.m	6 Dec 2006 16:55:35 -0000
@@ -541,14 +541,12 @@
 
 replace_in_event_spec(EventSpec0, EventSpec, EqvMap, EqvInstMap,
         !RecompInfo, !UsedModules, !Specs) :-
-    EventSpec0 = event_spec(EventNumber, EventLineNumber,
-        VisAttrs0, AllAttrs0),
-    replace_in_event_attrs(VisAttrs0, VisAttrs, EqvMap, EqvInstMap,
-        !RecompInfo, !UsedModules, !Specs),
-    replace_in_event_attrs(AllAttrs0, AllAttrs, EqvMap, EqvInstMap,
+    EventSpec0 = event_spec(EventNumber, EventName, EventLineNumber,
+        Attrs0, SyntAttrNumOrder),
+    replace_in_event_attrs(Attrs0, Attrs, EqvMap, EqvInstMap,
         !RecompInfo, !UsedModules, !Specs),
-    EventSpec = event_spec(EventNumber, EventLineNumber,
-        VisAttrs, AllAttrs).
+    EventSpec = event_spec(EventNumber, EventName, EventLineNumber,
+        Attrs, SyntAttrNumOrder).
 
 :- pred replace_in_event_attrs(
     list(event_attribute)::in, list(event_attribute)::out,
@@ -576,12 +574,14 @@
         !RecompInfo, !UsedModules, !Specs) :-
     % We construct the attributes' modes ourselves in event_spec.m; they should
     % not contain type names.
-    Attr0 = event_attribute(AttrName, AttrType0, AttrMode, MaybeSynthCall),
+    Attr0 = event_attribute(AttrNum, AttrName, AttrType0, AttrMode,
+        MaybeSynthCall),
     TVarSet0 = varset.init,
     replace_in_type_location(eqv_type_out_of_module, EqvMap,
         AttrType0, AttrType, _Changed, TVarSet0, _TVarSet, no, _EquivTypeInfo,
         !UsedModules),
-    Attr = event_attribute(AttrName, AttrType, AttrMode, MaybeSynthCall).
+    Attr = event_attribute(AttrNum, AttrName, AttrType, AttrMode,
+        MaybeSynthCall).
 
 :- pred replace_in_type_defn(eqv_type_location::in, eqv_map::in, type_ctor::in,
     type_defn::in, type_defn::out, bool::out, tvarset::in, tvarset::out,
Index: compiler/hlds_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hlds_out.m,v
retrieving revision 1.413
diff -u -b -r1.413 hlds_out.m
--- compiler/hlds_out.m	5 Dec 2006 03:50:51 -0000	1.413
+++ compiler/hlds_out.m	8 Dec 2006 15:16:31 -0000
@@ -1777,15 +1777,16 @@
         globals.io_lookup_string_option(dump_hlds_options, Verbose, !IO),
         ( string.contains_char(Verbose, 'l') ->
             write_indent(Indent, !IO),
-            io.write_string("% event call\n", !IO)
+            io.write_string("% event call\n", !IO),
+            write_indent(Indent, !IO),
+            io.write_string("event ", !IO)
         ;
-            true
+            write_indent(Indent, !IO)
         ),
         term.context_init(Context),
         Functor = term.atom(EventName),
         term.var_list_to_term_list(ArgVars, ArgTerms),
         Term = term.functor(Functor, ArgTerms, Context),
-        write_indent(Indent, !IO),
         mercury_output_term(VarSet, AppendVarNums, Term, !IO),
         io.write_string(Follow, !IO)
     ;
Index: compiler/layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout.m,v
retrieving revision 1.32
diff -u -b -r1.32 layout.m
--- compiler/layout.m	5 Dec 2006 03:50:53 -0000	1.32
+++ compiler/layout.m	8 Dec 2006 07:11:24 -0000
@@ -44,8 +44,8 @@
 :- import_module assoc_list.
 :- import_module bool.
 :- import_module list.
+:- import_module map.
 :- import_module maybe.
-:- import_module pair.
 
 %-----------------------------------------------------------------------------%
 
@@ -53,6 +53,14 @@
 :- type string_with_0s
     --->    string_with_0s(string).
 
+:- type event_set_layout_data
+    --->    event_set_layout_data(
+                event_set_data,
+                map(int, rval)          % Maps each event number to an rval
+                                        % that gives the vector of typeinfos
+                                        % for the arguments of that event.
+            ).
+
 :- type layout_data
     --->    label_layout_data(          % defines MR_LabelLayout
                 proc_label              :: proc_label,
@@ -79,8 +87,7 @@
                 trace_level             :: trace_level,
                 suppressed_events       :: int,
                 num_label_exec_count    :: int,
-                maybe_event_specs       :: maybe(pair(string, string))
-                                        % event set name, event specifications
+                maybe_event_specs       :: maybe(event_set_layout_data)
             )
     ;       closure_proc_id_data(       % defines MR_ClosureId
                 caller_proc_label       :: proc_label,
@@ -104,12 +111,8 @@
 :- type user_event_data
     --->    user_event_data(
                 user_event_number       :: int,
-                user_event_name         :: string,
-                user_event_num_attr     :: int,
                 user_event_locns        :: rval,
-                user_event_types        :: rval,
-                user_event_names        :: list(string),
-                user_event_var_nums     :: list(int)
+                user_event_var_nums     :: list(maybe(int))
             ).
 
 :- type label_var_info
@@ -203,7 +206,6 @@
 :- type layout_name
     --->    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,
@@ -226,6 +228,11 @@
     ;       module_layout_file_vector(module_name)
     ;       module_layout_proc_vector(module_name)
     ;       module_layout_label_exec_count(module_name, int)
+    ;       module_layout_event_set_desc(module_name)
+    ;       module_layout_event_arg_names(module_name, int)
+    ;       module_layout_event_synth_attrs(module_name, int)
+    ;       module_layout_event_synth_attr_args(module_name, int, int)
+    ;       module_layout_event_synth_order(module_name, int)
     ;       module_layout_event_specs(module_name)
     ;       module_layout(module_name)
     ;       proc_static(rtti_proc_label)
Index: compiler/layout_out.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/layout_out.m,v
retrieving revision 1.80
diff -u -b -r1.80 layout_out.m
--- compiler/layout_out.m	5 Dec 2006 03:50:54 -0000	1.80
+++ compiler/layout_out.m	8 Dec 2006 09:08:08 -0000
@@ -109,8 +109,10 @@
 :- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_foreign.
 
+:- import_module assoc_list.
 :- import_module int.
 :- import_module list.
+:- import_module map.
 :- import_module maybe.
 :- import_module pair.
 :- import_module string.
@@ -239,12 +241,6 @@
         io.write_string(
             label_to_c_string(internal_label(LabelNum, ProcLabel), yes), !IO)
     ;
-        Data = user_event_attr_names(ProcLabel, LabelNum),
-        io.write_string(mercury_data_prefix, !IO),
-        io.write_string("_user_event_attr_names__", !IO),
-        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),
@@ -339,6 +335,47 @@
         ModuleNameStr = sym_name_mangle(ModuleName),
         io.write_string(ModuleNameStr, !IO)
     ;
+        Data = module_layout_event_set_desc(ModuleName),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_layout_event_set_desc__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO)
+    ;
+        Data = module_layout_event_arg_names(ModuleName, EventNumber),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_layout_event_arg_names__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO),
+        io.write_string("_", !IO),
+        io.write_int(EventNumber, !IO)
+    ;
+        Data = module_layout_event_synth_attrs(ModuleName, EventNumber),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_layout_event_synth_attrs__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO),
+        io.write_string("_", !IO),
+        io.write_int(EventNumber, !IO)
+    ;
+        Data = module_layout_event_synth_attr_args(ModuleName,
+            EventNumber, SynthCallArgNumber),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_layout_event_synth_attr_args__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO),
+        io.write_string("_", !IO),
+        io.write_int(EventNumber, !IO),
+        io.write_string("_", !IO),
+        io.write_int(SynthCallArgNumber, !IO)
+    ;
+        Data = module_layout_event_synth_order(ModuleName, EventNumber),
+        io.write_string(mercury_data_prefix, !IO),
+        io.write_string("_module_layout_event_synth_order__", !IO),
+        ModuleNameStr = sym_name_mangle(ModuleName),
+        io.write_string(ModuleNameStr, !IO),
+        io.write_string("_", !IO),
+        io.write_int(EventNumber, !IO)
+    ;
         Data = module_layout_event_specs(ModuleName),
         io.write_string(mercury_data_prefix, !IO),
         io.write_string("_module_layout_event_specs__", !IO),
@@ -370,29 +407,24 @@
         output_proc_label_no_prefix(ProcLabel, !IO)
     ).
 
-output_layout_name_storage_type_name(Data, BeingDefined, !IO) :-
+output_layout_name_storage_type_name(Name, BeingDefined, !IO) :-
     (
-        Data = label_layout(ProcLabel, LabelNum, LabelVars),
+        Name = label_layout(_ProcLabel, _LabelNum, LabelVars),
         io.write_string("static const ", !IO),
         io.write_string(label_vars_to_type(LabelVars), !IO),
         io.write_string(" ", !IO),
-        output_layout_name(label_layout(ProcLabel, LabelNum, LabelVars), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = user_event_layout(ProcLabel, LabelNum),
+        Name = user_event_layout(_ProcLabel, _LabelNum),
         io.write_string("static const struct MR_UserEvent_Struct ", !IO),
-        output_layout_name(user_event_layout(ProcLabel, LabelNum), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = user_event_attr_names(ProcLabel, LabelNum),
-        io.write_string("static const char * ", !IO),
-        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),
+        Name = user_event_attr_var_nums(_ProcLabel, _LabelNum),
+        io.write_string("static const MR_HLDSVarNum ", !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = proc_layout(ProcLabel, Kind),
+        Name = proc_layout(ProcLabel, Kind),
         ProcIsImported = ProcLabel ^ proc_is_imported,
         ProcIsExported = ProcLabel ^ proc_is_exported,
         (
@@ -411,31 +443,31 @@
         io.write_string("const ", !IO),
         io.write_string(proc_layout_kind_to_type(Kind), !IO),
         io.write_string(" ", !IO),
-        output_layout_name(proc_layout(ProcLabel, Kind), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = proc_layout_exec_trace(ProcLabel),
+        Name = proc_layout_exec_trace(_ProcLabel),
         io.write_string("static MR_STATIC_CODE_CONST MR_ExecTrace\n\t", !IO),
-        output_layout_name(proc_layout_exec_trace(ProcLabel), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = proc_layout_head_var_nums(ProcLabel),
+        Name = proc_layout_head_var_nums(_ProcLabel),
         io.write_string("static const ", !IO),
         io.write_string("MR_uint_least16_t ", !IO),
-        output_layout_name(proc_layout_head_var_nums(ProcLabel), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = proc_layout_var_names(ProcLabel),
+        Name = proc_layout_var_names(_ProcLabel),
         io.write_string("static const ", !IO),
         io.write_string("MR_uint_least32_t ", !IO),
-        output_layout_name(proc_layout_var_names(ProcLabel), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = proc_layout_body_bytecode(ProcLabel),
+        Name = proc_layout_body_bytecode(_ProcLabel),
         io.write_string("static const ", !IO),
         io.write_string("MR_uint_least8_t ", !IO),
-        output_layout_name(proc_layout_body_bytecode(ProcLabel), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = closure_proc_id(CallerProcLabel, SeqNo, ClosureProcLabel),
+        Name = closure_proc_id(_CallerProcLabel, _SeqNo, ClosureProcLabel),
         io.write_string("static const ", !IO),
         (
             ClosureProcLabel = ordinary_proc_label(_, _, _, _, _, _),
@@ -444,74 +476,95 @@
             ClosureProcLabel = special_proc_label(_, _, _, _, _, _),
             io.write_string("MR_UCIClosureId\n", !IO)
         ),
-        output_layout_name(closure_proc_id(CallerProcLabel, SeqNo,
-            ClosureProcLabel), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = file_layout(ModuleName, FileNum),
+        Name = file_layout(_ModuleName, _FileNum),
         io.write_string("static const MR_ModuleFileLayout ", !IO),
-        output_layout_name(file_layout(ModuleName, FileNum), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = file_layout_line_number_vector(ModuleName, FileNum),
+        Name = file_layout_line_number_vector(_ModuleName, _FileNum),
         io.write_string("static const MR_int_least16_t ", !IO),
-        output_layout_name(
-            file_layout_line_number_vector(ModuleName, FileNum), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = file_layout_label_layout_vector(ModuleName, FileNum),
+        Name = file_layout_label_layout_vector(_ModuleName, _FileNum),
         io.write_string("static const MR_LabelLayout *", !IO),
-        output_layout_name(
-            file_layout_label_layout_vector(ModuleName, FileNum), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = module_layout_string_table(ModuleName),
+        Name = module_layout_string_table(_ModuleName),
         io.write_string("static const char ", !IO),
-        output_layout_name(module_layout_string_table(ModuleName), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = module_layout_file_vector(ModuleName),
+        Name = module_layout_file_vector(_ModuleName),
         io.write_string("static const MR_ModuleFileLayout *", !IO),
-        output_layout_name(module_layout_file_vector(ModuleName), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = module_layout_label_exec_count(ModuleName, NumElements),
+        Name = module_layout_label_exec_count(_ModuleName, NumElements),
         io.write_string("static MR_Unsigned ", !IO),
-        output_layout_name(
-            module_layout_label_exec_count(ModuleName, NumElements), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[", !IO),
         io.write_int(NumElements, !IO),
         io.write_string("]", !IO)
     ;
-        Data = module_layout_proc_vector(ModuleName),
+        Name = module_layout_proc_vector(_ModuleName),
         io.write_string("static const MR_ProcLayout *", !IO),
-        output_layout_name(module_layout_proc_vector(ModuleName), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = module_layout_event_specs(ModuleName),
+        Name = module_layout_event_set_desc(_ModuleName),
         io.write_string("static const char ", !IO),
-        output_layout_name(module_layout_event_specs(ModuleName), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = module_layout(ModuleName),
+        Name = module_layout_event_arg_names(_ModuleName, _EventNumber),
+        io.write_string("static const char * ", !IO),
+        output_layout_name(Name, !IO),
+        io.write_string("[]", !IO)
+    ;
+        Name = module_layout_event_synth_attrs(_ModuleName, _EventNumber),
+        io.write_string("static MR_SynthAttr ", !IO),
+        output_layout_name(Name, !IO),
+        io.write_string("[]", !IO)
+    ;
+        Name = module_layout_event_synth_attr_args(_ModuleName,
+            _EventNumber, _SynthCallArgNumber),
+        io.write_string("static MR_uint_least16_t ", !IO),
+        output_layout_name(Name, !IO),
+        io.write_string("[]", !IO)
+    ;
+        Name = module_layout_event_synth_order(_ModuleName, _EventNumber),
+        io.write_string("static MR_int_least16_t ", !IO),
+        output_layout_name(Name, !IO),
+        io.write_string("[]", !IO)
+    ;
+        Name = module_layout_event_specs(_ModuleName),
+        io.write_string("static MR_UserEventSpec ", !IO),
+        output_layout_name(Name, !IO),
+        io.write_string("[]", !IO)
+    ;
+        Name = module_layout(_ModuleName),
         io.write_string("static const MR_ModuleLayout ", !IO),
-        output_layout_name(module_layout(ModuleName), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = proc_static(RttiProcLabel),
+        Name = proc_static(_RttiProcLabel),
         io.write_string("static MR_ProcStatic ", !IO),
-        output_layout_name(proc_static(RttiProcLabel), !IO)
+        output_layout_name(Name, !IO)
     ;
-        Data = proc_static_call_sites(RttiProcLabel),
+        Name = proc_static_call_sites(_RttiProcLabel),
         io.write_string("static const MR_CallSiteStatic ", !IO),
-        output_layout_name(proc_static_call_sites(RttiProcLabel), !IO),
+        output_layout_name(Name, !IO),
         io.write_string("[]", !IO)
     ;
-        Data = table_io_decl(RttiProcLabel),
+        Name = table_io_decl(_RttiProcLabel),
         io.write_string("static const MR_TableIoDecl ", !IO),
-        output_layout_name(table_io_decl(RttiProcLabel), !IO)
+        output_layout_name(Name, !IO)
     ).
 
 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.
@@ -527,6 +580,14 @@
 layout_name_would_include_code_addr(module_layout_file_vector(_)) = no.
 layout_name_would_include_code_addr(module_layout_proc_vector(_)) = no.
 layout_name_would_include_code_addr(module_layout_label_exec_count(_, _)) = no.
+layout_name_would_include_code_addr(module_layout_event_set_desc(_)) = no.
+layout_name_would_include_code_addr(module_layout_event_arg_names(_, _)) = no.
+layout_name_would_include_code_addr(module_layout_event_synth_attrs(_, _))
+    = no.
+layout_name_would_include_code_addr(
+    module_layout_event_synth_attr_args(_, _, _)) = no.
+layout_name_would_include_code_addr(module_layout_event_synth_order(_, _))
+    = no.
 layout_name_would_include_code_addr(module_layout_event_specs(_)) = no.
 layout_name_would_include_code_addr(module_layout(_)) = no.
 layout_name_would_include_code_addr(proc_static(_)) = no.
@@ -579,24 +640,15 @@
     ;
         MaybeUserData = yes(UserData),
         UserChars = "_U",
-        UserData = user_event_data(UserEventNumber, UserEventName,
-            UserNumAttributes, UserLocnsRval, UserTypesRval,
-            UserAttrNames, UserAttrVarNums),
-
-        AttrNamesLayoutName = user_event_attr_names(ProcLabel, LabelNum),
-        AttrNamesDataAddr = layout_addr(AttrNamesLayoutName),
-        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\n", !IO),
+        UserData = user_event_data(UserEventNumber, UserLocnsRval,
+            UserAttrMaybeVarNums),
 
         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_list(UserAttrMaybeVarNums, ", ", output_maybe_var_num, !IO),
         io.write_string("\n};\n\n", !IO),
 
         UserLayoutName = user_event_layout(ProcLabel, LabelNum),
@@ -605,16 +657,8 @@
         output_layout_name_storage_type_name(UserLayoutName, no, !IO),
         io.write_string(" = {\n", !IO),
         io.write_int(UserEventNumber, !IO),
-        io.write_string(",\n""", !IO),
-        io.write_string(UserEventName, !IO),
-        io.write_string(""",\n", !IO),
-        io.write_int(UserNumAttributes, !IO),
         io.write_string(",\n(MR_LongLval *) ", !IO),
         output_rval_as_addr(UserLocnsRval, !IO),
-        io.write_string(",\n(MR_TypeInfo *) ", !IO),
-        output_rval_as_addr(UserTypesRval, !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)
@@ -721,6 +765,14 @@
     io.write_string(");\n", !IO),
     decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
+:- pred output_maybe_var_num(maybe(int)::in, io::di, io::uo) is det.
+
+output_maybe_var_num(no, !IO) :-
+    % Zero means not a variable, which is what we want.
+    io.write_int(0, !IO).
+output_maybe_var_num(yes(VarNum), !IO) :-
+    io.write_int(VarNum, !IO).
+
     % Output the rval in a context in which it is immediately cast to an
     % address.
     %
@@ -1343,12 +1395,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(pair(string, string))::in,
+    trace_level::in, int::in, int::in, maybe(event_set_layout_data)::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
 output_module_layout_data_defn(ModuleName, StringTableSize, StringTable,
         ProcLayoutNames, FileLayouts, TraceLevel, SuppressedEvents,
-        NumLabels, MaybeEventSet, !DeclSet, !IO) :-
+        NumLabels, MaybeEventSetLayout, !DeclSet, !IO) :-
     output_module_string_table(ModuleName, StringTableSize, StringTable,
         !DeclSet, !IO),
     output_module_layout_proc_vector_defn(ModuleName, ProcLayoutNames,
@@ -1366,10 +1418,16 @@
     decl_set_insert(decl_data_addr(layout_addr(LabelExecCountName)), !DeclSet),
 
     (
-        MaybeEventSet = no
+        MaybeEventSetLayout = no
     ;
-        MaybeEventSet = yes(_EventSetName - EventSpecs),
-        output_event_specs_defn(ModuleName, EventSpecs, !DeclSet, !IO)
+        MaybeEventSetLayout = yes(EventSetDataLayout),
+        EventSetDataLayout =
+            event_set_layout_data(EventSetDataA, TypesRvalMap),
+        EventSetDataA = event_set_data(_EventSetName, EventSetDesc,
+            EventSpecsA, _MaxNumAttr),
+        output_event_set_desc_defn(ModuleName, EventSetDesc, !DeclSet, !IO),
+        output_event_specs_and_components(EventSpecsA, ModuleName,
+            TypesRvalMap, !DeclSet, !IO)
     ),
 
     ModuleLayoutName = module_layout(ModuleName),
@@ -1404,19 +1462,186 @@
     output_layout_name(LabelExecCountName, !IO),
     io.write_string(",\n", !IO),
     (
-        MaybeEventSet = no,
+        MaybeEventSetLayout = no,
+        io.write_string("NULL,\n", !IO),
         io.write_string("NULL,\n", !IO),
+        io.write_string("0,\n", !IO),
+        io.write_string("0,\n", !IO),
         io.write_string("NULL", !IO)
     ;
-        MaybeEventSet = yes(EventSetName - _),
+        MaybeEventSetLayout = yes(EventSetDataLayoutB),
+        EventSetDataLayoutB =
+            event_set_layout_data(EventSetDataB, _TypesRvalMap),
+        EventSetDataB = event_set_data(EventSetName, _EventSetDesc,
+            EventSpecsB, MaxNumAttr),
         quote_and_write_string(EventSetName, !IO),
         io.write_string(",\n", !IO),
+        EventSetDescLayoutName = module_layout_event_set_desc(ModuleName),
+        output_layout_name(EventSetDescLayoutName, !IO),
+        io.write_string(",\n", !IO),
+        io.write_int(MaxNumAttr, !IO),
+        io.write_string(",\n", !IO),
+        io.write_int(list.length(EventSpecsB), !IO),
+        io.write_string(",\n", !IO),
         EventSpecLayoutName = module_layout_event_specs(ModuleName),
         output_layout_name(EventSpecLayoutName, !IO)
     ),
     io.write_string("\n};\n", !IO),
     decl_set_insert(decl_data_addr(layout_addr(ModuleLayoutName)), !DeclSet).
 
+:- pred output_event_specs_and_components(list(event_spec)::in,
+    module_name::in, map(int, rval)::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_event_specs_and_components(EventSpecs, ModuleName, TypesRvalMap,
+        !DeclSet, !IO) :-
+    list.foldl2(output_event_spec_components(ModuleName), EventSpecs,
+        !DeclSet, !IO),
+
+    LayoutName = module_layout_event_specs(ModuleName),
+    DataAddr = layout_addr(LayoutName),
+    decl_set_insert(decl_data_addr(DataAddr), !DeclSet),
+    output_layout_name_storage_type_name(LayoutName, yes, !IO),
+    io.write_string(" = {\n", !IO),
+    io.write_list(EventSpecs, ",\n",
+        output_event_spec(ModuleName, TypesRvalMap), !IO),
+    io.write_string("\n};\n\n", !IO).
+
+:- pred output_event_spec_components(module_name::in, event_spec::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_event_spec_components(ModuleName, EventSpec, !DeclSet, !IO) :-
+    EventSpec = event_spec(EventNumber, _EventName, _EventLineNumber,
+        Attrs, SynthOrder),
+
+    AttrNamesLayoutName =
+        module_layout_event_arg_names(ModuleName, EventNumber),
+    AttrNamesDataAddr = layout_addr(AttrNamesLayoutName),
+    decl_set_insert(decl_data_addr(AttrNamesDataAddr), !DeclSet),
+    output_layout_name_storage_type_name(AttrNamesLayoutName, yes, !IO),
+    io.write_string(" = {\n", !IO),
+    io.write_list(Attrs, ", ", output_attr_name, !IO),
+    io.write_string("\n};\n\n", !IO),
+
+    (
+        SynthOrder = []
+    ;
+        SynthOrder = [_ | _],
+
+        list.foldl2(output_synth_attr_args(ModuleName, EventNumber),
+            Attrs, !DeclSet, !IO),
+
+        SynthAttrsLayoutName =
+            module_layout_event_synth_attrs(ModuleName, EventNumber),
+        SynthAttrsDataAddr = layout_addr(SynthAttrsLayoutName),
+        decl_set_insert(decl_data_addr(SynthAttrsDataAddr), !DeclSet),
+        output_layout_name_storage_type_name(SynthAttrsLayoutName, yes, !IO),
+        io.write_string(" = {\n", !IO),
+        io.write_list(Attrs, ",\n",
+            output_synth_attr(ModuleName, EventNumber), !IO),
+        io.write_string("\n};\n\n", !IO),
+
+        SynthOrderLayoutName =
+            module_layout_event_synth_order(ModuleName, EventNumber),
+        SynthOrderDataAddr = layout_addr(SynthOrderLayoutName),
+        decl_set_insert(decl_data_addr(SynthOrderDataAddr), !DeclSet),
+        output_layout_name_storage_type_name(SynthOrderLayoutName, yes, !IO),
+        io.write_string(" = {\n", !IO),
+        % The -1 acts as sentinel.
+        io.write_list(SynthOrder ++ [-1], ", ", io.write_int, !IO),
+        io.write_string("\n};\n\n", !IO)
+    ).
+
+:- pred output_attr_name(event_attribute::in, io::di, io::uo) is det.
+
+output_attr_name(Attr, !IO) :-
+    io.write_string("""", !IO),
+    io.write_string(Attr ^ attr_name, !IO),
+    io.write_string("""", !IO).
+
+:- pred output_synth_attr_args(module_name::in, int::in, event_attribute::in,
+    decl_set::in, decl_set::out, io::di, io::uo) is det.
+
+output_synth_attr_args(ModuleName, EventNumber, Attr, !DeclSet, !IO) :-
+    MaybeSynthCall = Attr ^ attr_maybe_synth_call,
+    (
+        MaybeSynthCall = yes(SynthCall),
+        SynthCall = event_attr_synth_call(_FuncAttrNameNum, ArgAttrNameNums),
+        assoc_list.values(ArgAttrNameNums, ArgAttrNums),
+        AttrNumber = Attr ^ attr_num,
+        LayoutName = module_layout_event_synth_attr_args(ModuleName,
+            EventNumber, AttrNumber),
+
+        DataAddr = layout_addr(LayoutName),
+        decl_set_insert(decl_data_addr(DataAddr), !DeclSet),
+        output_layout_name_storage_type_name(LayoutName, yes, !IO),
+        io.write_string(" =\n{ ", !IO),
+        io.write_list(ArgAttrNums, ", ", io.write_int, !IO),
+        io.write_string(" };\n\n", !IO)
+    ;
+        MaybeSynthCall = no
+    ).
+
+:- pred output_synth_attr(module_name::in, int::in, event_attribute::in,
+    io::di, io::uo) is det.
+
+output_synth_attr(ModuleName, EventNumber, Attr, !IO) :-
+    io.write_string("{ ", !IO),
+    MaybeSynthCall = Attr ^ attr_maybe_synth_call,
+    (
+        MaybeSynthCall = yes(SynthCall),
+        SynthCall = event_attr_synth_call(_FuncAttrName - FuncAttrNum,
+            ArgAttrNameNums),
+        io.write_int(FuncAttrNum, !IO),
+        io.write_string(", ", !IO),
+        io.write_int(list.length(ArgAttrNameNums), !IO),
+        io.write_string(", ", !IO),
+        AttrNumber = Attr ^ attr_num,
+        LayoutName = module_layout_event_synth_attr_args(ModuleName,
+            EventNumber, AttrNumber),
+        output_layout_name(LayoutName, !IO)
+    ;
+        MaybeSynthCall = no,
+        io.write_string("-1, -1, NULL", !IO)
+    ),
+    io.write_string(" }", !IO).
+
+:- pred output_event_spec(module_name::in, map(int, rval)::in, event_spec::in,
+    io::di, io::uo) is det.
+
+output_event_spec(ModuleName, TypesRvalMap, EventSpec, !IO) :-
+    EventSpec = event_spec(EventNumber, EventName, _EventLineNumber, Attrs,
+        SynthOrder),
+    map.lookup(TypesRvalMap, EventNumber, TypesRval),
+
+    io.write_string("{ """, !IO),
+    io.write_string(EventName, !IO),
+    io.write_string(""", ", !IO),
+    io.write_int(list.length(Attrs), !IO),
+    io.write_string(",\n\t", !IO),
+
+    AttrNamesLayoutName =
+        module_layout_event_arg_names(ModuleName, EventNumber),
+    output_layout_name(AttrNamesLayoutName, !IO),
+    io.write_string(",\n\t(MR_TypeInfo *) ", !IO),
+    output_rval_as_addr(TypesRval, !IO),
+    io.write_string(",\n\t", !IO),
+
+    (
+        SynthOrder = [],
+        io.write_string("NULL, NULL }", !IO)
+    ;
+        SynthOrder = [_ | _],
+        SynthAttrsLayoutName =
+            module_layout_event_synth_attrs(ModuleName, EventNumber),
+        SynthOrderLayoutName =
+            module_layout_event_synth_order(ModuleName, EventNumber),
+        output_layout_name(SynthAttrsLayoutName, !IO),
+        io.write_string(",\n\t", !IO),
+        output_layout_name(SynthOrderLayoutName, !IO),
+        io.write_string(" }", !IO)
+    ).
+
 :- pred output_module_layout_proc_vector_defn(module_name::in,
     list(layout_name)::in, layout_name::out, decl_set::in, decl_set::out,
     io::di, io::uo) is det.
@@ -1456,17 +1681,17 @@
 
 %-----------------------------------------------------------------------------%
 
-:- pred output_event_specs_defn(module_name::in, string::in,
+:- pred output_event_set_desc_defn(module_name::in, string::in,
     decl_set::in, decl_set::out, io::di, io::uo) is det.
 
-output_event_specs_defn(ModuleName, EventSpecs, !DeclSet, !IO) :-
-    LayoutName = module_layout_event_specs(ModuleName),
+output_event_set_desc_defn(ModuleName, EventSetDesc, !DeclSet, !IO) :-
+    LayoutName = module_layout_event_set_desc(ModuleName),
     io.write_string("\n", !IO),
     output_layout_name_storage_type_name(LayoutName, yes, !IO),
     io.write_string(" = {", !IO),
-    string.length(EventSpecs, EventSpecsSize),
-    output_module_string_table_chars_driver(0, EventSpecsSize - 1,
-        string_with_0s(EventSpecs), !IO),
+    string.length(EventSetDesc, EventSetDescSize),
+    output_module_string_table_chars_driver(0, EventSetDescSize - 1,
+        string_with_0s(EventSetDesc), !IO),
     io.write_string("};\n", !IO),
     decl_set_insert(decl_data_addr(layout_addr(LayoutName)), !DeclSet).
 
Index: compiler/module_qual.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/module_qual.m,v
retrieving revision 1.153
diff -u -b -r1.153 module_qual.m
--- compiler/module_qual.m	1 Dec 2006 15:04:11 -0000	1.153
+++ compiler/module_qual.m	6 Dec 2006 16:55:46 -0000
@@ -772,26 +772,22 @@
 do_module_qualify_event_specs(FileName,
         [Name - Spec0 | NameSpecs0], [Name - Spec | NameSpecs],
         !Info, !Specs) :-
-    do_module_qualify_event_spec(FileName, Name, Spec0, Spec, !Info, !Specs),
+    do_module_qualify_event_spec(FileName, Spec0, Spec, !Info, !Specs),
     do_module_qualify_event_specs(FileName, NameSpecs0, NameSpecs,
         !Info, !Specs).
 
-:- pred do_module_qualify_event_spec(string::in, string::in,
+:- pred do_module_qualify_event_spec(string::in,
     event_spec::in, event_spec::out, mq_info::in, mq_info::out,
     list(error_spec)::in, list(error_spec)::out) is det.
 
-do_module_qualify_event_spec(EventName, FileName, EventSpec0, EventSpec,
-        !Info, !Specs) :-
-    EventSpec0 = event_spec(EventNumber, EventLineNumber,
-        VisAttrs0, AllAttrs0),
-    list.map_foldl2(
-        do_module_qualify_event_attr(EventName, FileName, EventLineNumber),
-        VisAttrs0, VisAttrs, !Info, !Specs),
+do_module_qualify_event_spec(FileName, EventSpec0, EventSpec, !Info, !Specs) :-
+    EventSpec0 = event_spec(EventNumber, EventName, EventLineNumber,
+        Attrs0, SynthAttrNumOrder),
     list.map_foldl2(
         do_module_qualify_event_attr(EventName, FileName, EventLineNumber),
-        AllAttrs0, AllAttrs, !Info, !Specs),
-    EventSpec = event_spec(EventNumber, EventLineNumber,
-        VisAttrs, AllAttrs).
+        Attrs0, Attrs, !Info, !Specs),
+    EventSpec = event_spec(EventNumber, EventName, EventLineNumber,
+        Attrs, SynthAttrNumOrder).
 
 :- pred do_module_qualify_event_attr(string::in, string::in, int::in,
     event_attribute::in, event_attribute::out, mq_info::in, mq_info::out,
@@ -799,13 +795,15 @@
 
 do_module_qualify_event_attr(EventName, FileName, LineNumber, Attr0, Attr,
         !Info, !Specs) :-
-    Attr0 = event_attribute(AttrName, AttrType0, AttrMode0, MaybeSynthCall),
+    Attr0 = event_attribute(AttrNum, AttrName, AttrType0, AttrMode0,
+        MaybeSynthCall),
     MQErrorContext = mqec_event_spec_attr(EventName, AttrName),
     Context = context(FileName, LineNumber),
     mq_info_set_error_context(MQErrorContext - Context, !Info),
     qualify_type(AttrType0, AttrType, !Info, !Specs),
     qualify_mode(AttrMode0, AttrMode, !Info, !Specs),
-    Attr = event_attribute(AttrName, AttrType, AttrMode, MaybeSynthCall).
+    Attr = event_attribute(AttrNum, AttrName, AttrType, AttrMode,
+        MaybeSynthCall).
 
 :- pred update_import_status(module_defn::in, mq_info::in, mq_info::out,
     bool::out) is det.
Index: compiler/opt_debug.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/opt_debug.m,v
retrieving revision 1.183
diff -u -b -r1.183 opt_debug.m
--- compiler/opt_debug.m	5 Dec 2006 03:50:56 -0000	1.183
+++ compiler/opt_debug.m	8 Dec 2006 07:14:33 -0000
@@ -459,9 +459,6 @@
 dump_layout_name(user_event_layout(ProcLabel, LabelNum)) = Str :-
     LabelStr = dump_label(internal_label(LabelNum, ProcLabel)),
     Str = "user_event_layout(" ++ LabelStr ++ ")".
-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 ++ ")".
@@ -496,8 +493,24 @@
 dump_layout_name(module_layout_label_exec_count(ModuleName, NumLabels)) =
     "module_layout_label_exec_count(" ++ sym_name_mangle(ModuleName)
         ++ ", " ++ int_to_string(NumLabels) ++ ")".
+dump_layout_name(module_layout_event_set_desc(ModuleName)) =
+    "module_layout_event_set_desc(" ++ sym_name_mangle(ModuleName) ++ ")".
 dump_layout_name(module_layout_event_specs(ModuleName)) =
     "module_layout_event_specs(" ++ sym_name_mangle(ModuleName) ++ ")".
+dump_layout_name(module_layout_event_arg_names(ModuleName, EventNum)) =
+    "module_layout_event_arg_names(" ++ sym_name_mangle(ModuleName) ++
+        ", " ++ int_to_string(EventNum) ++ ")".
+dump_layout_name(module_layout_event_synth_attrs(ModuleName, EventNum)) =
+    "module_layout_event_synth_attrs(" ++ sym_name_mangle(ModuleName) ++
+        ", " ++ int_to_string(EventNum) ++ ")".
+dump_layout_name(module_layout_event_synth_attr_args(ModuleName,
+        EventNum, ArgNum)) =
+    "module_layout_event_synth_attrs(" ++ sym_name_mangle(ModuleName) ++
+        ", " ++ int_to_string(EventNum) ++
+        ", " ++ int_to_string(ArgNum) ++ ")".
+dump_layout_name(module_layout_event_synth_order(ModuleName, EventNum)) =
+    "module_layout_event_synth_order(" ++ sym_name_mangle(ModuleName) ++
+        ", " ++ int_to_string(EventNum) ++ ")".
 dump_layout_name(module_layout(ModuleName)) =
     "module_layout(" ++ sym_name_mangle(ModuleName) ++ ")".
 dump_layout_name(proc_static(RttiProcLabel)) =
Index: compiler/prog_data.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_data.m,v
retrieving revision 1.180
diff -u -b -r1.180 prog_data.m
--- compiler/prog_data.m	5 Dec 2006 03:50:57 -0000	1.180
+++ compiler/prog_data.m	6 Dec 2006 12:15:21 -0000
@@ -1559,6 +1559,7 @@
 
 :- type event_attribute
     --->    event_attribute(
+                attr_num                    :: int,
                 attr_name                   :: string,
                 attr_type                   :: mer_type,
                 attr_mode                   :: mer_mode,
@@ -1567,16 +1568,17 @@
 
 :- type event_attr_synth_call
     --->    event_attr_synth_call(
-                synth_func_attr_name        :: string,
-                synth_arg_attr_names        :: list(string)
+                synth_func_attr_name_num    :: pair(string, int),
+                synth_arg_attr_name_nums    :: assoc_list(string, int)
             ).
 
 :- type event_spec
     --->    event_spec(
                 event_spec_num              :: int,
+                event_spec_name             :: string,
                 event_spec_linenum          :: int,
-                event_spec_visible_attrs    :: list(event_attribute),
-                event_spec_all_attrs        :: list(event_attribute)
+                event_spec_attrs            :: list(event_attribute),
+                event_spec_synth_order      :: list(int)
             ).
 
     % This type maps the name of an event to the event's specification.
@@ -1588,6 +1590,14 @@
                 event_set_spec_map          :: event_spec_map
             ).
 
+:- type event_set_data
+    --->    event_set_data(
+                event_set_data_name         :: string,
+                event_set_data_description  :: string,
+                event_set_data_specs        :: list(event_spec),
+                event_set_data_max_num_attr :: int
+            ).
+
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
Index: compiler/prog_event.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_event.m,v
retrieving revision 1.5
diff -u -b -r1.5 prog_event.m
--- compiler/prog_event.m	5 Dec 2006 03:50:58 -0000	1.5
+++ compiler/prog_event.m	10 Dec 2006 15:56:49 -0000
@@ -34,16 +34,16 @@
 
     % Return a description of the given event set.
     %
-:- func event_set_description(event_spec_map) = string.
+:- func derive_event_set_data(event_set) = event_set_data.
 
     % Given an event name, returns its number.
     %
 :- pred event_number(event_spec_map::in, string::in, int::out) is semidet.
 
-    % Given an event name, returns the names of the arguments of the event.
+    % Given an event name, returns the attributes of the event.
     %
-:- pred event_arg_names(event_spec_map::in, string::in, list(string)::out)
-    is semidet.
+:- pred event_attributes(event_spec_map::in, string::in,
+    list(event_attribute)::out) is semidet.
 
     % Given an event name, returns the types of the arguments of the event.
     %
@@ -63,12 +63,15 @@
 :- import_module mdbcomp.prim_data.
 :- import_module parse_tree.prog_mode.
 :- import_module parse_tree.prog_out.
+:- import_module parse_tree.prog_type.
 
+:- import_module assoc_list.
 :- import_module bimap.
 :- import_module bool.
+:- import_module int.
+:- import_module map.
 :- import_module maybe.
 :- import_module pair.
-:- import_module map.
 :- import_module relation.
 :- import_module string.
 :- import_module svbimap.
@@ -100,7 +103,7 @@
             (
                 TermReadRes = ok(EventSetTerm),
                 EventSetTerm = event_set_spec(EventSetName, EventSpecsTerm),
-                convert_list_to_spec_map(TermFileName, EventSpecsTerm,
+                convert_list_to_spec_map(SpecsFileName, EventSpecsTerm,
                     map.init, EventSpecMap, [], ErrorSpecs)
             ;
                 TermReadRes = eof,
@@ -211,7 +214,7 @@
 
                     /* NULL terminate the string we have read in. */
                     spec_buf[num_bytes_read] = '\\0';
-                    event_set = MR_read_event_set(spec_buf);
+                    event_set = MR_read_event_set(SpecsFileName, spec_buf);
                     if (event_set == NULL) {
                         char    buf[4096];
 
@@ -259,23 +262,30 @@
     --->    event_spec_term(
                 event_name      :: string,
                 event_num       :: int,
-                event_linenum   :: int,
+                event_linenumber    :: int,
                 event_attrs     :: list(event_attr_term)
             ).
 
 :- type event_attr_term
     --->    event_attr_term(
                 attr_name       :: string,
+                attr_linenum        :: int,
                 attr_type       :: event_attr_type
             ).
 
+:- type event_attr_synth_call_term
+    --->    event_attr_synth_call_term(
+                func_attr_name  :: string,
+                arg_attr_names  :: list(string)
+            ).
+
 :- type event_attr_type
     --->    event_attr_type_ordinary(
                 event_attr_type_term
             )
     ;       event_attr_type_synthesized(
                 event_attr_type_term,
-                event_attr_synth_call
+                event_attr_synth_call_term
             )
     ;       event_attr_type_function.
 
@@ -322,28 +332,33 @@
     % It does the data format conversion, and performs the last checks.
 
     build_plain_type_map(EventName, FileName, EventLineNumber, AttrTerms,
-        map.init, AttrTypeMap0, bimap.init, KeyMap, relation.init, DepRel0,
-        !ErrorSpecs),
-    build_dep_map(EventName, FileName, EventLineNumber, KeyMap, AttrTerms,
+        0, map.init, AttrMap, map.init, AttrTypeMap0, bimap.init, KeyMap,
+        relation.init, DepRel0, !ErrorSpecs),
+    build_dep_map(EventName, FileName, AttrMap, KeyMap, AttrTerms,
         AttrTypeMap0, AttrTypeMap, DepRel0, DepRel, !ErrorSpecs),
-    convert_terms_to_attrs(EventName, FileName, EventLineNumber, AttrTypeMap,
-        AttrTerms, [], RevVisAttrs, [], RevAllAttrs, !ErrorSpecs),
-    ( relation.tsort(DepRel, _AttrOrder) ->
+    convert_terms_to_attrs(EventName, FileName, AttrMap, AttrTypeMap,
+        0, AttrTerms, [], RevAttrs, !ErrorSpecs),
+    ( relation.tsort(DepRel, AllAttrNameOrder) ->
         % There is an order for computing the synthesized attributes.
-        % XXX We should record this order for use by the debugger.
-        true
+        % list.reverse(RevAllAttrNameOrder, AllAttrNameOrder),
+        keep_only_synth_attr_nums(AttrMap, AllAttrNameOrder, SynthAttrNumOrder)
     ;
+        % It would be nice to print a list of the attributes involved in the
+        % (one or more) circular dependencies detected by relation.tsort,
+        % but at present relation.m does not have any predicates that can
+        % report the information we would need for that.
         Pieces = [words("Circular dependency among"),
             words("the synthesized attributes of event"),
             quote(EventName), suffix("."), nl],
         CircErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
             [simple_msg(context(FileName, EventLineNumber),
                 [always(Pieces)])]),
-        !:ErrorSpecs = [CircErrorSpec | !.ErrorSpecs]
+        !:ErrorSpecs = [CircErrorSpec | !.ErrorSpecs],
+        SynthAttrNumOrder = []
     ),
-    list.reverse(RevVisAttrs, VisAttrs),
-    list.reverse(RevAllAttrs, AllAttrs),
-    EventSpec = event_spec(EventNumber, EventLineNumber, VisAttrs, AllAttrs),
+    list.reverse(RevAttrs, Attrs),
+    EventSpec = event_spec(EventNumber, EventName, EventLineNumber,
+        Attrs, SynthAttrNumOrder),
     ( map.search(!.EventSpecMap, EventName, OldEventSpec) ->
         OldLineNumber = OldEventSpec ^ event_spec_linenum,
         Pieces1 = [words("Duplicate event specification for event"),
@@ -357,6 +372,33 @@
         svmap.det_insert(EventName, EventSpec, !EventSpecMap)
     ).
 
+:- pred keep_only_synth_attr_nums(attr_map::in, list(string)::in,
+    list(int)::out) is det.
+
+keep_only_synth_attr_nums(_, [], []).
+keep_only_synth_attr_nums(AttrMap, [AttrName | AttrNames], SynthAttrNums) :-
+    keep_only_synth_attr_nums(AttrMap, AttrNames, SynthAttrNumsTail),
+    map.lookup(AttrMap, AttrName, attr_info(AttrNum, _, AttrType)),
+    (
+        ( AttrType = event_attr_type_ordinary(_)
+        ; AttrType = event_attr_type_function
+        ),
+        SynthAttrNums = SynthAttrNumsTail
+    ;
+        AttrType = event_attr_type_synthesized(_, _),
+        SynthAttrNums = [AttrNum | SynthAttrNumsTail]
+    ).
+
+:- type attr_info
+    --->    attr_info(
+                attr_info_number        :: int,
+                attr_info_linenumber    :: int,
+                attr_info_type          :: event_attr_type
+            ).
+
+:- func attr_info_number(attr_info) = int.
+
+:- type attr_map == map(string, attr_info).
 :- type attr_type_map == map(string, mer_type).
 :- type attr_dep_rel == relation(string).
 :- type attr_key_map == bimap(string, relation_key).
@@ -365,23 +407,27 @@
     % of this predicate.
     %
 :- pred build_plain_type_map(string::in, string::in, int::in,
-    list(event_attr_term)::in, attr_type_map::in, attr_type_map::out,
+    list(event_attr_term)::in, int::in, attr_map::in, attr_map::out,
+    attr_type_map::in, attr_type_map::out,
     attr_key_map::in, attr_key_map::out, attr_dep_rel::in, attr_dep_rel::out,
     list(error_spec)::in, list(error_spec)::out) is det.
 
-build_plain_type_map(_, _, _, [], !AttrTypeMap, !KeyMap, !DepRel, !ErrorSpecs).
-build_plain_type_map(EventName, FileName, LineNumber, [AttrTerm | AttrTerms],
-        !AttrTypeMap, !KeyMap, !DepRel, !ErrorSpecs) :-
-    AttrTerm = event_attr_term(AttrName, AttrTypeTerm),
+build_plain_type_map(_, _, _, [], _, !AttrMap, !AttrTypeMap, !KeyMap, !DepRel,
+        !ErrorSpecs).
+build_plain_type_map(EventName, FileName, EventLineNumber, [AttrTerm | AttrTerms],
+        AttrNum, !AttrMap, !AttrTypeMap, !KeyMap, !DepRel, !ErrorSpecs) :-
+    AttrTerm = event_attr_term(AttrName, AttrLineNumber, AttrTypeTerm),
     svrelation.add_element(AttrName, AttrKey, !DepRel),
     ( svbimap.insert(AttrName, AttrKey, !KeyMap) ->
-        true
+        AttrInfo = attr_info(AttrNum, AttrLineNumber, AttrTypeTerm),
+        svmap.det_insert(AttrName, AttrInfo, !AttrMap)
     ;
         Pieces = [words("Event"), quote(EventName),
             words("has more than one attribute named"),
             quote(AttrName), suffix("."), nl],
         ErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
-            [simple_msg(context(FileName, LineNumber), [always(Pieces)])]),
+            [simple_msg(context(FileName, EventLineNumber),
+                [always(Pieces)])]),
         !:ErrorSpecs = [ErrorSpec | !.ErrorSpecs]
     ),
     (
@@ -398,53 +444,90 @@
     ;
         AttrTypeTerm = event_attr_type_function
     ),
-    build_plain_type_map(EventName, FileName, LineNumber, AttrTerms,
-        !AttrTypeMap, !KeyMap, !DepRel, !ErrorSpecs).
+    build_plain_type_map(EventName, FileName, EventLineNumber, AttrTerms,
+        AttrNum + 1, !AttrMap, !AttrTypeMap, !KeyMap, !DepRel, !ErrorSpecs).
 
     % See the big comment in convert_term_to_spec_map for the documentation
     % of this predicate.
     %
-:- pred build_dep_map(string::in, string::in, int::in,
-    attr_key_map::in, list(event_attr_term)::in,
+:- pred build_dep_map(string::in, string::in,
+    attr_map::in, attr_key_map::in, list(event_attr_term)::in,
     attr_type_map::in, attr_type_map::out, attr_dep_rel::in, attr_dep_rel::out,
     list(error_spec)::in, list(error_spec)::out) is det.
 
 build_dep_map(_, _, _, _, [], !AttrTypeMap, !DepRel, !ErrorSpecs).
-build_dep_map(EventName, FileName, LineNumber, KeyMap,
-        [AttrTerm | AttrTerms], !AttrTypeMap, !DepRel, !ErrorSpecs) :-
-    AttrTerm = event_attr_term(AttrName, AttrTypeTerm),
+build_dep_map(EventName, FileName, AttrMap, KeyMap, [AttrTerm | AttrTerms],
+        !AttrTypeMap, !DepRel, !ErrorSpecs) :-
+    AttrTerm = event_attr_term(AttrName, AttrLineNumber, AttrTypeTerm),
     bimap.lookup(KeyMap, AttrName, AttrKey),
     (
-        AttrTypeTerm = event_attr_type_synthesized(_TypeTerm, SynthCall),
-        SynthCall = event_attr_synth_call(FuncAttrName, ArgAttrs),
-        record_arg_dependencies(EventName, FileName, LineNumber, KeyMap,
-            AttrName, AttrKey, ArgAttrs, !DepRel, [], AttrErrorSpecs),
+        AttrTypeTerm = event_attr_type_synthesized(_TypeTerm, SynthCallTerm),
+        SynthCallTerm = event_attr_synth_call_term(FuncAttrName, ArgAttrNames),
+        record_arg_dependencies(EventName, FileName, AttrLineNumber, KeyMap,
+            AttrName, AttrKey, ArgAttrNames, !DepRel, [], AttrErrorSpecs),
         (
             AttrErrorSpecs = [_ | _],
+            % We still record the fact that FuncAttrName is used, to prevent
+            % us from generating error messages saying that it is unused.
+            svmap.det_insert(FuncAttrName, void_type, !AttrTypeMap),
             !:ErrorSpecs = AttrErrorSpecs ++ !.ErrorSpecs
         ;
             AttrErrorSpecs = [],
-            map.lookup(!.AttrTypeMap, AttrName, AttrType),
-            ArgTypes = list.map(map.lookup(!.AttrTypeMap), ArgAttrs),
+            ( map.search(!.AttrTypeMap, AttrName, AttrType) ->
+                ArgTypes = list.map(map.lookup(!.AttrTypeMap), ArgAttrNames),
             FuncAttrType = higher_order_type(ArgTypes, yes(AttrType),
                 purity_pure, lambda_normal),
-            ( map.search(!.AttrTypeMap, FuncAttrName, OldFuncAttrType) ->
+                (
+                    map.search(AttrMap, FuncAttrName, AttrInfo),
+                    AttrInfo ^ attr_info_type = event_attr_type_function
+                ->
+                    (
+                        map.search(!.AttrTypeMap, FuncAttrName,
+                            OldFuncAttrType)
+                    ->
                 ( FuncAttrType = OldFuncAttrType ->
                     % AttrTypeMap already contains the correct info.
                     true
                 ;
+                            (
+                                map.search(AttrMap, FuncAttrName,
+                                    FuncAttrInfo)
+                            ->
+                                FuncAttrLineNumber =
+                                    FuncAttrInfo ^ attr_info_linenumber
+                            ;
+                                % This is the best line number we can give,
+                                FuncAttrLineNumber = AttrLineNumber
+                            ),
                     % XXX Maybe we should give the types themselves.
                     Pieces = [words("Attribute"), quote(FuncAttrName),
                         words("is assigned inconsistent types"),
                         words("by synthesized attributes."), nl],
                     ErrorSpec = error_spec(severity_error,
                         phase_term_to_parse_tree,
-                        [simple_msg(context(FileName, LineNumber),
+                                [simple_msg(
+                                    context(FileName, FuncAttrLineNumber),
+                                    [always(Pieces)])]),
+                            !:ErrorSpecs = [ErrorSpec | !.ErrorSpecs]
+                        )
+                    ;
+                        svmap.det_insert(FuncAttrName, FuncAttrType,
+                            !AttrTypeMap)
+                    )
+                ;
+                    Pieces = [words("Attribute"), quote(AttrName),
+                        words("cannot be synthesized"),
+                        words("by non-function attribute"),
+                        quote(FuncAttrName), suffix("."), nl],
+                    ErrorSpec = error_spec(severity_error,
+                        phase_term_to_parse_tree,
+                        [simple_msg(context(FileName, AttrLineNumber),
                             [always(Pieces)])]),
                     !:ErrorSpecs = [ErrorSpec | !.ErrorSpecs]
                 )
             ;
-                svmap.det_insert(FuncAttrName, FuncAttrType, !AttrTypeMap)
+                % The error message was already generated in the previous pass.
+                true
             )
         )
     ;
@@ -452,7 +535,7 @@
     ;
         AttrTypeTerm = event_attr_type_function
     ),
-    build_dep_map(EventName, FileName, LineNumber, KeyMap, AttrTerms,
+    build_dep_map(EventName, FileName, AttrMap, KeyMap, AttrTerms,
         !AttrTypeMap, !DepRel, !ErrorSpecs).
 
 :- pred record_arg_dependencies(string::in, string::in, int::in,
@@ -461,66 +544,78 @@
     list(error_spec)::in, list(error_spec)::out) is det.
 
 record_arg_dependencies(_, _, _, _, _, _, [], !DepRel, !ErrorSpecs).
-record_arg_dependencies(EventName, FileName, LineNumber, KeyMap,
-        FunctionAttrName, FunctionAttrKey, [AttrName | AttrNames],
+record_arg_dependencies(EventName, FileName, AttrLineNumber, KeyMap,
+        SynthAttrName, SynthAttrKey, [AttrName | AttrNames],
         !DepRel, !ErrorSpecs) :-
     ( bimap.search(KeyMap, AttrName, AttrKey) ->
-        svrelation.add(FunctionAttrKey, AttrKey, !DepRel)
+        svrelation.add(AttrKey, SynthAttrKey, !DepRel)
     ;
-        Pieces = [words("Attribute"), quote(FunctionAttrName),
+        Pieces = [words("Attribute"), quote(SynthAttrName),
             words("of event"), quote(EventName),
             words("uses nonexistent attribute"), quote(AttrName),
             words("in its synthesis."), nl],
         ErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
-            [simple_msg(context(FileName, LineNumber), [always(Pieces)])]),
+            [simple_msg(context(FileName, AttrLineNumber), [always(Pieces)])]),
         !:ErrorSpecs = [ErrorSpec | !.ErrorSpecs]
     ),
-    record_arg_dependencies(EventName, FileName, LineNumber, KeyMap,
-        FunctionAttrName, FunctionAttrKey, AttrNames, !DepRel, !ErrorSpecs).
+    record_arg_dependencies(EventName, FileName, AttrLineNumber, KeyMap,
+        SynthAttrName, SynthAttrKey, AttrNames, !DepRel, !ErrorSpecs).
 
     % See the big comment in convert_term_to_spec_map for the documentation
     % of this predicate.
     %
-:- pred convert_terms_to_attrs(string::in, string::in, int::in,
-    attr_type_map::in, list(event_attr_term)::in,
-    list(event_attribute)::in, list(event_attribute)::out,
+:- pred convert_terms_to_attrs(string::in, string::in,
+    attr_map::in, attr_type_map::in, int::in, list(event_attr_term)::in,
     list(event_attribute)::in, list(event_attribute)::out,
     list(error_spec)::in, list(error_spec)::out) is det.
 
-convert_terms_to_attrs(_, _, _, _, [], !RevVisAttrs, !RevAllAttrs,
-        !ErrorSpecs).
-convert_terms_to_attrs(EventName, FileName, LineNumber, AttrTypeMap,
-        [AttrTerm | AttrTerms], !RevVisAttrs, !RevAllAttrs, !ErrorSpecs) :-
-    AttrTerm = event_attr_term(AttrName, AttrTypeTerm),
+convert_terms_to_attrs(_, _, _, _, _, [], !RevAttrs, !ErrorSpecs).
+convert_terms_to_attrs(EventName, FileName, AttrMap,
+        AttrTypeMap, AttrNum, [AttrTerm | AttrTerms], !RevAttrs,
+        !ErrorSpecs) :-
+    AttrTerm = event_attr_term(AttrName, AttrLineNumber, AttrTypeTerm),
     (
         AttrTypeTerm = event_attr_type_ordinary(_),
         map.lookup(AttrTypeMap, AttrName, AttrType),
-        EventAttr = event_attribute(AttrName, AttrType, in_mode, no),
-        !:RevVisAttrs = [EventAttr | !.RevVisAttrs],
-        !:RevAllAttrs = [EventAttr | !.RevAllAttrs]
+        EventAttr = event_attribute(AttrNum, AttrName, AttrType, in_mode, no),
+        !:RevAttrs = [EventAttr | !.RevAttrs]
     ;
-        AttrTypeTerm = event_attr_type_synthesized(_, SynthCall),
+        AttrTypeTerm = event_attr_type_synthesized(_, SynthCallTerm),
         map.lookup(AttrTypeMap, AttrName, AttrType),
-        EventAttr = event_attribute(AttrName, AttrType, in_mode,
+        SynthCallTerm = event_attr_synth_call_term(FuncAttrName, ArgAttrNames),
+        FuncAttrNum = map.lookup(AttrMap, FuncAttrName) ^ attr_info_number,
+        ( list.map(map.search(AttrMap), ArgAttrNames, ArgAttrInfos) ->
+            ArgAttrNums = list.map(attr_info_number, ArgAttrInfos),
+            ArgAttrNameNums = assoc_list.from_corresponding_lists(ArgAttrNames,
+                ArgAttrNums),
+            SynthCall = event_attr_synth_call(FuncAttrName - FuncAttrNum,
+                ArgAttrNameNums),
+            EventAttr = event_attribute(AttrNum, AttrName, AttrType, in_mode,
             yes(SynthCall)),
-        !:RevAllAttrs = [EventAttr | !.RevAllAttrs]
+            !:RevAttrs = [EventAttr | !.RevAttrs]
+        ;
+            % The error that caused the map search failure has already had
+            % an error message generated for it.
+            true
+        )
     ;
         AttrTypeTerm = event_attr_type_function,
         ( map.search(AttrTypeMap, AttrName, AttrType) ->
-            EventAttr = event_attribute(AttrName, AttrType, in_mode, no),
-            !:RevVisAttrs = [EventAttr | !.RevVisAttrs],
-            !:RevAllAttrs = [EventAttr | !.RevAllAttrs]
+            EventAttr = event_attribute(AttrNum, AttrName, AttrType, in_mode,
+                no),
+            !:RevAttrs = [EventAttr | !.RevAttrs]
         ;
             Pieces = [words("Event"), quote(EventName),
                 words("does not use the function attribute"),
                 quote(AttrName), suffix("."), nl],
             ErrorSpec = error_spec(severity_error, phase_term_to_parse_tree,
-                [simple_msg(context(FileName, LineNumber), [always(Pieces)])]),
+                [simple_msg(context(FileName, AttrLineNumber),
+                    [always(Pieces)])]),
             !:ErrorSpecs = [ErrorSpec | !.ErrorSpecs]
         )
     ),
-    convert_terms_to_attrs(EventName, FileName, LineNumber, AttrTypeMap,
-        AttrTerms, !RevVisAttrs, !RevAllAttrs, !ErrorSpecs).
+    convert_terms_to_attrs(EventName, FileName, AttrMap, AttrTypeMap,
+        AttrNum + 1, AttrTerms, !RevAttrs, !ErrorSpecs).
 
 :- func convert_term_to_type(event_attr_type_term) = mer_type.
 
@@ -539,41 +634,51 @@
 
 %-----------------------------------------------------------------------------%
 
-event_set_description(EventSpecMap) = Desc :-
-    map.to_assoc_list(EventSpecMap, EventSpecList),
+derive_event_set_data(EventSet) = EventSetData :-
+    EventSet = event_set(EventSetName, EventSpecMap),
+    map.values(EventSpecMap, EventSpecList),
     list.sort(compare_event_specs_by_num, EventSpecList, SortedEventSpecList),
     DescStrings = list.map(describe_event_spec, SortedEventSpecList),
-    string.append_list(DescStrings, Desc).
+    string.append_list(DescStrings, Desc),
+    list.foldl(update_max_num_attr, EventSpecList, -1, MaxNumAttr),
+    EventSetData = event_set_data(EventSetName, Desc, SortedEventSpecList,
+        MaxNumAttr).
+
+:- pred update_max_num_attr(event_spec::in, int::in, int::out) is det.
+
+update_max_num_attr(Spec, !MaxNumAttr) :-
+    AllAttrs = Spec ^ event_spec_attrs,
+    list.length(AllAttrs, NumAttr),
+    !:MaxNumAttr = int.max(!.MaxNumAttr, NumAttr).
 
-:- pred compare_event_specs_by_num(
-    pair(string, event_spec)::in, pair(string, event_spec)::in,
+:- pred compare_event_specs_by_num(event_spec::in, event_spec::in,
     comparison_result::out) is det.
 
-compare_event_specs_by_num(_NameA - SpecA, _NameB - SpecB, Result) :-
+compare_event_specs_by_num(SpecA, SpecB, Result) :-
     compare(Result, SpecA ^ event_spec_num, SpecB ^ event_spec_num).
 
-:- func describe_event_spec(pair(string, event_spec)) = string.
+:- func describe_event_spec(event_spec) = string.
 
-describe_event_spec(Name - Spec) = Desc :-
-    Spec = event_spec(_EventNumber, _EventLineNumber, _VisAttrs, AllAttrs),
-    AttrDescs = string.join_list(",\n",
-        list.map(describe_event_attr, AllAttrs)),
-    Desc = "event " ++ Name ++ "(" ++ AttrDescs ++ ")".
+describe_event_spec(Spec) = Desc :-
+    Spec = event_spec(_EventNumber, EventName, _EventLineNumber,
+        Attrs, _SynthAttrNumOrder),
+    AttrDescs = string.join_list(",\n", list.map(describe_event_attr, Attrs)),
+    Desc = "event " ++ EventName ++ "(" ++ AttrDescs ++ ")".
 
 :- func describe_event_attr(event_attribute) = string.
 
 describe_event_attr(Attr) = Desc :-
-    Attr = event_attribute(Name, Type, _Mode, MaybeSynthCall),
+    Attr = event_attribute(_Num, Name, Type, _Mode, MaybeSynthCall),
     TypeDesc = describe_attr_type(Type),
     (
         MaybeSynthCall = no,
         SynthCallDesc = ""
     ;
         MaybeSynthCall = yes(SynthCall),
-        SynthCall = event_attr_synth_call(FuncAttrName, ArgAttrNames),
-        ArgAttrDesc = string.join_list(", ", ArgAttrNames),
+        SynthCall = event_attr_synth_call(FuncAttrNameNum, ArgAttrNameNums),
+        ArgAttrDesc = string.join_list(", ", assoc_list.keys(ArgAttrNameNums)),
         SynthCallDesc = "synthesized by " ++
-            FuncAttrName ++ "(" ++ ArgAttrDesc ++ ")"
+            fst(FuncAttrNameNum) ++ "(" ++ ArgAttrDesc ++ ")"
     ),
     Desc = Name ++ ": " ++ TypeDesc ++ SynthCallDesc.
 
@@ -609,32 +714,32 @@
     map.search(EventSpecMap, EventName, EventSpec),
     EventNumber = EventSpec ^ event_spec_num.
 
-event_arg_names(EventSpecMap, EventName, ArgNames) :-
+event_attributes(EventSpecMap, EventName, Attributes) :-
     map.search(EventSpecMap, EventName, EventSpec),
-    ArgInfos = EventSpec ^ event_spec_visible_attrs,
-    ArgNames = list.map(project_event_arg_name, ArgInfos).
+    Attributes = EventSpec ^ event_spec_attrs.
 
 event_arg_types(EventSpecMap, EventName, ArgTypes) :-
-    map.search(EventSpecMap, EventName, EventSpec),
-    ArgInfos = EventSpec ^ event_spec_visible_attrs,
-    ArgTypes = list.map(project_event_arg_type, ArgInfos).
+    event_attributes(EventSpecMap, EventName, Attributes),
+    list.filter_map(project_event_arg_type, Attributes, ArgTypes).
 
 event_arg_modes(EventSpecMap, EventName, ArgModes) :-
-    map.search(EventSpecMap, EventName, EventSpec),
-    ArgInfos = EventSpec ^ event_spec_visible_attrs,
-    ArgModes = list.map(project_event_arg_mode, ArgInfos).
+    event_attributes(EventSpecMap, EventName, Attributes),
+    list.filter_map(project_event_arg_mode, Attributes, ArgModes).
 
-:- func project_event_arg_name(event_attribute) = string.
+:- pred project_event_arg_name(event_attribute::in, string::out) is semidet.
 
-project_event_arg_name(Attribute) = Attribute ^ attr_name.
+project_event_arg_name(Attribute, Attribute ^ attr_name) :-
+    Attribute ^ attr_maybe_synth_call = no.
 
-:- func project_event_arg_type(event_attribute) = mer_type.
+:- pred project_event_arg_type(event_attribute::in, mer_type::out) is semidet.
 
-project_event_arg_type(Attribute) = Attribute ^ attr_type.
+project_event_arg_type(Attribute, Attribute ^ attr_type) :-
+    Attribute ^ attr_maybe_synth_call = no.
 
-:- func project_event_arg_mode(event_attribute) = mer_mode.
+:- pred project_event_arg_mode(event_attribute::in, mer_mode::out) is semidet.
 
-project_event_arg_mode(Attribute) = Attribute ^ attr_mode.
+project_event_arg_mode(Attribute, Attribute ^ attr_mode) :-
+    Attribute ^ attr_maybe_synth_call = no.
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/stack_layout.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_layout.m,v
retrieving revision 1.128
diff -u -b -r1.128 stack_layout.m
--- compiler/stack_layout.m	5 Dec 2006 03:50:59 -0000	1.128
+++ compiler/stack_layout.m	8 Dec 2006 15:16:31 -0000
@@ -148,8 +148,7 @@
     ProcLayoutNames = LayoutInfo ^ proc_layout_name_list,
     StringTable = LayoutInfo ^ string_table,
     LabelTables = LayoutInfo ^ label_tables,
-    global_data_set_static_cell_info(LayoutInfo ^ static_cell_info,
-        !GlobalData),
+    StaticCellInfo1 = LayoutInfo ^ static_cell_info,
     StringTable = string_table(_, RevStringList, StringOffset),
     list.reverse(RevStringList, StringList),
     concat_string_list(StringList, StringOffset, ConcatStrings),
@@ -171,13 +170,19 @@
         HasUserEvent = LayoutInfo ^ has_user_event,
         (
             HasUserEvent = no,
-            MaybeEventSet = no
+            MaybeEventSet = no,
+            StaticCellInfo = StaticCellInfo1
         ;
             HasUserEvent = yes,
             module_info_get_event_set(ModuleInfo, EventSet),
-            EventSet = event_set(EventSetName, EventSpecMap),
-            EventSpecs = event_set_description(EventSpecMap),
-            MaybeEventSet = yes(EventSetName - EventSpecs)
+            EventSetData = derive_event_set_data(EventSet),
+            list.foldl2(build_event_arg_type_info_map,
+                EventSetData ^ event_set_data_specs,
+                map.init, EventArgTypeInfoMap,
+                StaticCellInfo1, StaticCellInfo),
+            EventSetLayoutData = event_set_layout_data(EventSetData,
+                EventArgTypeInfoMap),
+            MaybeEventSet = yes(EventSetLayoutData)
         ),
         ModuleLayout = module_layout_data(ModuleName,
             StringOffset, ConcatStrings, ProcLayoutNames, SourceFileLayouts,
@@ -185,8 +190,10 @@
         Layouts = [ModuleLayout | Layouts0]
     ;
         TraceLayout = no,
-        Layouts = Layouts0
-    ).
+        Layouts = Layouts0,
+        StaticCellInfo = StaticCellInfo1
+    ),
+    global_data_set_static_cell_info(StaticCellInfo, !GlobalData).
 
 :- pred valid_proc_layout(proc_layout_info::in) is semidet.
 
@@ -200,6 +207,32 @@
         ProcLabel = special_proc_label(_, _, _, _, _, _)
     ).
 
+:- pred build_event_arg_type_info_map(event_spec::in,
+    map(int, rval)::in, map(int, rval)::out,
+    static_cell_info::in, static_cell_info::out) is det.
+
+build_event_arg_type_info_map(EventSpec, !EventArgTypeInfoMap,
+        !StaticCellInfo) :-
+    EventNumber = EventSpec ^ event_spec_num,
+    Attrs = EventSpec ^ event_spec_attrs,
+    list.map_foldl(build_event_arg_type_info, Attrs, RvalsAndTypes,
+        !StaticCellInfo),
+    add_scalar_static_cell(RvalsAndTypes, TypesDataAddr, !StaticCellInfo),
+    Rval = const(llconst_data_addr(TypesDataAddr, no)),
+    svmap.det_insert(EventNumber, Rval, !EventArgTypeInfoMap).
+
+:- pred build_event_arg_type_info(event_attribute::in,
+    pair(rval, llds_type)::out,
+    static_cell_info::in, static_cell_info::out) is det.
+
+build_event_arg_type_info(Attr, TypeRvalAndType, !StaticCellInfo) :-
+    Type = Attr ^ attr_type,
+    ExistQTvars = [],
+    NumUnivQTvars = -1,
+    ll_pseudo_type_info.construct_typed_llds_pseudo_type_info(Type,
+        NumUnivQTvars, ExistQTvars, !StaticCellInfo, TypeRval, TypeRvalType),
+    TypeRvalAndType = TypeRval - TypeRvalType.
+
 %---------------------------------------------------------------------------%
 
     % concat_string_list appends a list of strings together,
@@ -577,10 +610,10 @@
         MaybeTableInfo = no
     ;
         MaybeTableInfo = yes(TableInfo),
-        get_static_cell_info(!.Info, StaticCellInfo0),
+        get_layout_static_cell_info(!.Info, StaticCellInfo0),
         make_table_data(RttiProcLabel, Kind, TableInfo, MaybeTableData,
             StaticCellInfo0, StaticCellInfo),
-        set_static_cell_info(StaticCellInfo, !Info),
+        set_layout_static_cell_info(StaticCellInfo, !Info),
         add_table_data(MaybeTableData, !Info)
     ).
 
@@ -748,7 +781,7 @@
             MaybeUser = no
         ;
             MaybeUser = yes(UserEvent),
-            UserEvent = user_event_info(_PortNum, _PortName, Attributes),
+            UserEvent = user_event_info(_UserEventNumber, Attributes),
             list.foldl2(user_attribute_var_num_map(VarSet), Attributes,
                 !VarNumMap, !Counter)
         )
@@ -783,12 +816,17 @@
     list.foldl2(add_named_var_to_var_number_map, VarsNames,
         !VarNumMap, !Counter).
 
-:- pred user_attribute_var_num_map(prog_varset::in, user_attribute::in,
+:- pred user_attribute_var_num_map(prog_varset::in, maybe(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).
+user_attribute_var_num_map(VarSet, MaybeAttribute, !VarNumMap, !Counter) :-
+    (
+        MaybeAttribute = yes(Attribute),
+        Attribute = user_attribute(_Locn, Var),
+        add_var_to_var_number_map(VarSet, Var, !VarNumMap, !Counter)
+    ;
+        MaybeAttribute = no
+    ).
 
 :- 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.
@@ -937,24 +975,17 @@
     ;
         MaybeUserInfo = yes(UserInfo),
         set_has_user_event(yes, !Info),
-        UserInfo = user_event_info(UserEventNumber, UserEventName,
-            Attributes),
-        list.length(Attributes, NumAttributes),
+        UserInfo = user_event_info(UserEventNumber, Attributes),
         construct_user_data_array(VarNumMap, Attributes,
-            UserLocnsArray, UserTypesArray, UserAttrNames, UserAttrVarNums,
-            !Info),
+            UserLocnsArray, UserAttrVarNums, !Info),
 
-        get_static_cell_info(!.Info, StaticCellInfo0),
+        get_layout_static_cell_info(!.Info, StaticCellInfo0),
         add_scalar_static_cell(UserLocnsArray, UserLocnsDataAddr,
-            StaticCellInfo0, StaticCellInfo1),
-        add_scalar_static_cell(UserTypesArray, UserTypesDataAddr,
-            StaticCellInfo1, StaticCellInfo),
-        set_static_cell_info(StaticCellInfo, !Info),
+            StaticCellInfo0, StaticCellInfo),
+        set_layout_static_cell_info(StaticCellInfo, !Info),
 
         UserLocnsRval = const(llconst_data_addr(UserLocnsDataAddr, no)),
-        UserTypesRval = const(llconst_data_addr(UserTypesDataAddr, no)),
-        UserData = user_event_data(UserEventNumber, UserEventName,
-            NumAttributes, UserLocnsRval, UserTypesRval, UserAttrNames,
+        UserData = user_event_data(UserEventNumber, UserLocnsRval,
             UserAttrVarNums),
         MaybeUserData = yes(UserData)
     ),
@@ -982,32 +1013,30 @@
     add_internal_layout_data(LayoutData, Label, LayoutName, !Info),
     LabelLayout = {ProcLabel, LabelNum, LabelVars, Internal}.
 
-:- 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, list(int)::out,
+:- pred construct_user_data_array(var_num_map::in,
+    list(maybe(user_attribute))::in,
+    assoc_list(rval, llds_type)::out, list(maybe(int))::out,
     stack_layout_info::in, stack_layout_info::out) is det.
 
-construct_user_data_array(_, [], [], [], [], [], !Info).
-construct_user_data_array(VarNumMap, [Attr | Attrs],
-        [LocnRvalAndType | LocnRvalAndTypes],
-        [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),
+construct_user_data_array(_, [], [], [], !Info).
+construct_user_data_array(VarNumMap, [MaybeAttr | MaybeAttrs],
+        [LocnRvalAndType | LocnRvalAndTypes], [MaybeVarNum | MaybeVarNums],
+        !Info) :-
+    (
+        MaybeAttr = yes(Attr),
+        Attr = user_attribute(Locn, Var),
+        represent_locn_or_const_as_int_rval(Locn, LocnRval, LocnRvalType,
+            !Info),
     LocnRvalAndType = LocnRval - LocnRvalType,
-
-    ExistQTvars = [],
-    NumUnivQTvars = -1,
-    get_static_cell_info(!.Info, StaticCellInfo0),
-    ll_pseudo_type_info.construct_typed_llds_pseudo_type_info(Type,
-        NumUnivQTvars, ExistQTvars, StaticCellInfo0, StaticCellInfo,
-        TypeRval, TypeRvalType),
-    set_static_cell_info(StaticCellInfo, !Info),
-    TypeRvalAndType = TypeRval - TypeRvalType,
-
-    construct_user_data_array(VarNumMap, Attrs, LocnRvalAndTypes,
-        TypeRvalAndTypes, Names, VarNums, !Info).
+        convert_var_to_int(VarNumMap, Var, VarNum),
+        MaybeVarNum = yes(VarNum)
+    ;
+        MaybeAttr = no,
+        LocnRvalAndType = const(llconst_int(0)) - uint_least32,
+        MaybeVarNum = no
+    ),
+    construct_user_data_array(VarNumMap, MaybeAttrs, LocnRvalAndTypes,
+        MaybeVarNums, !Info).
 
 %---------------------------------------------------------------------------%
 
@@ -1207,11 +1236,11 @@
     list.map(associate_type(uint_least8), ByteLocns, ByteLocnsTypes),
     list.append(IntLocnsTypes, ByteLocnsTypes, AllLocnsTypes),
     list.append(AllTypeRvalsTypes, AllLocnsTypes, TypeLocnVectorRvalsTypes),
-    get_static_cell_info(!.Info, StaticCellInfo0),
+    get_layout_static_cell_info(!.Info, StaticCellInfo0),
     add_scalar_static_cell(TypeLocnVectorRvalsTypes, TypeLocnVectorAddr,
         StaticCellInfo0, StaticCellInfo1),
     TypeLocnVector = const(llconst_data_addr(TypeLocnVectorAddr, no)),
-    set_static_cell_info(StaticCellInfo1, !Info),
+    set_layout_static_cell_info(StaticCellInfo1, !Info),
 
     get_trace_stack_layout(!.Info, TraceStackLayout),
     (
@@ -1219,10 +1248,10 @@
         list.foldl(AddRevNums, AllArrayInfo, [], RevVarNumRvals),
         list.reverse(RevVarNumRvals, VarNumRvals),
         list.map(associate_type(uint_least16), VarNumRvals, VarNumRvalsTypes),
-        get_static_cell_info(!.Info, StaticCellInfo2),
+        get_layout_static_cell_info(!.Info, StaticCellInfo2),
         add_scalar_static_cell(VarNumRvalsTypes, NumVectorAddr,
             StaticCellInfo2, StaticCellInfo),
-        set_static_cell_info(StaticCellInfo, !Info),
+        set_layout_static_cell_info(StaticCellInfo, !Info),
         NumVector = const(llconst_data_addr(NumVectorAddr, no))
     ;
         TraceStackLayout = no,
@@ -1447,11 +1476,11 @@
     % we can take the variable number directly from the procedure's tvar set.
     ExistQTvars = [],
     NumUnivQTvars = -1,
-    get_static_cell_info(!.Info, StaticCellInfo0),
+    get_layout_static_cell_info(!.Info, StaticCellInfo0),
     ll_pseudo_type_info.construct_typed_llds_pseudo_type_info(Type,
         NumUnivQTvars, ExistQTvars, StaticCellInfo0, StaticCellInfo,
         Rval, LldsType),
-    set_static_cell_info(StaticCellInfo, !Info).
+    set_layout_static_cell_info(StaticCellInfo, !Info).
 
 :- pred represent_special_live_value_type(string::in, rval::out) is det.
 
@@ -1477,16 +1506,20 @@
         globals.lookup_bool_option(Globals, unboxed_float, UnboxedFloat),
         rval_type_as_arg(LvalOrConst, UnboxedFloat, LLDSType),
 
-        get_static_cell_info(!.Info, StaticCellInfo0),
+        get_layout_static_cell_info(!.Info, StaticCellInfo0),
         add_scalar_static_cell([LvalOrConst - LLDSType], DataAddr,
             StaticCellInfo0, StaticCellInfo),
-        set_static_cell_info(StaticCellInfo, !Info),
+        set_layout_static_cell_info(StaticCellInfo, !Info),
         Rval = const(llconst_data_addr(DataAddr, no)),
         Type = data_ptr
     ;
+        LvalOrConst = mkword(Tag, LvalOrConstBase),
+        represent_locn_or_const_as_int_rval(LvalOrConstBase, BaseRval, Type,
+            !Info),
+        Rval = mkword(Tag, BaseRval)
+    ;
         ( LvalOrConst = binop(_, _, _)
         ; LvalOrConst = unop(_, _)
-        ; LvalOrConst = mkword(_, _)
         ; LvalOrConst = mem_addr(_)
         ; LvalOrConst = var(_)
         ),
@@ -1767,8 +1800,8 @@
 :- pred get_string_table(stack_layout_info::in, string_table::out) is det.
 :- pred get_label_tables(stack_layout_info::in, map(string, label_table)::out)
     is det.
-:- pred get_static_cell_info(stack_layout_info::in, static_cell_info::out)
-    is det.
+:- pred get_layout_static_cell_info(stack_layout_info::in,
+    static_cell_info::out) is det.
 :- pred get_has_user_event(stack_layout_info::in, bool::out) is det.
 
 get_module_info(LI, LI ^ module_info).
@@ -1782,7 +1815,7 @@
 get_label_set(LI, LI ^ label_set).
 get_string_table(LI, LI ^ string_table).
 get_label_tables(LI, LI ^ label_tables).
-get_static_cell_info(LI, LI ^ static_cell_info).
+get_layout_static_cell_info(LI, LI ^ static_cell_info).
 get_has_user_event(LI, LI ^ has_user_event).
 
 :- pred allocate_label_number(int::out,
@@ -1838,7 +1871,7 @@
 :- pred set_label_tables(map(string, label_table)::in,
     stack_layout_info::in, stack_layout_info::out) is det.
 
-:- pred set_static_cell_info(static_cell_info::in,
+:- pred set_layout_static_cell_info(static_cell_info::in,
     stack_layout_info::in, stack_layout_info::out) is det.
 
 :- pred set_has_user_event(bool::in,
@@ -1846,7 +1879,7 @@
 
 set_string_table(ST, LI, LI ^ string_table := ST).
 set_label_tables(LT, LI, LI ^ label_tables := LT).
-set_static_cell_info(SCI, LI, LI ^ static_cell_info := SCI).
+set_layout_static_cell_info(SCI, LI, LI ^ static_cell_info := SCI).
 set_has_user_event(HUE, LI, LI ^ has_user_event := HUE).
 
 %---------------------------------------------------------------------------%
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/user_guide.texi
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/doc/user_guide.texi,v
retrieving revision 1.502
diff -u -b -r1.502 user_guide.texi
--- doc/user_guide.texi	7 Dec 2006 05:10:26 -0000	1.502
+++ doc/user_guide.texi	9 Dec 2006 06:33:24 -0000
@@ -2171,6 +2171,10 @@
 		test_failed:	string,
 		arg_b:		int,
 		arg_d:		int,
+		arg_list_len:   int synthesized by list_len_func(sorted_list),
+		sorted_list:    list(int) synthesized by list_sort_func(arg_list),
+		list_len_func:  function,
+		list_sort_func: function,
 		arg_list:	list(int)
 	)
 
@@ -2187,30 +2191,65 @@
 the name of the event, and,
 if the event has any attributes, a parenthesized list of those attributes.
 Each attribute's specification consists of
-a name, a colon and the Mercury type of that attribute.
+a name, a colon and information about the attribute.
+
+There are three kinds of attributes.
+ at itemize
+ at item
+For ordinary attributes, like @samp{arg_b}, 
+the information about the attribute is the Mercury type of that attribute.
+ at item
+For function attributes, like @samp{list_sort_func}, 
+the information about the attribute is just the keyword @samp{function}.
+ at item
+For synthesized attributes, like @samp{sorted_list}, 
+the information about the attribute is the type of the attribute,
+the keywords @samp{synthesized by},
+and a description of the Mercury function call
+required to synthesize the value of the attribute.
+The synthesis call consists of the name of a function attribute
+and a list of the names of one or more argument attributes.
+Argument attributes cannot be function attributes;
+they may be either ordinary attributes, or previously synthesized attributes.
+A synthesized attribute is not allowed
+to depend on itself directly or indirectly,
+but there are no restrictions on the positions of of synthesized attributes
+compared to the positions of the function attributes computing them
+or of the argument attributes of the synthesis functions.
+ at end itemize
+
+The result types of function attributes
+are given by the types of the synthesized attributes they compute.
+The argument types of function attributes (and the number of those arguments)
+are given by the types of the arguments they are applied to.
+Each function attribute must be used
+to compute at least one synthesized attribute,
+otherwise there would be no way to compute its type.
+If it is used to compute more than one synthesized attribute,
+the result and argument types must be consistent.
 
 Each event goal in the program must use
 the name of one of the events defined here as the predicate name of the call,
-and the call's arguments must match the types of that event's attributes.
-This event goal is fine,
+and the call's arguments must match
+the types of that event's non-synthesized attributes.
+Given that B and N are integers and L is a list of integers,
+these event goals are fine,
 @example
+	event nodiag_fail("N - B", B, N, list.length, list.sort, [N | L]),
 	event safe_test([1, 2, 3])
 @end example
-but this goal
+but these goals
 @example
+	event nodiag_fail("N - B", B, N, list.sort, list.length, [N | L]),
+	event nodiag_fail("N - B", B, list.length, N, list.sort, [N | L]),
 	event safe_test([1], [2])
- at end example
-this goal
- at example
 	event safe_test(42)
- at end example
-and this goal
- at example
 	event nonexistent_event(42)
 @end example
 will all generate errors.
 
-All event attributes are always input, and the event goal is always @samp{det}.
+The attributes of event calls are always input,
+and the event goal is always @samp{det}.
 
 @node I/O tabling
 @section I/O tabling
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/stream/tests
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.104
diff -u -b -r1.104 mercury_stack_layout.h
--- runtime/mercury_stack_layout.h	5 Dec 2006 03:51:13 -0000	1.104
+++ runtime/mercury_stack_layout.h	8 Dec 2006 09:07:36 -0000
@@ -241,50 +241,104 @@
 
 /*-------------------------------------------------------------------------*/
 /*
-** Definitions for MR_UserEvent
+** Definitions for MR_UserEvent and MR_UserEventSpec
 */
 
 /*
-** This is the initial, temporary definition of the user-defined event
-** structure.
+** Our layout structures link to information about user events from two places:
+** the label layout structures of labels that correspond to user events,
+** and the module layout structures of modules that contain user events.
+** Label layout structures link to MR_UserEvent structures; module layout
+** structures link to MR_UserEventSpec structures. Most of the information
+** is in the MR_UserEventSpec structures; MR_UserEvent structures contain
+** only information that may differ between two instances of the same event.
+*/
+
+/*
+** The fields of MR_UserEvent:
 **
-** The port is represented as both an integer and a string.
+** The event_number field contains the ordinal number of the event in the
+** event set the module was compiled with: it gives the identity of the event.
+** (Event numbers start at zero.) This field is also the link to the rest of
+** the information about the event, contained in the MR_UserEventSpec structure
+** linked to by the module layout structure. The MR_user_event_spec macro
+** follows this link.
+**
+** The next two fields all point to arrays whose length is the number of
+** attributes (which is available in the MR_UserEventSpec structure).
+**
+** attr_locns[i] gives the location where we can find the value of the
+** i'th attribute (the first attribute is attribute zero). This is
+** meaningful only if the attribute is not a synthesized attribute.
+** 
+** attr_var_nums[i] gives the variable number of the i'th attribute;
+** if it contains zero, that means the attribute is synthesized. 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.)
+*/
+
+typedef	MR_uint_least16_t		MR_HLDSVarNum;
+
+struct MR_UserEvent_Struct {
+	MR_uint_least16_t		MR_ue_event_number;
+	MR_LongLval			*MR_ue_attr_locns;
+	const MR_HLDSVarNum		*MR_ue_attr_var_nums;
+};
+
+/*
+** The fields of MR_UserEventSpec:
 **
-** The num_attributes field gives the number of attributes. Once the runtime
-** system knows the number of attributes of each kind of event, this field may
-** disappear.
+** The event_number field contains the name of the event.
 **
-** The next three fields all point to an array whose length is the number of
+** The num_attrs field gives the number of attributes.
+**
+** The next three fields all point to arrays whose length is the number of
 ** attributes.
 **
-** 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).
+** attr_names[i] gives the location where we can find the value of the
+** i'th attribute.
 **
-** MR_ue_attr_types[i] is the typeinfo giving the type of the (i+1)th
-** attribute.
+** attr_types[i] is the typeinfo giving the type of the i'th attribute.
 **
-** MR_ue_attr_names[i] gives the name of the (i+1)th attribute.
-** (In the future, this field may disappear.)
+** If the i'th attribute is synthesized, synth_attrs[i] points to the
+** information required to synthesize it: the number of the attribute
+** containing the synthesis function, and the list of the attributes
+** that are the arguments of the synthesis function (represented as a length
+** and an array). If the i'th attribute is not synthesized,
+** synth_attrs[i] will be NULL.
+** 
+** The synth_attr_order field points to an array of attribute numbers that
+** gives the order in which the values of the synthesized attributes should be
+** evaluated. The array is ended by -1 as a sentinel.
 ** 
-** 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.)
+** The synth_attrs and synth_attr_order fields will both be NULL for events
+** that have no synthesized attributes.
 */
 
-struct MR_UserEvent_Struct {
-	MR_uint_least16_t		MR_ue_port_number;
-	const char			*MR_ue_port_name;
-	MR_uint_least16_t		MR_ue_num_attrs;
-	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;
+struct MR_SynthAttr_Struct {
+	MR_int_least16_t		MR_sa_func_attr;
+	MR_int_least16_t		MR_sa_num_arg_attrs;
+	MR_uint_least16_t		*MR_sa_arg_attrs;
+};
+
+struct MR_UserEventSpec_Struct {
+	const char			*MR_ues_event_name;
+	MR_uint_least16_t		MR_ues_num_attrs;
+	const char			**MR_ues_attr_names;
+	MR_TypeInfo			*MR_ues_attr_types;
+	MR_SynthAttr			*MR_ues_synth_attrs;
+	MR_int_least16_t		*MR_ues_synth_attr_order;
 };
 
+#define	MR_user_event_spec(label_layout)	\
+	label_layout->MR_sll_entry->MR_sle_module_layout->		\
+	MR_ml_user_event_specs[label_layout->MR_sll_user_event->	\
+		MR_ue_event_number]
+
 /*-------------------------------------------------------------------------*/
 /*
 ** Definitions for MR_LabelLayout
@@ -419,7 +473,7 @@
 	const MR_UserEvent		*MR_sll_user_event;
 	MR_Integer			MR_sll_var_count; /* >= 0 */
 	const void			*MR_sll_locns_types;
-	const MR_uint_least16_t		*MR_sll_var_nums;
+	const MR_HLDSVarNum		*MR_sll_var_nums;
 	const MR_TypeParamLocns	*MR_sll_tvars;
 };
 
@@ -1302,9 +1356,10 @@
 ** compiler/layout_out.m.
 */
 
-#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__EVENTSETNAME
+#define	MR_LAYOUT_VERSION		MR_LAYOUT_VERSION__SYNTH_ATTR
 #define	MR_LAYOUT_VERSION__USER_DEFINED	1
 #define	MR_LAYOUT_VERSION__EVENTSETNAME	2
+#define	MR_LAYOUT_VERSION__SYNTH_ATTR	3
 
 struct MR_ModuleLayout_Struct {
 	MR_uint_least8_t                MR_ml_version_number;
@@ -1319,8 +1374,11 @@
 	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;
+	const char			*MR_ml_user_event_set_name;
+	const char			*MR_ml_user_event_set_desc;
+	MR_int_least16_t		MR_ml_user_event_max_num_attr;
+	MR_int_least16_t		MR_ml_num_user_event_specs;
+	MR_UserEventSpec		*MR_ml_user_event_specs;
 };
 
 /*-------------------------------------------------------------------------*/
Index: runtime/mercury_types.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/runtime/mercury_types.h,v
retrieving revision 1.47
diff -u -b -r1.47 mercury_types.h
--- runtime/mercury_types.h	29 Nov 2006 05:18:27 -0000	1.47
+++ runtime/mercury_types.h	6 Dec 2006 01:47:25 -0000
@@ -233,7 +233,9 @@
 typedef struct MR_ProcLayout_Struct            MR_ProcLayout;
 typedef struct MR_ModuleLayout_Struct          MR_ModuleLayout;
 typedef struct MR_LabelLayout_Struct           MR_LabelLayout;
+typedef struct MR_SynthAttr_Struct              MR_SynthAttr;
 typedef struct MR_UserEvent_Struct              MR_UserEvent;
+typedef struct MR_UserEventSpec_Struct          MR_UserEventSpec;
 
 typedef union MR_TableNode_Union                MR_TableNode;
 typedef MR_TableNode                            *MR_TrieNode;
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.20
diff -u -b -r1.20 Mercury.options
--- tests/debugger/Mercury.options	5 Dec 2006 03:51:14 -0000	1.20
+++ tests/debugger/Mercury.options	8 Dec 2006 07:48:01 -0000
@@ -45,6 +45,8 @@
 
 MCFLAGS-user_event_shallow = --event-set-file-name user_event_spec --trace shallow
 
+MCFLAGS-synth_attr = --event-set-file-name synth_attr_spec
+
 # 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.
 # The -O2 is to prevent spurious inconsistencies.
Index: tests/debugger/Mmakefile
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/debugger/Mmakefile,v
retrieving revision 1.128
diff -u -b -r1.128 Mmakefile
--- tests/debugger/Mmakefile	5 Dec 2006 03:51:14 -0000	1.128
+++ tests/debugger/Mmakefile	8 Dec 2006 18:05:06 -0000
@@ -47,9 +47,10 @@
 	print_table			\
 	queens_rep			\
 	resume_typeinfos		\
-	shell				\
 	save				\
+	shell				\
 	solver_test			\
+	synth_attr			\
 	type_desc_test			\
 	uci_index			\
 	user_event
@@ -528,6 +529,9 @@
 uci_index.out: uci_index uci_index.inp
 	$(MDB_STD) ./uci_index < uci_index.inp 2>&1 > uci_index.out 2>&1
 
+synth_attr.out: synth_attr synth_attr.inp synth_attr_spec
+	$(MDB_STD) ./synth_attr < synth_attr.inp 2>&1 > synth_attr.out 2>&1
+
 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
 
Index: tests/debugger/synth_attr.exp
===================================================================
RCS file: tests/debugger/synth_attr.exp
diff -N tests/debugger/synth_attr.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/synth_attr.exp	9 Dec 2006 02:27:39 -0000
@@ -0,0 +1,64 @@
+      E1:     C1 CALL pred synth_attr.main/2-0 (cc_multi) synth_attr.m:17
+mdb> echo on
+Command echo enabled.
+mdb> register --quiet
+mdb> user
+      E2:     C2 USER <safe_test> pred synth_attr.queen/2-0 (nondet) c5; synth_attr.m:33
+mdb> print *
+       test_list (attr 0, Out)	[1, 2, 3, 4, 5]
+       f (attr 1)             	testlen(10)
+       excp (attr 2)          	univ_cons(software_error("testlen: N < Min"))
+       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
+      E3:     C3 USER <nodiag_fail> pred synth_attr.nodiag/3-0 (semidet) s2;c6;t;c4; synth_attr.m:75
+mdb> vars
+        1 test_failed (attr 0)
+        2 arg_b (attr 1, B)
+        3 arg_d (attr 2, N)
+        4 arg_list_len (attr 3)
+        5 sorted_list (attr 4)
+        6 list_len_func (attr 5)
+        7 list_sort_func (attr 6)
+        8 arg_list (attr 7, HeadVar__3)
+        9 HeadVar__1
+       10 HeadVar__2
+       11 HeadVar__3
+       12 B
+       13 BmN
+       14 D
+       15 L
+       16 N
+       17 NmB
+mdb> print *
+       test_failed (attr 0)   	"N - B"
+       arg_b (attr 1, B)      	1
+       arg_d (attr 2, N)      	2
+       arg_list_len (attr 3)  	4
+       sorted_list (attr 4)   	[2, 3, 4, 5]
+       list_len_func (attr 5) 	lambda_synth_attr_m_75
+       list_sort_func (attr 6)	lambda2_synth_attr_m_75
+       arg_list (attr 7, HeadVar__3)	[2, 3, 4, 5]
+       HeadVar__1             	1
+       HeadVar__2             	1
+       BmN                    	-1
+       D                      	1
+       L                      	[3, 4, 5]
+       NmB                    	1
+mdb> print !arg_b
+       arg_b (attr 1, B)      	1
+mdb> user
+      E4:     C2 USER <safe_test> pred synth_attr.queen/2-0 (nondet) c5; synth_attr.m:33
+mdb> print *
+       test_list (attr 0, Out)	[1, 2, 3, 5, 4]
+       f (attr 1)             	testlen(10)
+       excp (attr 2)          	univ_cons(software_error("testlen: N < Min"))
+       Data (arg 1)           	[1, 2, 3, 4, 5]
+mdb> continue
+[1, 3, 5, 2, 4]
Index: tests/debugger/synth_attr.inp
===================================================================
RCS file: tests/debugger/synth_attr.inp
diff -N tests/debugger/synth_attr.inp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/synth_attr.inp	8 Dec 2006 07:47:10 -0000
@@ -0,0 +1,16 @@
+echo on
+register --quiet
+user
+print *
+browse !test_list
+p
+^2^1
+p
+quit
+user
+vars
+print *
+print !arg_b
+user
+print *
+continue
Index: tests/debugger/synth_attr.m
===================================================================
RCS file: tests/debugger/synth_attr.m
diff -N tests/debugger/synth_attr.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/synth_attr.m	9 Dec 2006 01:40:30 -0000
@@ -0,0 +1,112 @@
+:- module synth_attr.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is cc_multi.
+
+:- implementation.
+
+:- import_module list.
+:- import_module int.
+:- import_module require.
+
+:- 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, testlen(10)),
+	safe(Out).
+
+:- func testlen(int, list(int)) = int.
+
+testlen(Min, L) = N :-
+	list.length(L, N0),
+	( N0 >= Min ->
+		N = N0
+	;
+		error("testlen: N < Min")
+	).
+
+:- 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, list.length, list.sort,
+			[N | L]),
+		fail
+	; D = BmN ->
+		event nodiag_fail("B - N", B, N, list.length, list.sort,
+			[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/synth_attr_spec
===================================================================
RCS file: tests/debugger/synth_attr_spec
diff -N tests/debugger/synth_attr_spec
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/debugger/synth_attr_spec	9 Dec 2006 01:36:55 -0000
@@ -0,0 +1,18 @@
+event set queens
+
+event nodiag_fail(
+/* 0 */	test_failed:	string,
+/* 1 */	arg_b:		int,
+/* 2 */	arg_d:		int,
+/* 3 */	arg_list_len:	int synthesized by list_len_func(sorted_list),
+/* 4 */	sorted_list:	list(int) synthesized by list_sort_func(arg_list),
+/* 5 */	list_len_func:	function,
+/* 6 */	list_sort_func:	function,
+/* 7 */	arg_list:	list(int)
+)
+
+event safe_test(
+	test_list:	listint,
+	f:		function,
+	excp:		int synthesized by f(test_list)
+)
cvs diff: Diffing tests/debugger/declarative
cvs diff: Diffing tests/dppd
cvs diff: Diffing tests/general
cvs diff: Diffing tests/general/accumulator
cvs diff: Diffing tests/general/string_format
cvs diff: Diffing tests/general/structure_reuse
cvs diff: Diffing tests/grade_subdirs
cvs diff: Diffing tests/hard_coded
cvs diff: Diffing tests/hard_coded/exceptions
cvs diff: Diffing tests/hard_coded/purity
cvs diff: Diffing tests/hard_coded/sub-modules
cvs diff: Diffing tests/hard_coded/typeclasses
cvs diff: Diffing tests/invalid
Index: tests/invalid/Mercury.options
===================================================================
RCS file: /home/mercury/mercury1/repository/tests/invalid/Mercury.options,v
retrieving revision 1.18
diff -u -b -r1.18 Mercury.options
--- tests/invalid/Mercury.options	5 Dec 2006 03:51:18 -0000	1.18
+++ tests/invalid/Mercury.options	9 Dec 2006 07:04:25 -0000
@@ -69,6 +69,8 @@
 MCFLAGS-sub_c = 		--verbose-error-messages \
 				--no-intermodule-optimization \
 				--no-automatic-intermodule-optimization
+MCFLAGS-synth_attr_error =	--event-set-file-name synth_attr_error_spec
+MCFLAGS-syntax_error_event =	--event-set-file-name syntax_error_event_spec
 
 # Force this test to be compiled in a non-trailing grade since in this
 # case the error we want to report is the absence of trailing.
Index: tests/invalid/syntax_error_event.err_exp
===================================================================
RCS file: tests/invalid/syntax_error_event.err_exp
diff -N tests/invalid/syntax_error_event.err_exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/syntax_error_event.err_exp	9 Dec 2006 06:47:48 -0000
@@ -0,0 +1,2 @@
+could not parse syntax_error_event_spec
+no input file:7: syntax error at symbol `/'
Index: tests/invalid/syntax_error_event.m
===================================================================
RCS file: tests/invalid/syntax_error_event.m
diff -N tests/invalid/syntax_error_event.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/syntax_error_event.m	9 Dec 2006 06:45:36 -0000
@@ -0,0 +1,100 @@
+:- module syntax_error_event.
+
+:- 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(Data, 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),
+	event nodiag_succeed(N, 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/invalid/syntax_error_event_spec
===================================================================
RCS file: tests/invalid/syntax_error_event_spec
diff -N tests/invalid/syntax_error_event_spec
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/syntax_error_event_spec	9 Dec 2006 06:46:09 -0000
@@ -0,0 +1,15 @@
+event set invalid_event
+
+% should process this comment correctly.
+
+event nodiag_fail(
+	test_failed:	string,
+	arg_b:		int,
+	/* the syntax error is the missing : on the next line */
+	arg_d 		int,
+	arg_list:	list(int)
+)
+
+event safe_test(
+	test_list:	listint
+)
Index: tests/invalid/synth_attr_error.err_exp
===================================================================
RCS file: tests/invalid/synth_attr_error.err_exp
diff -N tests/invalid/synth_attr_error.err_exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/synth_attr_error.err_exp	10 Dec 2006 15:52:27 -0000
@@ -0,0 +1,18 @@
+synth_attr_error_spec:003: Circular dependency among the synthesized attributes
+synth_attr_error_spec:003:   of event `nodiag_fail'.
+synth_attr_error_spec:007: Attribute `arg_list_len' of event `nodiag_fail' uses
+synth_attr_error_spec:007:   nonexistent attribute `xsorted_list' in its
+synth_attr_error_spec:007:   synthesis.
+synth_attr_error_spec:009: Attribute `arg_list_lenb' cannot be synthesized by
+synth_attr_error_spec:009:   non-function attribute `arg_list'.
+synth_attr_error_spec:015: Circular dependency among the synthesized attributes
+synth_attr_error_spec:015:   of event `safe_test'.
+synth_attr_error_spec:017: Attribute `f' is assigned inconsistent types by
+synth_attr_error_spec:017:   synthesized attributes.
+synth_attr_error_spec:026: Duplicate event specification for event `safe_test'.
+synth_attr_error_spec:015:   The previous event specification is here.
+synth_attr_error_spec:030: Event `e' has more than one attribute named `dupx'.
+synth_attr_error_spec:033: Attribute `f' is assigned inconsistent types by
+synth_attr_error_spec:033:   synthesized attributes.
+synth_attr_error_spec:040: Attribute `f' is assigned inconsistent types by
+synth_attr_error_spec:040:   synthesized attributes.
Index: tests/invalid/synth_attr_error.m
===================================================================
RCS file: tests/invalid/synth_attr_error.m
diff -N tests/invalid/synth_attr_error.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/synth_attr_error.m	9 Dec 2006 06:56:14 -0000
@@ -0,0 +1,112 @@
+:- module synth_attr_error.
+
+:- interface.
+
+:- import_module io.
+
+:- pred main(io::di, io::uo) is cc_multi.
+
+:- implementation.
+
+:- import_module list.
+:- import_module int.
+:- import_module require.
+
+:- 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, testlen(10)),
+	safe(Out).
+
+:- func testlen(int, list(int)) = int.
+
+testlen(Min, L) = N :-
+	list.length(L, N0),
+	( N0 >= Min ->
+		N = N0
+	;
+		error("testlen: N < Min")
+	).
+
+:- 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, list.length, list.sort,
+			[N | L]),
+		fail
+	; D = BmN ->
+		event nodiag_fail("B - N", B, N, list.length, list.sort,
+			[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/invalid/synth_attr_error_spec
===================================================================
RCS file: tests/invalid/synth_attr_error_spec
diff -N tests/invalid/synth_attr_error_spec
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/invalid/synth_attr_error_spec	9 Dec 2006 08:01:47 -0000
@@ -0,0 +1,45 @@
+event set queens
+
+event nodiag_fail(
+       	test_failed:	string,
+       	arg_b:		int,
+       	arg_d:		int,
+       	arg_list_len:	int synthesized by list_len_func(xsorted_list),
+       	sorted_list:	list(int) synthesized by list_sort_func(sorted_list),
+       	arg_list_lenb:	int synthesized by arg_list(sorted_list),
+       	list_len_func:	function,
+       	list_sort_func:	function,
+       	arg_list:	list(int)
+)
+
+event safe_test(
+	test_list:	listint,
+	f:		function,
+	excp:		int synthesized by f(test_list, excp2),
+	excp2:		int synthesized by f(excp, test_list)
+)
+
+/*
+** Test the line number counting code in the scanner.
+*/
+
+event safe_test(
+	dup:		listint
+)
+
+event e(
+	dupx:		listint,
+	dupx:		listint,
+	f:		function,
+	a:		string,
+	s1:		int synthesized by f(a),
+	s2:		string synthesized by f(a)
+)
+
+event f(
+	f:		function,
+	a:		string,
+	b:		float,
+	s1:		int synthesized by f(a),
+	s2:		int synthesized by f(b)
+)
cvs diff: Diffing tests/invalid/purity
cvs diff: Diffing tests/misc_tests
cvs diff: Diffing tests/mmc_make
cvs diff: Diffing tests/mmc_make/lib
cvs diff: Diffing tests/par_conj
cvs diff: Diffing tests/recompilation
cvs diff: Diffing tests/tabling
cvs diff: Diffing tests/term
cvs diff: Diffing tests/trailing
cvs diff: Diffing tests/valid
cvs diff: Diffing tests/warnings
cvs diff: Diffing tools
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.2
diff -u -b -r1.2 mercury_event_parser.y
--- trace/mercury_event_parser.y	5 Dec 2006 03:51:19 -0000	1.2
+++ trace/mercury_event_parser.y	10 Dec 2006 15:31:28 -0000
@@ -56,7 +56,7 @@
 
 %token              TOKEN_LPAREN
 %token              TOKEN_RPAREN
-%token              TOKEN_COLON
+%token  <Uline>     TOKEN_COLON
 %token              TOKEN_COMMA
 
 %token  <Uid>       TOKEN_ID
@@ -109,7 +109,7 @@
                 {
                     $$ = MR_NEW(struct MR_EventSpec_Struct);
                     $$->MR_event_num = mercury_event_next_num;
-                    $$->MR_event_lineno = $1;
+                    $$->MR_event_linenumber = $1;
                     $$->MR_event_name = $2;
                     $$->MR_event_attributes = $4;
                     mercury_event_next_num++;
@@ -140,6 +140,7 @@
                 {
                     $$ = MR_NEW(struct MR_EventAttr_Struct);
                     $$->MR_attr_name = $1;
+                    $$->MR_attr_linenumber = $2;
                     $$->MR_attr_type = $3;
                 }
             ;
Index: trace/mercury_event_scanner.l
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_scanner.l,v
retrieving revision 1.2
diff -u -b -r1.2 mercury_event_scanner.l
--- trace/mercury_event_scanner.l	5 Dec 2006 03:51:19 -0000	1.2
+++ trace/mercury_event_scanner.l	10 Dec 2006 15:25:13 -0000
@@ -52,7 +52,7 @@
 extern  void    mercury_event_init(void);
 
 const char      *mercury_event_filename = "no input file";
-int             mercury_event_linenum = 0;
+int             mercury_event_linenum = 1;
 
 /*
 ** Add the declarations for local functions that flex is too lazy to add.
@@ -83,6 +83,12 @@
 nl      [\n\f]
 nonl    [^\n\f]
 
+sc      "/*"
+ec      "*/"
+string  \"[^"]*\"
+inside  [^*]|("*"[^/])|{string}
+comment {sc}{inside}*{ec}
+
 %pointer
 %option noyywrap
 
@@ -100,7 +106,10 @@
 "("                 { return TOKEN_LPAREN;              }
 ")"                 { return TOKEN_RPAREN;              }
 ","                 { return TOKEN_COMMA;               }
-":"                 { return TOKEN_COLON;               }
+":"                 {
+                        mercury_event_lval.Uline = mercury_event_linenum;
+                        return TOKEN_COLON;
+                    }
 
 {alpha}{alnum}*     {
                         mercury_event_lval.Uid = strdup(yytext);
@@ -121,6 +130,15 @@
                     }
 
 "%"{nonl}*{nl}      { mercury_event_linenum++;          }
+{comment}           {
+                        const char  *s;
+
+                        for (s = yytext; *s != '\0'; s++) {
+                            if (*s == '\n') {
+                                mercury_event_linenum++;
+                            }
+                        }
+                    }
 
 {sp}+               {}
 {nl}                { mercury_event_linenum++;          }
Index: trace/mercury_event_spec.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_spec.c,v
retrieving revision 1.3
diff -u -b -r1.3 mercury_event_spec.c
--- trace/mercury_event_spec.c	5 Dec 2006 03:51:19 -0000	1.3
+++ trace/mercury_event_spec.c	10 Dec 2006 15:31:42 -0000
@@ -75,7 +75,7 @@
 }
 
 MR_EventSet
-MR_read_event_set(const char *input_data)
+MR_read_event_set(const char *filename, const char *input_data)
 {
     MR_EventSet     event_set;
     MR_EventSpecs   cur;
@@ -91,6 +91,8 @@
     MR_event_spec_char_max = strlen(input_data) - 1;
     MR_event_spec_char_next = 0;
 
+    mercury_event_filename = filename;
+
     if (mercury_event_parse() != 0) {
         return NULL;
     }
@@ -162,14 +164,16 @@
     {
         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);
+            event->MR_event_name, event->MR_event_num,
+            event->MR_event_linenumber);
 
         for (attrs = event->MR_event_attributes; attrs != NULL;
             attrs = attrs->MR_attrs_tail)
         {
             attr = attrs->MR_attrs_head;
 
-            fprintf(fp, "    event_attr_term(\"%s\", ", attr->MR_attr_name);
+            fprintf(fp, "    event_attr_term(\"%s\", %d, ",
+                attr->MR_attr_name, attr->MR_attr_linenumber);
             switch (attr->MR_attr_type->MR_type_kind) {
                 case MR_EVENT_ATTR_ORDINARY:
                     fprintf(fp, "event_attr_type_ordinary(");
@@ -232,7 +236,8 @@
 {
     MR_FlatArgs args;
 
-    fprintf(fp, "attr_synth_call(\"%s\", [", call->MR_flat_term_functor);
+    fprintf(fp, "event_attr_synth_call_term(\"%s\", [",
+        call->MR_flat_term_functor);
 
     for (args = call->MR_flat_term_args; args != NULL;
         args = args->MR_flat_args_tail)
Index: trace/mercury_event_spec.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_event_spec.h,v
retrieving revision 1.2
diff -u -b -r1.2 mercury_event_spec.h
--- trace/mercury_event_spec.h	5 Dec 2006 03:51:19 -0000	1.2
+++ trace/mercury_event_spec.h	10 Dec 2006 15:30:56 -0000
@@ -55,13 +55,14 @@
 
 struct MR_EventSpec_Struct {
     unsigned            MR_event_num;
-    int                 MR_event_lineno;
+    int                 MR_event_linenumber;
     const char          *MR_event_name;
     MR_EventAttrs       MR_event_attributes;
 };
 
 struct MR_EventAttr_Struct {
     const char          *MR_attr_name;
+    int                 MR_attr_linenumber;
     MR_EventAttrType    MR_attr_type;
 };
 
@@ -86,12 +87,14 @@
 extern  int             MR_event_get_input(char *buf, int buf_size);
 
 /*
-** 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.
+** Read the specification of a set of event types from the string given by
+** event_set, which should be the contents of the event set specification file
+** named filename. If the operation succeeded, return the result; otherwise,
+** return NULL.
 */
 
-extern  MR_EventSet     MR_read_event_set(const char *event_set);
+extern  MR_EventSet     MR_read_event_set(const char *filename,
+                            const char *event_set);
 
 /*
 ** Print out the set of event specifications given by event_set to the given
Index: trace/mercury_trace_internal.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_internal.c,v
retrieving revision 1.229
diff -u -b -r1.229 mercury_trace_internal.c
--- trace/mercury_trace_internal.c	5 Dec 2006 03:51:21 -0000	1.229
+++ trace/mercury_trace_internal.c	8 Dec 2006 17:08:23 -0000
@@ -366,7 +366,8 @@
                     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);
+                    MR_read_event_set("no input file",
+                        MR_trace_event_sets[i].MR_tes_desc);
                 if (MR_trace_event_sets[i].MR_tes_event_set == NULL) {
                     fprintf(MR_mdb_out,
                         "Internal error: could not parse "
@@ -1505,7 +1506,7 @@
         (MR_TracePort) label_layout->MR_sll_port == MR_PORT_USER)
     {
         maybe_user_event_name =
-            label_layout->MR_sll_user_event->MR_ue_port_name;
+            MR_user_event_spec(label_layout).MR_ues_event_name;
         fprintf(MR_mdb_out, " <%s>", maybe_user_event_name);
     } else {
         maybe_user_event_name = NULL;
Index: trace/mercury_trace_tables.c
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_tables.c,v
retrieving revision 1.46
diff -u -b -r1.46 mercury_trace_tables.c
--- trace/mercury_trace_tables.c	5 Dec 2006 03:51:21 -0000	1.46
+++ trace/mercury_trace_tables.c	8 Dec 2006 05:31:48 -0000
@@ -35,6 +35,7 @@
 int                 MR_trace_event_set_max = 0;
 
 MR_bool             MR_trace_event_sets_are_all_consistent = MR_TRUE;
+int                 MR_trace_event_sets_max_num_attr = -1;
 
 /*
 ** We record module layout structures in two tables. The MR_module_infos
@@ -173,21 +174,21 @@
         MR_insert_module_info(module);
 
         if (module->MR_ml_version_number >= MR_LAYOUT_VERSION__EVENTSETNAME) {
-            if (module->MR_ml_event_specs != NULL) {
+            if (module->MR_ml_user_event_set_desc != NULL) {
                 int                 i;
                 MR_bool             found;
                 const char          *event_set_name;
                 MR_TraceEventSet    *trace_event_set;
                 
-                event_set_name = module->MR_ml_event_set_name;
+                event_set_name = module->MR_ml_user_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))
+                        if (MR_strdiff(trace_event_set->MR_tes_desc,
+                            module->MR_ml_user_event_set_desc))
                         {
                             trace_event_set->MR_tes_is_consistent = MR_FALSE;
                         }
@@ -203,9 +204,20 @@
                     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_desc =
+                            module->MR_ml_user_event_set_desc;
                     trace_event_set->MR_tes_is_consistent = MR_TRUE;
+                    trace_event_set->MR_tes_specs =
+                            module->MR_ml_user_event_specs;
                     MR_trace_event_set_next++;
+
+                    if (MR_trace_event_sets_max_num_attr <
+                        module->MR_ml_user_event_max_num_attr)
+                    {
+                        MR_trace_event_sets_max_num_attr =
+                            module->MR_ml_user_event_max_num_attr;
+                    }
+
                 }
             }
         }
Index: trace/mercury_trace_tables.h
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/trace/mercury_trace_tables.h,v
retrieving revision 1.27
diff -u -b -r1.27 mercury_trace_tables.h
--- trace/mercury_trace_tables.h	5 Dec 2006 03:51:21 -0000	1.27
+++ trace/mercury_trace_tables.h	8 Dec 2006 05:30:45 -0000
@@ -63,9 +63,11 @@
 
 typedef struct {
     const char      *MR_tes_name;
-    const char      *MR_tes_string;
+    const char              *MR_tes_desc;
     MR_bool         MR_tes_is_consistent;
     MR_EventSet     MR_tes_event_set;
+    int                     MR_tes_num_specs;
+    MR_UserEventSpec        *MR_tes_specs;
 } MR_TraceEventSet;
 
 extern  MR_TraceEventSet    *MR_trace_event_sets;
@@ -73,6 +75,7 @@
 extern  int                 MR_trace_event_set_max;
 
 extern  MR_bool             MR_trace_event_sets_are_all_consistent;
+extern  int                 MR_trace_event_sets_max_num_attr;
 
 /*
 ** 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.73
diff -u -b -r1.73 mercury_trace_vars.c
--- trace/mercury_trace_vars.c	6 Dec 2006 03:45:03 -0000	1.73
+++ trace/mercury_trace_vars.c	9 Dec 2006 02:33:27 -0000
@@ -34,16 +34,24 @@
 #include <ctype.h>
 
 /*
-** This structure contains all the debugger's information about a variable.
+** MR_ValueDetails structures contain all the debugger's information about
+** a value.
 **
-** The fullname field obviously contains the variable's full name.
-** If this name ends with a sequence of digits, then the basename field will
-** contain the name of the variable minus those digits, the num_suffix field
-** will contain the numeric value of this sequence of digits, and the
-** has_suffix field will be set to true. If the full name does not end with
-** a sequence of digits, then the basename field will contain the same string
-** as the fullname field, and the has_suffix field will be set to false
-** (the num_suffix field will not contain anything meaningful).
+** A value can be the value of an attribute or the value of a program variable.
+** The value_kind field says which kind of value this is (and therefore which
+** alternative of the value_details union is valid), while the value_value
+** and value_type fields contain the value itself and the typeinfo describing
+** its type.
+**
+** For program variables' values, the fullname field obviously contains
+** the variable's full name. If this name ends with a sequence of digits,
+** then the basename field will contain the name of the variable minus
+** those digits, the num_suffix field will contain the numeric value of
+** this sequence of digits, and the has_suffix field will be set to true.
+** If the full name does not end with a sequence of digits, then the basename
+** field will contain the same string as the fullname field, and the has_suffix
+** field will be set to false (the num_suffix field will not contain anything
+** meaningful).
 **
 ** If the variable is an argument (but not a type-info argument), the
 ** is_headvar field is set to the argument number (starting at 1).
@@ -60,8 +68,14 @@
 ** variable numbers occurring in the RTTI are renumbered to be a dense set,
 ** whereas the original variable numbers are not guaranteed to be dense.)
 **
-** The last two fields contain the value of the variable and the typeinfo
-** describing the type of this value.
+** For attribute value, the num field gives the position of this attribute
+** in the attribute list (the first attribute is attribute #0). The name
+** field gives the attribute's name. For non-synthesized attributes, the
+** var_hlds_number field gives the HLDS number of the variable whose value
+** gives the attribute value, and the synth_attr field will be NULL.
+** For synthesized attributes, the var_hlds_number field will contain zero,
+** and the synth_attr field will point to the description of the call that
+** synthesizes the attribute's value.
 */
 
 typedef struct {
@@ -71,14 +85,15 @@
     MR_bool             MR_var_has_suffix;
     int                 MR_var_is_headvar;
     MR_bool             MR_var_is_ambiguous;
-    MR_uint_least16_t   MR_var_hlds_number;
+    MR_HLDSVarNum       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_HLDSVarNum       MR_attr_var_hlds_number;
+    MR_SynthAttr        *MR_attr_synth_attr;
 } MR_AttributeDetails;
 
 typedef union {
@@ -153,6 +168,9 @@
     MR_ValueDetails         *MR_point_vars;
 } MR_Point;
 
+#define MR_slot_value(slot_number) \
+        MR_point.MR_point_vars[(slot_number)].MR_value_value
+
 static  MR_bool         MR_trace_type_is_ignored(
                             MR_PseudoTypeInfo pseudo_type_info,
                             MR_bool print_optionals);
@@ -201,6 +219,11 @@
 ** do not export them. The types are a lie, but a safe lie.
 */
 
+MR_declare_entry(mercury__do_call_closure_compact);
+
+extern const struct MR_TypeCtorInfo_Struct
+  MR_TYPE_CTOR_INFO_NAME(univ, univ, 0);
+
 extern const struct MR_TypeCtorInfo_Struct
   MR_TYPE_CTOR_INFO_NAME(private_builtin, type_info, 0);
 extern const struct MR_TypeCtorInfo_Struct
@@ -359,6 +382,7 @@
 {
     const MR_ProcLayout     *entry;
     const MR_UserEvent      *user;
+    MR_UserEventSpec        *user_spec;
     MR_Word                 *valid_saved_regs;
     int                     var_count;
     int                     attr_count;
@@ -373,12 +397,19 @@
     int                     i;
     int                     slot;
     int                     slot_max;
+    int                     synth_slot;
+    int                     arg;
     char                    *copy;
     const char              *name;
     const char              *filename;
     int                     linenumber;
     char                    *attr_name;
     MR_bool                 succeeded;
+    MR_AttributeDetails     *attr_details;
+    MR_ProgVarDetails       *var_details;
+    int                     num_synth_attr;
+    MR_SynthAttr            *synth_attr;
+    MR_Word                 *engine_result;
 
     entry = level_layout->MR_sll_entry;
     if (! MR_PROC_LAYOUT_HAS_EXEC_TRACE(entry)) {
@@ -430,8 +461,10 @@
 
     user = level_layout->MR_sll_user_event;
     if (user != NULL) {
-        attr_count = user->MR_ue_num_attrs;
+        user_spec = &MR_user_event_spec(level_layout);
+        attr_count = user_spec->MR_ues_num_attrs;
     } else {
+        user_spec = NULL;
         attr_count = 0;
     }
 
@@ -478,9 +511,27 @@
 
     MR_point.MR_point_attr_var_max = -1;
     slot = 0;
+    if (attr_count > 0) {
+        num_synth_attr = 0;
+
     for (i = 0; i < attr_count; i++) {
+            if (user_spec->MR_ues_synth_attrs != NULL
+                && user_spec->MR_ues_synth_attrs[i].MR_sa_func_attr >= 0)
+            {
+                /*
+                ** This is a synthesized attribute; we can't look up its value.
+                ** Fill in a dummy as the value, but fill in all other fields
+                ** for real. The value field will be filled in after we know
+                ** the values of all non-synthesized attributes.
+                */
+                num_synth_attr++;
+                value = 0;
+                synth_attr = &user_spec->MR_ues_synth_attrs[i];
+#ifdef  MR_DEBUG_SYNTH_ATTR
+                fprintf(stderr, "skipping attr %d\n", i);
+#endif
+            } else {
         succeeded = MR_FALSE;
-
         value = MR_lookup_long_lval_base(user->MR_ue_attr_locns[i],
             valid_saved_regs, base_sp, base_curfr, &succeeded);
 
@@ -488,26 +539,108 @@
             MR_fatal_error("cannot look up value of attribute");
         }
 
-        type_info = user->MR_ue_attr_types[i];
-        attr_name = MR_copy_string(user->MR_ue_attr_names[i]);
+                synth_attr = NULL;
+
+#ifdef  MR_DEBUG_SYNTH_ATTR
+                fprintf(stderr, "set attr %d = %x\n", i, value);
+#endif
+            }
+
+            type_info = user_spec->MR_ues_attr_types[i];
+            attr_name = MR_copy_string(user_spec->MR_ues_attr_names[i]);
 
         MR_point.MR_point_vars[slot].MR_value_kind = MR_VALUE_ATTRIBUTE;
         MR_point.MR_point_vars[slot].MR_value_type = type_info;
         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 =
+
+            attr_details = &MR_point.MR_point_vars[slot].MR_value_attr;
+
+            attr_details->MR_attr_num = i;
+            attr_details->MR_attr_name = attr_name;
+            attr_details->MR_attr_var_hlds_number =
             user->MR_ue_attr_var_nums[i];
+            attr_details->MR_attr_synth_attr = synth_attr;
 
-        if (user->MR_ue_attr_var_nums[i] > MR_point.MR_point_attr_var_max) {
+            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++;
     }
 
+        if (num_synth_attr > 0) {
+            /* Sanity check. */
+            if (user_spec->MR_ues_synth_attr_order == NULL) {
+                MR_fatal_error("no order for synthesized attributes");
+            }
+
+            for (i = 0; user_spec->MR_ues_synth_attr_order[i] >= 0; i++) {
+                num_synth_attr--;
+
+                synth_slot = user_spec->MR_ues_synth_attr_order[i];
+                synth_attr = &user_spec->MR_ues_synth_attrs[synth_slot];
+
+#ifdef  MR_DEBUG_SYNTH_ATTR
+                fprintf(stderr, "\nsynthesizing attr %d\n", synth_slot);
+#endif
+
+                MR_save_registers();
+                MR_virtual_reg_assign(1,
+                    MR_slot_value(synth_attr->MR_sa_func_attr));
+                MR_virtual_reg_assign(2, synth_attr->MR_sa_num_arg_attrs);
+#ifdef  MR_DEBUG_SYNTH_ATTR
+                fprintf(stderr, "func attr %d = %x\n",
+                    synth_attr->MR_sa_func_attr,
+                    MR_virtual_reg_value(1));
+                fprintf(stderr, "num args = %d\n",
+                    MR_virtual_reg_value(2));
+#endif
+                for (arg = 0; arg < synth_attr->MR_sa_num_arg_attrs; arg++) {
+                    /*
+                    ** Argument numbers start at zero, but register numbers
+                    ** start at one. The first argument (arg 0) goes into r3.
+                    */
+
+                    MR_virtual_reg_assign(arg + 3,
+                        MR_slot_value(synth_attr->MR_sa_arg_attrs[arg]));
+#ifdef  MR_DEBUG_SYNTH_ATTR
+                    fprintf(stderr, "arg %d = %x\n",
+                        synth_attr->MR_sa_arg_attrs[arg],
+                        MR_virtual_reg_value(arg + 2));
+#endif
+                }
+                MR_restore_registers();
+
+                MR_save_transient_registers();
+                MR_TRACE_CALL_MERCURY(
+                    engine_result = MR_call_engine(
+                        MR_ENTRY(mercury__do_call_closure_compact), MR_TRUE);
+                );
+                MR_restore_transient_registers();
+
+                if (engine_result == NULL) {
+                    MR_point.MR_point_vars[synth_slot].MR_value_value = MR_r1;
+                } else {
+                    /*
+                    ** Replace the value with the univ thrown by the exception.
+                    */
+                    MR_point.MR_point_vars[synth_slot].MR_value_value =
+                        (MR_Word) engine_result;
+                    MR_point.MR_point_vars[synth_slot].MR_value_type =
+                        (MR_TypeInfo) &MR_TYPE_CTOR_INFO_NAME(univ, univ, 0);
+                }
+            }
+
+            /* Another sanity check. */
+            if (num_synth_attr != 0) {
+                MR_fatal_error("mismatch on number of synthesized attributes");
+            }
+        }
+    }
+
     for (i = 0; i < var_count; i++) {
-        MR_uint_least16_t   hlds_var_num;
+        MR_HLDSVarNum   hlds_var_num;
         int                 head_var_num;
         int                 start_of_num;
         char                *num_addr;
@@ -535,35 +668,33 @@
         MR_point.MR_point_vars[slot].MR_value_type = type_info;
         MR_point.MR_point_vars[slot].MR_value_value = value;
 
-        MR_point.MR_point_vars[slot].MR_value_var.MR_var_hlds_number =
-            hlds_var_num;
-        MR_point.MR_point_vars[slot].MR_value_var.MR_var_seq_num_in_label = i;
+        var_details = &MR_point.MR_point_vars[slot].MR_value_var;
+
+        var_details->MR_var_hlds_number = hlds_var_num;
+        var_details->MR_var_seq_num_in_label = i;
 
         copy = MR_copy_string(name);
-        MR_point.MR_point_vars[slot].MR_value_var.MR_var_fullname = copy;
+        var_details->MR_var_fullname = copy;
 
         /* We need another copy we can cut apart. */
         copy = MR_copy_string(name);
         start_of_num = MR_find_start_of_num_suffix(copy);
 
         if (start_of_num < 0) {
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_has_suffix =
-                MR_FALSE;
+            var_details->MR_var_has_suffix = MR_FALSE;
             /* Num_suffix should not be used. */
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_num_suffix = -1;
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_basename = copy;
+            var_details->MR_var_num_suffix = -1;
+            var_details->MR_var_basename = copy;
         } else {
             if (start_of_num == 0) {
                 MR_fatal_error("variable name starts with digit");
             }
 
             num_addr = copy + start_of_num;
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_has_suffix =
-                MR_TRUE;
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_num_suffix =
-                atoi(num_addr);
+            var_details->MR_var_has_suffix = MR_TRUE;
+            var_details->MR_var_num_suffix = atoi(num_addr);
             *num_addr = '\0';
-            MR_point.MR_point_vars[slot].MR_value_var.MR_var_basename = copy;
+            var_details->MR_var_basename = copy;
         }
 
         MR_point.MR_point_vars[slot].MR_value_var.MR_var_is_headvar = 0;
@@ -572,14 +703,13 @@
             head_var_num++)
         {
             if (entry->MR_sle_head_var_nums[head_var_num] == hlds_var_num) {
-                MR_point.MR_point_vars[slot].MR_value_var.MR_var_is_headvar =
+                var_details->MR_var_is_headvar =
                     head_var_num - num_added_args + 1;
                 break;
             }
         }
 
-        MR_point.MR_point_vars[slot].MR_value_var.MR_var_is_ambiguous =
-            MR_FALSE;
+        var_details->MR_var_is_ambiguous = MR_FALSE;
         slot++;
     }
 
@@ -788,7 +918,9 @@
     MR_ValueDetails     *value;
     MR_AttributeDetails *attr;
     MR_ProgVarDetails   *var;
+    MR_SynthAttr        *synth;
     int                 i;
+    int                 arg;
 
     if (MR_point.MR_point_problem != NULL) {
         return MR_point.MR_point_problem;
@@ -804,6 +936,21 @@
                     "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);
+
+                if (attr->MR_attr_synth_attr != NULL) {
+                    synth = attr->MR_attr_synth_attr;
+
+                    fprintf(out, "synthesized by attr %d(",
+                        synth->MR_sa_func_attr);
+                    for (arg = 0; arg < synth->MR_sa_num_arg_attrs; arg++) {
+                        if (arg > 0) {
+                            fprintf(out, ", ");
+                        }
+                        fprintf(out, "attr %d", synth->MR_sa_arg_attrs[arg]);
+                    }
+                    fprintf(out, ")\n");
+                }
+
                 break;
 
             case MR_VALUE_PROG_VAR:
@@ -1402,8 +1549,8 @@
 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;
+    MR_HLDSVarNum       attr_hlds_num;
+    MR_HLDSVarNum       var_hlds_num;
     int                 var_num;
     int                 i;
 
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