[m-rev.] diff: add field name prefixes

Zoltan Somogyi zs at csse.unimelb.edu.au
Tue Jan 29 15:51:58 AEDT 2008


compiler/*.m:
	Add prefixes to the field names of a bunch of structures, to make
	tags files more useful (by avoiding getting a bunch of irrelevant
	matches when searching for an identifier).

	In some cases, add prefixes to the names of function symbols and
	predicates, for the same reason.

	In some cases, rename the variables holding the structures, when doing
	so improves the clarity of code. (When a module passes around
	structures of more than one kind, it shouldn't name *both* of them
	just "Info".)

	Take some other opportunities for cleanups, e.g. using
	type_to_ctor_and_args_det instead of just plain type_to_ctor_and_args
	and a call to error.

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/code_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.357
diff -u -b -r1.357 code_info.m
--- compiler/code_info.m	21 Jan 2008 03:56:09 -0000	1.357
+++ compiler/code_info.m	24 Jan 2008 04:57:41 -0000
@@ -125,15 +125,15 @@
     %
 :- pred get_proc_id(code_info::in, proc_id::out) is det.
 
-    % Get the HLDS of the procedure we are generating code for.
-    %
-:- pred get_proc_info(code_info::in, proc_info::out) is det.
-
     % Get the HLDS of the predicate containing the procedure
     % we are generating code for.
     %
 :- pred get_pred_info(code_info::in, pred_info::out) is det.
 
+    % Get the HLDS of the procedure we are generating code for.
+    %
+:- pred get_proc_info(code_info::in, proc_info::out) is det.
+
     % Get the variables for the current procedure.
     %
 :- pred get_varset(code_info::in, prog_varset::out) is det.
@@ -309,169 +309,144 @@
 
 :- type code_info_static
     --->    code_info_static(
-                globals             :: globals,
                                     % For the code generation options.
+                cis_globals             :: globals,
 
-                module_info         :: module_info,
-                                    % The module_info structure - you just
-                                    % never know when you might need it.
+                % The module_info structure - you just never know
+                % when you might need it.
+                cis_module_info         :: module_info,
 
-                pred_id             :: pred_id,
                                     % The id of the current predicate.
+                cis_pred_id             :: pred_id,
 
-                proc_id             :: proc_id,
                                     % The id of the current procedure.
+                cis_proc_id             :: proc_id,
 
-                proc_info           :: proc_info,
-                                    % The proc_info for this procedure.
+                % The pred_info for the predicate containing this procedure.
+                cis_pred_info           :: pred_info,
 
-                pred_info           :: pred_info,
-                                    % The pred_info for the predicate containing
-                                    % this procedure.
+                % The proc_info for this procedure.
+                cis_proc_info           :: proc_info,
 
-                varset              :: prog_varset,
                                     % The variables in this procedure.
+                cis_varset              :: prog_varset,
 
-                var_slot_count      :: int,
-                                    % The number of stack slots allocated.
-                                    % for storing variables.
-                                    % (Some extra stack slots are used
-                                    % for saving and restoring registers.)
-
-                maybe_trace_info    :: maybe(trace_info),
-                                    % Information about which stack slots
-                                    % the call sequence number and depth
-                                    % are stored in, provided tracing is
-                                    % switched on.
-
-                opt_no_resume_calls :: bool,
-                                    % Should we optimize calls that cannot
-                                    % return?
+                % The number of stack slots allocated. for storing variables.
+                % (Some extra stack slots are used for saving and restoring
+                % registers.)
+                cis_var_slot_count      :: int,
+
+                % Information about which stack slots the call sequence number
+                % and depth are stored in, provided tracing is switched on.
+                cis_maybe_trace_info    :: maybe(trace_info),
+
+                % Should we optimize calls that cannot return?
+                cis_opt_no_resume_calls :: bool,
 
-                emit_trail_ops      :: add_trail_ops,
                                     % Should we emit trail operations?
+                cis_emit_trail_ops      :: add_trail_ops,
 
-                opt_trail_ops       :: bool,
-                                    % Should we try to avoid emiting trail
-                                    % operations?
+                % Should we try to avoid generating trail operations?
+                cis_opt_trail_ops       :: bool,
 
-                emit_region_ops     :: add_region_ops,
                                     % Should we emit region operations?
+                cis_emit_region_ops     :: add_region_ops,
 
-                opt_region_ops      :: bool,
-                                    % Should we try to avoid emiting region
-                                    % operations?
+                % Should we try to avoid generating region operations?
+                cis_opt_region_ops      :: bool,
 
-                auto_comments       :: bool,
                                     % The setting of --auto-comments.
+                cis_auto_comments       :: bool,
+
+                % The setting of --optimize-constructor-last-call-null.
+                cis_lcmc_null           :: bool
 
-                lcmc_null           :: bool
-                                    % The setting of --optimize-constructor-
-                                    % last-call-null.
             ).
 
 :- type code_info_loc_dep
     --->    code_info_loc_dep(
-                forward_live_vars   :: set(prog_var),
-                                    % Variables that are forward live
-                                    % after this goal.
+                % Variables that are forward live after this goal.
+                cild_forward_live_vars  :: set(prog_var),
 
-                instmap             :: instmap,
                                     % Current insts of the live variables.
+                cild_instmap            :: instmap,
 
-                zombies             :: set(prog_var),
-                                    % Zombie variables; variables that are not
-                                    % forward live but which are protected by
-                                    % an enclosing resume point.
-
-                var_locn_info       :: var_locn_info,
-                                    % A map storing the information about
-                                    % the status of each known variable.
-                                    % (Known vars = forward live vars
-                                    % + zombies)
-
-                temps_in_use        :: set(lval),
-                                    % The set of temporary locations currently
-                                    % in use. These lvals must be all be keys
-                                    % in the map of temporary locations ever
-                                    % used, which is one of the persistent
-                                    % fields below. Any keys in that map which
-                                    % are not in this set are free for reuse.
+                % Zombie variables; variables that are not forward live
+                % but which are protected by an enclosing resume point.
+                cild_zombies            :: set(prog_var),
+
+                % A map storing the information about the status of each known
+                % variable. (Known vars = forward live vars + zombies.)
+                cild_var_locn_info      :: var_locn_info,
+
+                % The set of temporary locations currently in use. These lvals
+                % must be all be keys in the map of temporary locations ever
+                % used, which is one of the persistent fields below. Any keys
+                % in that map which are not in this set are free for reuse.
+                cild_temps_in_use       :: set(lval),
 
-                fail_info           :: fail_info,
                                     % Information about how to manage failures.
+                cild_fail_info          :: fail_info,
 
-                par_conj_depth      :: int
-                                    % How deep in a nested parallel conjunction
-                                    % we are. This is zero at the beginning of
-                                    % a procedure and is incremented as we
-                                    % enter parallel conjunctions.
+                % How deep in a nested parallel conjunction we are.
+                % This is zero at the beginning of a procedure and
+                % is incremented as we enter parallel conjunctions.
+                cild_par_conj_depth     :: int
             ).
 
 :- type code_info_persistent
     --->    code_info_persistent(
-                label_num_src       :: counter,
-                                    % Counter for the local labels used
-                                    % by this procedure.
+                % Counter for the local labels used by this procedure.
+                cip_label_num_src       :: counter,
 
-                store_succip        :: bool,
                                     % do we need to store succip?
+                cip_store_succip        :: bool,
 
-                label_info          :: proc_label_layout_info,
-                                    % Information on which values
-                                    % are live and where at which labels,
-                                    % for tracing and/or accurate gc.
+                % Information on which values are live and where at which
+                % labels, for tracing and/or accurate gc.
+                cip_label_info          :: proc_label_layout_info,
 
-                proc_trace_events   :: bool,
                                     % Did the procedure have any trace events?
+                cip_proc_trace_events   :: bool,
 
-                stackslot_max       :: int,
-                                    % The maximum number of extra
-                                    % temporary stackslots that have been
-                                    % used during the procedure.
-
-                temp_contents       :: map(lval, slot_contents),
-                                    % The temporary locations that have ever
-                                    % been used on the stack, and what they
-                                    % contain. Once we have used a stack slot
-                                    % to store e.g. a ticket, we never reuse
-                                    % that slot to hold something else, e.g.
-                                    % a saved hp. This policy prevents us
-                                    % from making such conflicting choices
-                                    % in parallel branches, which would make it
-                                    % impossible to describe to gc what the
-                                    % slot contains after the end of the
-                                    % branched control structure.
-
-                persistent_temps    :: set(lval),
-                                    % Stack slot locations that should not be
-                                    % released even when the code generator
-                                    % resets its location-dependent state.
-
-                closure_layout_seq  :: counter,
-
-                closure_layouts     :: list(layout_data),
-                                    % Closure layout structures generated
-                                    % by this procedure.
-
-                max_reg_used        :: int,
-                                    % At each call to MR_trace, we compute the
-                                    % highest rN register number that contains
-                                    % a useful value. This slot contains the
-                                    % maximum of these highest values.
-                                    % Therefore at all calls to MR_trace in the
-                                    % procedure, we need only save the
-                                    % registers whose numbers are equal to or
-                                    % smaller than this field. This slot
-                                    % contains -1 if tracing is not enabled.
-
-                created_temp_frame  :: bool,
-                                    % True iff the procedure has created one or
-                                    % more temporary nondet frames.
+                % The maximum number of extra temporary stackslots that
+                % have been used during the procedure.
+                cip_stackslot_max       :: int,
+
+                % The temporary locations that have ever been used on the
+                % stack, and what they contain. Once we have used a stack slot
+                % to store e.g. a ticket, we never reuse that slot to hold
+                % something else, e.g. a saved hp. This policy prevents us
+                % from making such conflicting choices in parallel branches,
+                % which would make it impossible to describe to gc what the
+                % slot contains after the end of the branched control
+                % structure.
+                cip_temp_contents       :: map(lval, slot_contents),
+
+                % Stack slot locations that should not be released even when
+                % the code generator resets its location-dependent state.
+                cip_persistent_temps    :: set(lval),
+
+                cip_closure_layout_seq  :: counter,
+
+                % Closure layout structures generated by this procedure.
+                cip_closure_layouts     :: list(layout_data),
+
+                % At each call to MR_trace, we compute the highest rN register
+                % number that contains a useful value. This slot contains the
+                % maximum of these highest values. Therefore at all calls to
+                % MR_trace in the procedure, we need only save the registers
+                % whose numbers are equal to or smaller than this field.
+                % This slot contains -1 if tracing is not enabled.
+                cip_max_reg_used        :: int,
+
+                % True iff the procedure has created one or more temporary
+                % nondet frames.
+                cip_created_temp_frame  :: bool,
 
-                static_cell_info    :: static_cell_info,
+                cip_static_cell_info    :: static_cell_info,
 
-                used_env_vars       :: set(string)
+                cip_used_env_vars       :: set(string)
             ).
 
 %---------------------------------------------------------------------------%
@@ -552,8 +527,8 @@
             ModuleInfo,
             PredId,
             ProcId,
-            ProcInfo,
             PredInfo,
+            ProcInfo,
             VarSet,
             SlotMax,
             no,
@@ -614,73 +589,79 @@
 
 %---------------------------------------------------------------------------%
 
-get_globals(CI, CI ^ code_info_static ^ globals).
-get_module_info(CI, CI ^ code_info_static ^ module_info).
-get_pred_id(CI, CI ^ code_info_static ^ pred_id).
-get_proc_id(CI, CI ^ code_info_static ^ proc_id).
-get_proc_info(CI, CI ^ code_info_static ^ proc_info).
-get_pred_info(CI, CI ^ code_info_static ^ pred_info).
-get_varset(CI, CI ^ code_info_static ^ varset).
-get_var_slot_count(CI, CI ^ code_info_static ^ var_slot_count).
-get_maybe_trace_info(CI, CI ^ code_info_static ^ maybe_trace_info).
-get_opt_no_return_calls(CI, CI ^ code_info_static ^ opt_no_resume_calls).
-get_emit_trail_ops(CI, CI ^ code_info_static ^ emit_trail_ops).
-get_opt_trail_ops(CI, CI ^ code_info_static ^ opt_trail_ops).
-get_emit_region_ops(CI, CI ^ code_info_static ^ emit_region_ops).
-get_opt_region_ops(CI, CI ^ code_info_static ^ opt_region_ops).
-get_auto_comments(CI, CI ^ code_info_static ^ auto_comments).
-get_lcmc_null(CI, CI ^ code_info_static ^ lcmc_null).
-get_forward_live_vars(CI, CI ^ code_info_loc_dep ^ forward_live_vars).
-get_instmap(CI, CI ^ code_info_loc_dep ^ instmap).
-get_zombies(CI, CI ^ code_info_loc_dep ^ zombies).
-get_var_locn_info(CI, CI ^ code_info_loc_dep ^ var_locn_info).
-get_temps_in_use(CI, CI ^ code_info_loc_dep ^ temps_in_use).
-get_fail_info(CI, CI ^ code_info_loc_dep ^ fail_info).
-get_par_conj_depth(CI, CI ^ code_info_loc_dep ^ par_conj_depth).
-get_label_counter(CI, CI ^ code_info_persistent ^ label_num_src).
-get_succip_used(CI, CI ^ code_info_persistent ^ store_succip).
-get_layout_info(CI, CI ^ code_info_persistent ^ label_info).
-get_proc_trace_events(CI, CI ^ code_info_persistent ^ proc_trace_events).
-get_max_temp_slot_count(CI, CI ^ code_info_persistent ^ stackslot_max).
-get_temp_content_map(CI, CI ^ code_info_persistent ^ temp_contents).
-get_persistent_temps(CI, CI ^ code_info_persistent ^ persistent_temps).
-get_closure_seq_counter(CI, CI ^ code_info_persistent ^ closure_layout_seq).
-get_closure_layouts(CI, CI ^ code_info_persistent ^ closure_layouts).
-get_max_reg_in_use_at_trace(CI, CI ^ code_info_persistent ^ max_reg_used).
-get_created_temp_frame(CI, CI ^ code_info_persistent ^ created_temp_frame).
-get_static_cell_info(CI, CI ^ code_info_persistent ^ static_cell_info).
-get_used_env_vars(CI, CI ^ code_info_persistent ^ used_env_vars).
+get_globals(CI, CI ^ code_info_static ^ cis_globals).
+get_module_info(CI, CI ^ code_info_static ^ cis_module_info).
+get_pred_id(CI, CI ^ code_info_static ^ cis_pred_id).
+get_proc_id(CI, CI ^ code_info_static ^ cis_proc_id).
+get_pred_info(CI, CI ^ code_info_static ^ cis_pred_info).
+get_proc_info(CI, CI ^ code_info_static ^ cis_proc_info).
+get_varset(CI, CI ^ code_info_static ^ cis_varset).
+get_var_slot_count(CI, CI ^ code_info_static ^ cis_var_slot_count).
+get_maybe_trace_info(CI, CI ^ code_info_static ^ cis_maybe_trace_info).
+get_opt_no_return_calls(CI, CI ^ code_info_static ^ cis_opt_no_resume_calls).
+get_emit_trail_ops(CI, CI ^ code_info_static ^ cis_emit_trail_ops).
+get_opt_trail_ops(CI, CI ^ code_info_static ^ cis_opt_trail_ops).
+get_emit_region_ops(CI, CI ^ code_info_static ^ cis_emit_region_ops).
+get_opt_region_ops(CI, CI ^ code_info_static ^ cis_opt_region_ops).
+get_auto_comments(CI, CI ^ code_info_static ^ cis_auto_comments).
+get_lcmc_null(CI, CI ^ code_info_static ^ cis_lcmc_null).
+get_forward_live_vars(CI, CI ^ code_info_loc_dep ^ cild_forward_live_vars).
+get_instmap(CI, CI ^ code_info_loc_dep ^ cild_instmap).
+get_zombies(CI, CI ^ code_info_loc_dep ^ cild_zombies).
+get_var_locn_info(CI, CI ^ code_info_loc_dep ^ cild_var_locn_info).
+get_temps_in_use(CI, CI ^ code_info_loc_dep ^ cild_temps_in_use).
+get_fail_info(CI, CI ^ code_info_loc_dep ^ cild_fail_info).
+get_par_conj_depth(CI, CI ^ code_info_loc_dep ^ cild_par_conj_depth).
+get_label_counter(CI, CI ^ code_info_persistent ^ cip_label_num_src).
+get_succip_used(CI, CI ^ code_info_persistent ^ cip_store_succip).
+get_layout_info(CI, CI ^ code_info_persistent ^ cip_label_info).
+get_proc_trace_events(CI, CI ^ code_info_persistent ^ cip_proc_trace_events).
+get_max_temp_slot_count(CI, CI ^ code_info_persistent ^ cip_stackslot_max).
+get_temp_content_map(CI, CI ^ code_info_persistent ^ cip_temp_contents).
+get_persistent_temps(CI, CI ^ code_info_persistent ^ cip_persistent_temps).
+get_closure_seq_counter(CI,
+    CI ^ code_info_persistent ^ cip_closure_layout_seq).
+get_closure_layouts(CI, CI ^ code_info_persistent ^ cip_closure_layouts).
+get_max_reg_in_use_at_trace(CI, CI ^ code_info_persistent ^ cip_max_reg_used).
+get_created_temp_frame(CI, CI ^ code_info_persistent ^ cip_created_temp_frame).
+get_static_cell_info(CI, CI ^ code_info_persistent ^ cip_static_cell_info).
+get_used_env_vars(CI, CI ^ code_info_persistent ^ cip_used_env_vars).
 
 %---------------------------------------------------------------------------%
 
-set_maybe_trace_info(TI, CI, CI ^ code_info_static ^ maybe_trace_info := TI).
+set_maybe_trace_info(TI, CI,
+    CI ^ code_info_static ^ cis_maybe_trace_info := TI).
 set_forward_live_vars(LV, CI,
-    CI ^ code_info_loc_dep ^ forward_live_vars := LV).
-set_instmap(IM, CI, CI ^ code_info_loc_dep ^ instmap := IM).
-set_zombies(Zs, CI, CI ^ code_info_loc_dep ^ zombies := Zs).
-set_var_locn_info(EI, CI, CI ^ code_info_loc_dep ^ var_locn_info := EI).
-set_temps_in_use(TI, CI, CI ^ code_info_loc_dep ^ temps_in_use := TI).
-set_fail_info(FI, CI, CI ^ code_info_loc_dep ^ fail_info := FI).
-set_par_conj_depth(N, CI, CI ^ code_info_loc_dep ^ par_conj_depth := N).
-set_label_counter(LC, CI, CI ^ code_info_persistent ^ label_num_src := LC).
-set_succip_used(SU, CI, CI ^ code_info_persistent ^ store_succip := SU).
-set_layout_info(LI, CI, CI ^ code_info_persistent ^ label_info := LI).
+    CI ^ code_info_loc_dep ^ cild_forward_live_vars := LV).
+set_instmap(IM, CI, CI ^ code_info_loc_dep ^ cild_instmap := IM).
+set_zombies(Zs, CI, CI ^ code_info_loc_dep ^ cild_zombies := Zs).
+set_var_locn_info(EI, CI, CI ^ code_info_loc_dep ^ cild_var_locn_info := EI).
+set_temps_in_use(TI, CI, CI ^ code_info_loc_dep ^ cild_temps_in_use := TI).
+set_fail_info(FI, CI, CI ^ code_info_loc_dep ^ cild_fail_info := FI).
+set_par_conj_depth(N, CI, CI ^ code_info_loc_dep ^ cild_par_conj_depth := N).
+set_label_counter(LC, CI, CI ^ code_info_persistent ^ cip_label_num_src := LC).
+set_succip_used(SU, CI, CI ^ code_info_persistent ^ cip_store_succip := SU).
+set_layout_info(LI, CI, CI ^ code_info_persistent ^ cip_label_info := LI).
 set_proc_trace_events(PTE, CI,
-    CI ^ code_info_persistent ^ proc_trace_events := PTE).
+    CI ^ code_info_persistent ^ cip_proc_trace_events := PTE).
 set_max_temp_slot_count(TM, CI,
-    CI ^ code_info_persistent ^ stackslot_max := TM).
-set_temp_content_map(CM, CI, CI ^ code_info_persistent ^ temp_contents := CM).
-set_persistent_temps(PT, CI, CI ^ code_info_persistent ^ persistent_temps := PT).
+    CI ^ code_info_persistent ^ cip_stackslot_max := TM).
+set_temp_content_map(CM, CI,
+    CI ^ code_info_persistent ^ cip_temp_contents := CM).
+set_persistent_temps(PT, CI,
+    CI ^ code_info_persistent ^ cip_persistent_temps := PT).
 set_closure_seq_counter(CLS, CI,
-    CI ^ code_info_persistent ^ closure_layout_seq := CLS).
-set_closure_layouts(CG, CI, CI ^ code_info_persistent ^ closure_layouts := CG).
+    CI ^ code_info_persistent ^ cip_closure_layout_seq := CLS).
+set_closure_layouts(CG, CI,
+    CI ^ code_info_persistent ^ cip_closure_layouts := CG).
 set_max_reg_in_use_at_trace(MR, CI,
-    CI ^ code_info_persistent ^ max_reg_used := MR).
+    CI ^ code_info_persistent ^ cip_max_reg_used := MR).
 set_created_temp_frame(MR, CI,
-    CI ^ code_info_persistent ^ created_temp_frame := MR).
+    CI ^ code_info_persistent ^ cip_created_temp_frame := MR).
 set_static_cell_info(SCI, CI,
-    CI ^ code_info_persistent ^ static_cell_info := SCI).
-set_used_env_vars(UEV, CI, CI ^ code_info_persistent ^ used_env_vars := UEV).
+    CI ^ code_info_persistent ^ cip_static_cell_info := SCI).
+set_used_env_vars(UEV, CI,
+    CI ^ code_info_persistent ^ cip_used_env_vars := UEV).
 
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
@@ -924,11 +905,7 @@
 
 search_type_defn(CI, Type, TypeDefn) :-
     get_module_info(CI, ModuleInfo),
-    ( type_to_ctor_and_args(Type, TypeCtorPrime, _) ->
-        TypeCtor = TypeCtorPrime
-    ;
-        unexpected(this_file, "unknown type in search_type_defn")
-    ),
+    type_to_ctor_and_args_det(Type, TypeCtor, _),
     module_info_get_type_table(ModuleInfo, TypeTable),
     map.search(TypeTable, TypeCtor, TypeDefn).
 
Index: compiler/constraint.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/constraint.m,v
retrieving revision 1.88
diff -u -b -r1.88 constraint.m
--- compiler/constraint.m	30 Dec 2007 08:23:33 -0000	1.88
+++ compiler/constraint.m	12 Jan 2008 20:54:45 -0000
@@ -114,9 +114,9 @@
         % recomputed.
         constraint_info_update_changed(Constraints, !Info)
     ),
-    InstMap0 = !.Info ^ instmap,
+    InstMap0 = !.Info ^ constr_instmap,
     propagate_conj_sub_goal_2(Goal0, Constraints, Goals, !Info, !IO),
-    !:Info = !.Info ^ instmap := InstMap0.
+    !:Info = !.Info ^ constr_instmap := InstMap0.
 
 :- pred propagate_conj_sub_goal_2(hlds_goal::in, list(constraint)::in,
     list(hlds_goal)::out, constraint_info::in, constraint_info::out,
@@ -150,14 +150,14 @@
         FinalGoals = [hlds_goal(switch(Var, CanFail, Cases), GoalInfo)]
     ;
         GoalExpr = if_then_else(Vars, Cond0, Then0, Else0),
-        InstMap0 = !.Info ^ instmap,
+        InstMap0 = !.Info ^ constr_instmap,
         % We can't safely propagate constraints into the condition of an
         % if-then-else, because that would change the answers generated
         % by the procedure.
         propagate_goal(Cond0, [], Cond, !Info, !IO),
         constraint_info_update_goal(Cond, !Info),
         propagate_goal(Then0, Constraints, Then, !Info, !IO),
-        !:Info = !.Info ^ instmap := InstMap0,
+        !:Info = !.Info ^ constr_instmap := InstMap0,
         propagate_goal(Else0, Constraints, Else, !Info, !IO),
         FinalGoals =
             [hlds_goal(if_then_else(Vars, Cond, Then, Else), GoalInfo)]
@@ -228,9 +228,9 @@
 propagate_in_independent_goals([], _, [], !Info, !IO).
 propagate_in_independent_goals([Goal0 | Goals0], Constraints, [Goal | Goals],
         !Info, !IO) :-
-    InstMap0 = !.Info ^ instmap,
+    InstMap0 = !.Info ^ constr_instmap,
     propagate_goal(Goal0, Constraints, Goal, !Info, !IO),
-    !:Info = !.Info ^ instmap := InstMap0,
+    !:Info = !.Info ^ constr_instmap := InstMap0,
     propagate_in_independent_goals(Goals0, Constraints, Goals, !Info, !IO).
 
 %-----------------------------------------------------------------------------%
@@ -243,10 +243,10 @@
 propagate_cases(Var, Constraints, [Case0 | Cases0], [Case | Cases],
         !Info, !IO) :-
     Case0 = case(MainConsId, OtherConsIds, Goal0),
-    InstMap0 = !.Info ^ instmap,
+    InstMap0 = !.Info ^ constr_instmap,
     constraint_info_bind_var_to_functors(Var, MainConsId, OtherConsIds, !Info),
     propagate_goal(Goal0, Constraints, Goal, !Info, !IO),
-    !:Info = !.Info ^ instmap := InstMap0,
+    !:Info = !.Info ^ constr_instmap := InstMap0,
     Case = case(MainConsId, OtherConsIds, Goal),
     propagate_cases(Var, Constraints, Cases0, Cases, !Info, !IO).
 
@@ -274,9 +274,9 @@
         ->
             propagate_conj_sub_goal(Goal0, [], Goals, !Info, !IO)
         ;
-            InstMap0 = !.Info ^ instmap,
-            ModuleInfo = !.Info ^ module_info,
-            VarTypes = !.Info ^ vartypes,
+            InstMap0 = !.Info ^ constr_instmap,
+            ModuleInfo = !.Info ^ constr_module_info,
+            VarTypes = !.Info ^ constr_vartypes,
             annotate_conj_output_vars(Goals0, ModuleInfo,
                 VarTypes, InstMap0, [], RevGoals1),
             annotate_conj_constraints(ModuleInfo, RevGoals1,
@@ -414,10 +414,10 @@
         IncompatibleInstVars),
     Goal = hlds_goal(GoalExpr, GoalInfo),
     NonLocals = goal_info_get_nonlocals(GoalInfo),
-    CI_ModuleInfo0 = !.Info ^ module_info,
+    CI_ModuleInfo0 = !.Info ^ constr_module_info,
     goal_can_loop_or_throw(Goal, GoalCanLoopOrThrow,
         CI_ModuleInfo0, CI_ModuleInfo, !IO),
-    !:Info = !.Info ^ module_info := CI_ModuleInfo,
+    !:Info = !.Info ^ constr_module_info := CI_ModuleInfo,
     (
         % Propagate goals that can fail and have no output variables.
         % Propagating cc_nondet goals would be tricky, because we would
@@ -463,7 +463,7 @@
 
         % If the constraint was the only use of the constant, the old goal
         % can be removed. We need to rerun quantification to work that out.
-        !:Info = !.Info ^ changed := yes
+        !:Info = !.Info ^ constr_changed := yes
     ;
         % Prune away the constraints after a goal that cannot succeed
         % -- they can never be executed.
@@ -550,13 +550,13 @@
         ConstraintNonLocals = goal_info_get_nonlocals(ConstraintInfo),
         set.member(ConstructVar, ConstraintNonLocals)
     ->
-        VarSet0 = !.Info ^ varset,
-        VarTypes0 = !.Info ^ vartypes,
+        VarSet0 = !.Info ^ constr_varset,
+        VarTypes0 = !.Info ^ constr_vartypes,
         varset.new_var(VarSet0, NewVar, VarSet),
         map.lookup(VarTypes0, ConstructVar, VarType),
         map.det_insert(VarTypes0, NewVar, VarType, VarTypes),
-        !:Info = !.Info ^ varset := VarSet,
-        !:Info = !.Info ^ vartypes := VarTypes,
+        !:Info = !.Info ^ constr_varset := VarSet,
+        !:Info = !.Info ^ constr_vartypes := VarTypes,
         map.from_assoc_list([ConstructVar - NewVar], Subn),
         rename_some_vars_in_goal(Subn, Construct0, Construct),
         Constructs = [Construct | Constructs0],
@@ -729,11 +729,11 @@
 
 :- type constraint_info
     --->    constraint_info(
-                module_info :: module_info,
-                vartypes    :: vartypes,
-                varset      :: prog_varset,
-                instmap     :: instmap,
-                changed     :: bool     % has anything changed.
+                constr_module_info  :: module_info,
+                constr_vartypes     :: vartypes,
+                constr_varset       :: prog_varset,
+                constr_instmap      :: instmap,
+                constr_changed      :: bool     % has anything changed.
             ).
 
 constraint_info_init(ModuleInfo, VarTypes, VarSet, InstMap, ConstraintInfo) :-
@@ -748,23 +748,23 @@
     constraint_info::in, constraint_info::out) is det.
 
 constraint_info_update_goal(hlds_goal(_, GoalInfo), !Info) :-
-    InstMap0 = !.Info ^ instmap,
+    InstMap0 = !.Info ^ constr_instmap,
     InstMapDelta = goal_info_get_instmap_delta(GoalInfo),
     instmap.apply_instmap_delta(InstMap0, InstMapDelta, InstMap),
-    !:Info = !.Info ^ instmap := InstMap.
+    !:Info = !.Info ^ constr_instmap := InstMap.
 
 :- pred constraint_info_bind_var_to_functors(prog_var::in, cons_id::in,
     list(cons_id)::in, constraint_info::in, constraint_info::out) is det.
 
 constraint_info_bind_var_to_functors(Var, MainConsId, OtherConsIds, !Info) :-
-    InstMap0 = !.Info ^ instmap,
-    ModuleInfo0 = !.Info ^ module_info,
-    VarTypes = !.Info ^ vartypes,
+    InstMap0 = !.Info ^ constr_instmap,
+    ModuleInfo0 = !.Info ^ constr_module_info,
+    VarTypes = !.Info ^ constr_vartypes,
     map.lookup(VarTypes, Var, Type),
     bind_var_to_functors(Var, Type, MainConsId, OtherConsIds,
         InstMap0, InstMap, ModuleInfo0, ModuleInfo),
-    !:Info = !.Info ^ instmap := InstMap,
-    !:Info = !.Info ^ module_info := ModuleInfo.
+    !:Info = !.Info ^ constr_instmap := InstMap,
+    !:Info = !.Info ^ constr_module_info := ModuleInfo.
 
     % If a non-empty list of constraints is pushed into a sub-goal,
     % quantification, instmap_deltas and determinism need to be
@@ -778,7 +778,7 @@
         Constraints = []
     ;
         Constraints = [_ | _],
-        !:Info = !.Info ^ changed := yes
+        !:Info = !.Info ^ constr_changed := yes
     ).
 
 %-----------------------------------------------------------------------------%
Index: compiler/cse_detection.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/cse_detection.m,v
retrieving revision 1.115
diff -u -b -r1.115 cse_detection.m
--- compiler/cse_detection.m	22 Jan 2008 15:06:08 -0000	1.115
+++ compiler/cse_detection.m	24 Jan 2008 04:56:40 -0000
@@ -162,10 +162,10 @@
 
 :- type cse_info
     --->    cse_info(
-                varset          :: prog_varset,
-                vartypes        :: vartypes,
-                rtti_varmaps    :: rtti_varmaps,
-                module_info     :: module_info
+                csei_varset         :: prog_varset,
+                csei_vartypes       :: vartypes,
+                csei_rtti_varmaps   :: rtti_varmaps,
+                csei_module_info    :: module_info
             ).
 
 :- pred detect_cse_in_proc_pass(proc_id::in, pred_id::in, bool::out,
@@ -265,7 +265,7 @@
         (
             RHS0 = rhs_lambda_goal(Purity, Groundness, PredOrFunc, EvalMethod,
                 NonLocalVars, Vars, Modes, Det, LambdaGoal0),
-            ModuleInfo = !.CseInfo ^ module_info,
+            ModuleInfo = !.CseInfo ^ csei_module_info,
             instmap.pre_lambda_update(ModuleInfo, Vars, Modes,
                 InstMap0, InstMap1),
             detect_cse_in_goal(LambdaGoal0, LambdaGoal, !CseInfo,
@@ -362,10 +362,9 @@
         !CseInfo, Redo, GoalExpr) :-
     (
         instmap.lookup_var(InstMap0, Var, VarInst0),
-        ModuleInfo = !.CseInfo ^ module_info,
-        % XXX we only need inst_is_bound, but leave this as it is
-        % until mode analysis can handle aliasing between free
-        % variables.
+        ModuleInfo = !.CseInfo ^ csei_module_info,
+        % XXX We only need inst_is_bound, but leave this as it is until
+        % mode analysis can handle aliasing between free variables.
         inst_is_ground_or_any(ModuleInfo, VarInst0),
         common_deconstruct(Goals0, Var, !CseInfo, Unify,
             FirstOldNew, LaterOldNew, Goals)
@@ -402,7 +401,7 @@
     (
         Var \= SwitchVar,
         instmap.lookup_var(InstMap0, Var, VarInst0),
-        ModuleInfo = !.CseInfo ^ module_info,
+        ModuleInfo = !.CseInfo ^ csei_module_info,
         % XXX We only need inst_is_bound, but leave this as it is until
         % mode analysis can handle aliasing between free variables.
         inst_is_ground_or_any(ModuleInfo, VarInst0),
@@ -443,7 +442,7 @@
 detect_cse_in_ite([Var | Vars], IfVars, Cond0, Then0, Else0, GoalInfo,
         InstMap, !CseInfo, Redo, GoalExpr) :-
     (
-        ModuleInfo = !.CseInfo ^ module_info,
+        ModuleInfo = !.CseInfo ^ csei_module_info,
         instmap.lookup_var(InstMap, Var, VarInst0),
         % XXX We only need inst_is_bound, but leave this as it is until
         % mode analysis can handle aliasing between free variables.
@@ -652,8 +651,8 @@
 
 create_parallel_subterm(OFV, Context, UnifyContext, !CseInfo, !OldNewVar,
         Goal) :-
-    VarSet0 = !.CseInfo ^ varset,
-    VarTypes0 = !.CseInfo ^ vartypes,
+    VarSet0 = !.CseInfo ^ csei_varset,
+    VarTypes0 = !.CseInfo ^ csei_vartypes,
     varset.new_var(VarSet0, NFV, VarSet),
     map.lookup(VarTypes0, OFV, Type),
     map.det_insert(VarTypes0, NFV, Type, VarTypes),
@@ -665,8 +664,8 @@
     % track of the inst of OFV.
     create_pure_atomic_complicated_unification(OFV, rhs_var(NFV),
         Context, MainCtxt, SubCtxt, Goal),
-    !:CseInfo = !.CseInfo ^ varset := VarSet,
-    !:CseInfo = !.CseInfo ^ vartypes := VarTypes.
+    !:CseInfo = !.CseInfo ^ csei_varset := VarSet,
+    !:CseInfo = !.CseInfo ^ csei_vartypes := VarTypes.
 
 %-----------------------------------------------------------------------------%
 
@@ -788,8 +787,8 @@
     (
         Unify = hlds_goal(unify(_, _, _, UnifyInfo, _), _),
         UnifyInfo = deconstruct(Var, ConsId, _, _, _, _),
-        ModuleInfo = !.CseInfo ^ module_info,
-        VarTypes = !.CseInfo ^ vartypes,
+        ModuleInfo = !.CseInfo ^ csei_module_info,
+        VarTypes = !.CseInfo ^ csei_vartypes,
         map.lookup(VarTypes, Var, Type),
         type_util.is_existq_cons(ModuleInfo, Type, ConsId)
     ->
@@ -807,14 +806,13 @@
     map.from_assoc_list(FirstOldNew, FirstOldNewMap),
     map.from_assoc_list(LaterOldNew, LaterOldNewMap),
 
-    RttiVarMaps0 = !.CseInfo ^ rtti_varmaps,
-    VarTypes0 = !.CseInfo ^ vartypes,
+    RttiVarMaps0 = !.CseInfo ^ csei_rtti_varmaps,
+    VarTypes0 = !.CseInfo ^ csei_vartypes,
 
     % Build a map for all locations in the rtti_varmaps that are changed
     % by the application of FirstOldNewMap. The keys of this map are the
     % new locations, and the values are the tvars (from the first branch)
     % that have had their locations moved.
-    %
     rtti_varmaps_tvars(RttiVarMaps0, TvarsList),
     list.foldl(find_type_info_locn_tvar_map(RttiVarMaps0, FirstOldNewMap),
         TvarsList, map.init, NewTvarMap),
@@ -823,21 +821,19 @@
     % branches that merge with locations in the first branch. When we find one,
     % add a type substitution which represents the type variables that were
     % merged.
-    %
     list.foldl(find_merged_tvars(RttiVarMaps0, LaterOldNewMap, NewTvarMap),
         TvarsList, map.init, Renaming),
 
     % Apply the full old->new map and the type substitution to the
     % rtti_varmaps, and apply the type substitution to the vartypes.
-    %
     list.append(FirstOldNew, LaterOldNew, OldNew),
     map.from_assoc_list(OldNew, OldNewMap),
     apply_substitutions_to_rtti_varmaps(Renaming, map.init, OldNewMap,
         RttiVarMaps0, RttiVarMaps),
     map.map_values(apply_tvar_rename(Renaming), VarTypes0, VarTypes),
 
-    !:CseInfo = !.CseInfo ^ rtti_varmaps := RttiVarMaps,
-    !:CseInfo = !.CseInfo ^ vartypes := VarTypes.
+    !:CseInfo = !.CseInfo ^ csei_rtti_varmaps := RttiVarMaps,
+    !:CseInfo = !.CseInfo ^ csei_vartypes := VarTypes.
 
 :- pred apply_tvar_rename(tvar_renaming::in, prog_var::in,
     mer_type::in, mer_type::out) is det.
Index: compiler/delay_construct.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/delay_construct.m,v
retrieving revision 1.26
diff -u -b -r1.26 delay_construct.m
--- compiler/delay_construct.m	30 Dec 2007 08:23:35 -0000	1.26
+++ compiler/delay_construct.m	12 Jan 2008 19:58:07 -0000
@@ -81,10 +81,10 @@
 
 :- type delay_construct_info
     --->    delay_construct_info(
-                module_info             :: module_info,
-                body_typeinfo_liveness  :: bool,
-                vartypes                :: vartypes,
-                rtti_varmaps            :: rtti_varmaps
+                dci_module_info             :: module_info,
+                dci_body_typeinfo_liveness  :: bool,
+                dci_vartypes                :: vartypes,
+                dci_rtti_varmaps            :: rtti_varmaps
             ).
 
 %-----------------------------------------------------------------------------%
@@ -210,9 +210,9 @@
         Unif = construct(Var, _, Args, _, _, _, _),
         Args = [_ | _], % We are constructing a cell, not a constant
         instmap.lookup_var(InstMap0, Var, Inst0),
-        inst_is_free(DelayInfo ^ module_info, Inst0),
+        inst_is_free(DelayInfo ^ dci_module_info, Inst0),
         instmap.lookup_var(InstMap1, Var, Inst1),
-        inst_is_ground(DelayInfo ^ module_info, Inst1)
+        inst_is_ground(DelayInfo ^ dci_module_info, Inst1)
     ->
         set.insert(ConstructedVars0, Var, ConstructedVars1),
         RevDelayedGoals1 = [Goal0 | RevDelayedGoals0],
@@ -223,9 +223,9 @@
         delay_construct_skippable(GoalExpr0, GoalInfo0),
         NonLocals = goal_info_get_nonlocals(GoalInfo0),
         maybe_complete_with_typeinfo_vars(NonLocals,
-            DelayInfo ^ body_typeinfo_liveness,
-            DelayInfo ^ vartypes,
-            DelayInfo ^ rtti_varmaps, CompletedNonLocals),
+            DelayInfo ^ dci_body_typeinfo_liveness,
+            DelayInfo ^ dci_vartypes,
+            DelayInfo ^ dci_rtti_varmaps, CompletedNonLocals),
         set.intersect(CompletedNonLocals, ConstructedVars0,
             Intersection),
         set.empty(Intersection),
Index: compiler/goal_path.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/goal_path.m,v
retrieving revision 1.48
diff -u -b -r1.48 goal_path.m
--- compiler/goal_path.m	22 Jan 2008 15:06:09 -0000	1.48
+++ compiler/goal_path.m	24 Jan 2008 01:18:48 -0000
@@ -78,9 +78,9 @@
 
 :- type slot_info
     --->    slot_info(
-                vartypes                    :: vartypes,
-                module_info                 :: module_info,
-                omit_mode_equiv_prefix      :: bool
+                slot_info_vartypes                  :: vartypes,
+                slot_info_module_info               :: module_info,
+                slot_info_omit_mode_equiv_prefix    :: bool
             ).
 
 fill_goal_path_slots(ModuleInfo, !Proc) :-
@@ -116,7 +116,7 @@
 
 fill_goal_slots(Path0, SlotInfo,
         hlds_goal(Expr0, Info0), hlds_goal(Expr, Info)) :-
-    OmitModeEquivPrefix = SlotInfo ^ omit_mode_equiv_prefix,
+    OmitModeEquivPrefix = SlotInfo ^ slot_info_omit_mode_equiv_prefix,
     (
         OmitModeEquivPrefix = yes,
         PathSteps0 = cord.list(Path0),
@@ -152,8 +152,8 @@
         Goal = disj(Goals)
     ;
         Goal0 = switch(Var, CanFail, Cases0),
-        VarTypes = SlotInfo ^ vartypes,
-        ModuleInfo = SlotInfo ^ module_info,
+        VarTypes = SlotInfo ^ slot_info_vartypes,
+        ModuleInfo = SlotInfo ^ slot_info_module_info,
         map.lookup(VarTypes, Var, Type),
         ( switch_type_num_functors(ModuleInfo, Type, NumFunctors) ->
             MaybeNumFunctors = yes(NumFunctors)
Index: compiler/hhf.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/hhf.m,v
retrieving revision 1.34
diff -u -b -r1.34 hhf.m
--- compiler/hhf.m	22 Jan 2008 15:06:09 -0000	1.34
+++ compiler/hhf.m	24 Jan 2008 01:18:49 -0000
@@ -184,9 +184,9 @@
 
 :- type hhf_info
     --->    hhf_info(
-                inst_graph  :: inst_graph,
-                varset      :: prog_varset,
-                vartypes    :: vartypes
+                hhfi_inst_graph :: inst_graph,
+                hhfi_varset     :: prog_varset,
+                hhfi_vartypes   :: vartypes
             ).
 
 :- pred process_clause(list(prog_var)::in, clause::in, clause::out,
@@ -198,14 +198,16 @@
     NonLocals = goal_info_get_nonlocals(GoalInfo0),
 
     process_goal(NonLocals, Goal0, Goal, !HI).
-% XXX We probably need to requantify, but it stuffs up the inst_graph to do
-% that.
-%   VarSet1 = !.HI ^ varset,
-%   VarTypes1 = !.HI ^ vartypes,
-%   implicitly_quantify_clause_body(HeadVars, Goal1, VarSet1, VarTypes1,
-%       Goal, VarSet, VarTypes, _Warnings),
-%   !:HI = !.HI varset := VarSet,
-%   !:HI = !.HI vartypes := VarTypes.
+
+    % XXX We probably need to requantify, but doing so stuffs up the
+    % inst_graph.
+    %
+    % VarSet1 = !.HI ^ hhfi_varset,
+    % VarTypes1 = !.HI ^ hhfi_vartypes,
+    % implicitly_quantify_clause_body(HeadVars, Goal1, VarSet1, VarTypes1,
+    %     Goal, VarSet, VarTypes, _Warnings),
+    % !:HI = !.HI ^ hhfi_varset := VarSet,
+    % !:HI = !.HI ^ hhfi_vartypes := VarTypes.
 
 :- pred process_goal(set(prog_var)::in, hlds_goal::in, hlds_goal::out,
     hhf_info::in, hhf_info::out) is det.
@@ -298,9 +300,9 @@
         Unif, Context).
 process_unify(rhs_functor(ConsId0, IsExistConstruct, ArgsA), NonLocals,
         GoalInfo0, X, Mode, Unif, Context, GoalExpr, !HI) :-
-    TypeOfX = !.HI ^ vartypes ^ det_elem(X),
+    map.lookup(!.HI ^ hhfi_vartypes, X, TypeOfX),
     qualify_cons_id(TypeOfX, ArgsA, ConsId0, _, ConsId),
-    InstGraph0 = !.HI ^ inst_graph,
+    InstGraph0 = !.HI ^ hhfi_inst_graph,
     map.lookup(InstGraph0, X, node(Functors0, MaybeParent)),
     ( map.search(Functors0, ConsId, ArgsB) ->
         make_unifications(ArgsA, ArgsB, GoalInfo0, Mode, Unif, Context,
@@ -309,12 +311,12 @@
     ;
         add_unifications(ArgsA, NonLocals, GoalInfo0, Mode, Unif, Context,
             Args, Unifications, !HI),
-        InstGraph1 = !.HI ^ inst_graph,
+        InstGraph1 = !.HI ^ hhfi_inst_graph,
         map.det_insert(Functors0, ConsId, Args, Functors),
         map.det_update(InstGraph1, X, node(Functors, MaybeParent),
             InstGraph2),
         list.foldl(inst_graph.set_parent(X), Args, InstGraph2, InstGraph),
-        !:HI = !.HI ^ inst_graph := InstGraph
+        !:HI = !.HI ^ hhfi_inst_graph := InstGraph
     ),
     GINonlocals0 = goal_info_get_nonlocals(GoalInfo0),
     GINonlocals = set.union(GINonlocals0, list_to_set(Args)),
@@ -347,7 +349,7 @@
 add_unifications([], _, _, _, _, _, [], [], !HI).
 add_unifications([A | As], NonLocals, GI0, M, U, C, [V | Vs], Goals, !HI) :-
     add_unifications(As, NonLocals, GI0, M, U, C, Vs, Goals0, !HI),
-    InstGraph0 = !.HI ^ inst_graph,
+    InstGraph0 = !.HI ^ hhfi_inst_graph,
     (
         (
             map.lookup(InstGraph0, A, Node),
@@ -356,16 +358,16 @@
             set.member(A, NonLocals)
         )
     ->
-        VarSet0 = !.HI ^ varset,
-        VarTypes0 = !.HI ^ vartypes,
+        VarSet0 = !.HI ^ hhfi_varset,
+        VarTypes0 = !.HI ^ hhfi_vartypes,
         varset.new_var(VarSet0, V, VarSet),
         map.lookup(VarTypes0, A, Type),
         map.det_insert(VarTypes0, V, Type, VarTypes),
         map.init(Empty),
         map.det_insert(InstGraph0, V, node(Empty, top_level), InstGraph),
-        !:HI = !.HI ^ varset := VarSet,
-        !:HI = !.HI ^ vartypes := VarTypes,
-        !:HI = !.HI ^ inst_graph := InstGraph,
+        !:HI = !.HI ^ hhfi_varset := VarSet,
+        !:HI = !.HI ^ hhfi_vartypes := VarTypes,
+        !:HI = !.HI ^ hhfi_inst_graph := InstGraph,
         GINonlocals0 = goal_info_get_nonlocals(GI0),
         GINonlocals = set.insert(GINonlocals0, V),
         goal_info_set_nonlocals(GINonlocals, GI0, GI),
@@ -379,7 +381,7 @@
     is det.
 
 complete_inst_graph(ModuleInfo, !HI) :-
-    InstGraph0 = !.HI ^ inst_graph,
+    InstGraph0 = !.HI ^ hhfi_inst_graph,
     map.keys(InstGraph0, Vars),
     list.foldl(complete_inst_graph_node(ModuleInfo, Vars), Vars, !HI).
 
@@ -387,7 +389,7 @@
     prog_var::in, hhf_info::in, hhf_info::out) is det.
 
 complete_inst_graph_node(ModuleInfo, BaseVars, Var, !HI) :-
-    VarTypes0 = !.HI ^ vartypes,
+    VarTypes0 = !.HI ^ hhfi_vartypes,
     (
         map.search(VarTypes0, Var, Type),
         type_constructors(ModuleInfo, Type, Constructors),
@@ -405,15 +407,15 @@
 maybe_add_cons_id(Var, ModuleInfo, BaseVars, TypeCtor, Ctor, !HI) :-
     Ctor = ctor(_, _, Name, Args, _),
     ConsId = make_cons_id(Name, Args, TypeCtor),
-    map.lookup(!.HI ^ inst_graph, Var, node(Functors0, MaybeParent)),
+    map.lookup(!.HI ^ hhfi_inst_graph, Var, node(Functors0, MaybeParent)),
     ( map.contains(Functors0, ConsId) ->
         true
     ;
         list.map_foldl(add_cons_id(Var, ModuleInfo, BaseVars), Args, NewVars,
             !HI),
         map.det_insert(Functors0, ConsId, NewVars, Functors),
-        !:HI = !.HI ^ inst_graph :=
-            map.det_update(!.HI ^ inst_graph, Var,
+        !:HI = !.HI ^ hhfi_inst_graph :=
+            map.det_update(!.HI ^ hhfi_inst_graph, Var,
                 node(Functors, MaybeParent))
     ).
 
Index: compiler/higher_order.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/higher_order.m,v
retrieving revision 1.173
diff -u -b -r1.173 higher_order.m
--- compiler/higher_order.m	24 Jan 2008 03:40:54 -0000	1.173
+++ compiler/higher_order.m	25 Jan 2008 04:53:55 -0000
@@ -104,9 +104,9 @@
     map.init(GoalSizes0),
     set.init(Requests0),
     map.init(VersionInfo0),
-    some [!Info] (
-        !:Info = higher_order_global_info(Requests0, NewPreds0, VersionInfo0,
-            !.ModuleInfo, GoalSizes0, Params, counter.init(1)),
+    some [!GlobalInfo] (
+        !:GlobalInfo = higher_order_global_info(Requests0, NewPreds0,
+            VersionInfo0, !.ModuleInfo, GoalSizes0, Params, counter.init(1)),
 
         module_info_predids(PredIds0, !ModuleInfo),
         module_info_get_type_spec_info(!.ModuleInfo, TypeSpecInfo),
@@ -127,16 +127,17 @@
             set.to_sorted_list(PredIdSet, PredIds),
 
             set.to_sorted_list(UserSpecPreds, UserSpecPredList),
-            !:Info = !.Info ^ hogi_params ^ param_do_user_type_spec := yes,
-            list.foldl(get_specialization_requests, UserSpecPredList, !Info),
-            process_requests(!Info, !IO)
+            !GlobalInfo ^ hogi_params ^ param_do_user_type_spec := yes,
+            list.foldl(get_specialization_requests, UserSpecPredList,
+                !GlobalInfo),
+            process_requests(!GlobalInfo, !IO)
         ),
 
         ( bool.or_list([HigherOrder, TypeSpec, UserTypeSpec], yes) ->
             % Process all other specializations until no more requests
             % are generated.
-            list.foldl(get_specialization_requests, PredIds, !Info),
-            recursively_process_requests(!Info, !IO)
+            list.foldl(get_specialization_requests, PredIds, !GlobalInfo),
+            recursively_process_requests(!GlobalInfo, !IO)
         ;
             true
         ),
@@ -145,7 +146,7 @@
         % user-requested type specializations, since they are not called
         % from anywhere and are no longer needed.
         list.foldl(module_info_remove_predicate,
-            UserSpecPredList, !.Info ^ hogi_module_info, !:ModuleInfo)
+            UserSpecPredList, !.GlobalInfo ^ hogi_module_info, !:ModuleInfo)
     ).
 
     % Process one lot of requests, returning requests for any
@@ -154,8 +155,8 @@
 :- pred process_requests(higher_order_global_info::in,
     higher_order_global_info::out, io::di, io::uo) is det.
 
-process_requests(!Info, !IO) :-
-    filter_requests(Requests, LoopRequests, !Info, !IO),
+process_requests(!GlobalInfo, !IO) :-
+    filter_requests(Requests, LoopRequests, !GlobalInfo, !IO),
     (
         Requests = []
     ;
@@ -163,20 +164,20 @@
         some [!PredProcsToFix] (
             set.init(!:PredProcsToFix),
             create_new_preds(Requests, [], NewPredList, !PredProcsToFix,
-                !Info, !IO),
-            list.foldl(check_loop_request(!.Info), LoopRequests,
+                !GlobalInfo, !IO),
+            list.foldl(check_loop_request(!.GlobalInfo), LoopRequests,
                 !PredProcsToFix),
             set.to_sorted_list(!.PredProcsToFix, PredProcs)
         ),
-        fixup_specialized_versions(NewPredList, !Info),
-        fixup_preds(PredProcs, !Info),
+        fixup_specialized_versions(NewPredList, !GlobalInfo),
+        fixup_preds(PredProcs, !GlobalInfo),
         (
             NewPredList = [_ | _],
             % The dependencies may have changed, so the dependency graph
             % needs to rebuilt for inlining to work properly.
-            ModuleInfo0 = !.Info ^ hogi_module_info,
+            ModuleInfo0 = !.GlobalInfo ^ hogi_module_info,
             module_info_clobber_dependency_info(ModuleInfo0, ModuleInfo),
-            !:Info = !.Info ^ hogi_module_info := ModuleInfo
+            !GlobalInfo ^ hogi_module_info := ModuleInfo
         ;
             NewPredList = []
         )
@@ -187,36 +188,34 @@
 :- pred recursively_process_requests(higher_order_global_info::in,
     higher_order_global_info::out, io::di, io::uo) is det.
 
-recursively_process_requests(!Info, !IO) :-
-    ( set.empty(!.Info ^ hogi_requests) ->
+recursively_process_requests(!GlobalInfo, !IO) :-
+    ( set.empty(!.GlobalInfo ^ hogi_requests) ->
         true
     ;
-        process_requests(!Info, !IO),
-        recursively_process_requests(!Info, !IO)
+        process_requests(!GlobalInfo, !IO),
+        recursively_process_requests(!GlobalInfo, !IO)
     ).
 
 %-----------------------------------------------------------------------------%
 
 :- type higher_order_global_info
     --->    higher_order_global_info(
-                hogi_requests       :: set(request),
                                     % Requested versions.
+                hogi_requests       :: set(request),
 
-                hogi_new_preds      :: new_preds,
                                     % Specialized versions for each predicate
                                     % not changed by traverse_proc_body.
+                hogi_new_preds      :: new_preds,
 
+                % Extra information about each specialized version.
                 hogi_version_info   :: map(pred_proc_id, version_info),
-                                    % Extra information about each specialized
-                                    % version.
 
                 hogi_module_info    :: module_info,
                 hogi_goal_sizes     :: goal_sizes,
                 hogi_params         :: ho_params,
 
+                % Number identifying a specialized version.
                 hogi_next_id        :: counter
-                                    % Number identifying a specialized
-                                    % version.
             ).
 
     % Used while traversing goals.
@@ -225,57 +224,49 @@
     --->    higher_order_info(
                 hoi_global_info         :: higher_order_global_info,
 
+                % Higher_order variables.
                 hoi_pred_vars           :: pred_vars,
-                                        % higher_order variables.
 
+                % The pred_proc_id, pred_info and proc_info of the procedure
+                % whose body is being traversed.
                 hoi_pred_proc_id        :: pred_proc_id,
-                                        % pred_proc_id of goal being traversed.
-
                 hoi_pred_info           :: pred_info,
-                                        % pred_info of goal being traversed.
-
                 hoi_proc_info           :: proc_info,
-                                        % proc_info of goal being traversed.
 
                 hoi_changed             :: changed
             ).
 
 :- type request
     --->    ho_request(
+                % Calling predicate.
                 rq_caller           :: pred_proc_id,
-                                    % calling pred
 
+                % Called predicate.
                 rq_callee           :: pred_proc_id,
-                                    % called pred
 
+                % The call's arguments.
                 rq_args             :: list(prog_var),
-                                    % call args
 
+                % Type variables for which extra type-infos must be passed
+                % from the caller if --typeinfo-liveness is set.
                 rq_tvars            :: list(tvar),
-                                    % Type variables for which
-                                    % extra type-infos must be
-                                    % passed from the caller if
-                                    % --typeinfo-liveness is set.
 
+                % Argument types in caller.
                 rq_ho_args          :: list(higher_order_arg),
                 rq_caller_types     :: list(mer_type),
-                                    % argument types in caller
 
-                rq_typeinfo_liveness :: bool,
-                                    % Should the interface of
-                                    % the specialized procedure
+                % Should the interface of the specialized procedure
                                     % use typeinfo liveness?
+                rq_typeinfo_liveness :: bool,
 
-                rq_caller_tvarset   :: tvarset,
                                     % Caller's typevarset.
+                rq_caller_tvarset   :: tvarset,
 
-                rq_user_req_spec    :: bool,
                                     % Is this a user-requested specialization?
+                rq_user_req_spec    :: bool,
 
+                % Context of the call which caused the request to be generated.
                 rq_call_context     :: context
-                                    % Context of the call which
-                                    % caused the request to be
-                                    % generated.
             ).
 
     % Stores cons_id, index in argument vector, number of
@@ -287,29 +278,28 @@
 :- type higher_order_arg
     --->    higher_order_arg(
                 hoa_cons_id         :: cons_id,
-                hoa_index           :: int,
+
                                     % Index in argument vector.
+                hoa_index                   :: int,
 
-                hoa_num_curried_args :: int,
                                     % Number of curried args.
+                hoa_num_curried_args        :: int,
 
-                hoa_curry_arg_in_caller :: list(prog_var),
                                     % Curried arguments in caller.
+                hoa_curry_arg_in_caller     :: list(prog_var),
 
-                hoa_curry_type_in_caller :: list(mer_type),
                                     % Curried argument types in caller.
+                hoa_curry_type_in_caller    :: list(mer_type),
 
+                % Types associated with type_infos and constraints associated
+                % with typeclass_infos in the arguments.
                 hoa_curry_rtti_type :: list(rtti_var_info),
-                                    % Types associated with type_infos and
-                                    % constraints associated with
-                                    % typeclass_infos in the arguments.
 
+                % Higher-order curried arguments with known values.
                 hoa_known_curry_args :: list(higher_order_arg),
-                                    % Higher-order curried arguments
-                                    % with known values.
 
-                hoa_is_constant     :: bool
                                     % Is this higher_order_arg a constant?
+                hoa_is_constant             :: bool
             ).
 
     % Stores the size of each predicate's goal used in the heuristic
@@ -339,79 +329,88 @@
 
 :- type ho_params
     --->    ho_params(
-                param_do_higher_order_spec  :: bool,
                                             % Propagate higher-order constants.
-                param_do_type_spec          :: bool,
+                param_do_higher_order_spec  :: bool,
+
                                             % Propagate type-info constants.
-                param_do_user_type_spec     :: bool,
+                param_do_type_spec          :: bool,
+
                                             % User-guided type specialization.
-                param_size_limit            :: int,
+                param_do_user_type_spec     :: bool,
+
                                             % Size limit on requested version.
+                param_size_limit            :: int,
+
+                % The maximum size of the higher order arguments
+                % of a specialized version.
                 param_arg_limit             :: int
-                                            % The maximum size of the higher
-                                            % order arguments of a specialized
-                                            % version.
             ).
 
 :- type version_info
     --->    version_info(
+                % The procedure from the original program from which
+                % this version was created.
                 pred_proc_id,
-                        % The procedure from the original program
-                        % from which this version was created.
 
-                int,    % Depth of the higher_order_args for this version.
+                % Depth of the higher_order_args for this version.
+                int,
 
+                % Higher-order or constant input variables for a
+                % specialised version.
                 pred_vars,
-                        % Higher-order or constant input variables
-                        % for a specialised version.
 
+                % The chain of specialized versions which caused this version
+                % to be created. For each element in the list with the same
+                % pred_proc_id, the depth must decrease. This ensures that
+                % the specialization process must terminate.
                 list(parent_version_info)
-                        % The chain of specialized versions which caused this
-                        % version to be created.  For each element in the list
-                        % with the same pred_proc_id, the depth must decrease.
-                        % This ensures that the specialization process must
-                        % terminate.
             ).
 
 :- type parent_version_info
     --->    parent_version_info(
-                pred_proc_id,
                         % The procedure from the original program from which
                         % this parent was created.
+                pred_proc_id,
 
-                int
                         % Depth of the higher_order_args for this version.
+                int
             ).
 
 :- type new_pred
     --->    new_pred(
-                np_version_ppid         :: pred_proc_id,
                                         % version pred_proc_id
-                np_old_ppid             :: pred_proc_id,
+                np_version_ppid         :: pred_proc_id,
+
                                         % old pred_proc_id
-                np_req_ppid             :: pred_proc_id,
+                np_old_ppid             :: pred_proc_id,
+
                                         % requesting caller
-                np_name                 :: sym_name,
+                np_req_ppid             :: pred_proc_id,
+
                                         % name
-                np_spec_args            :: list(higher_order_arg),
+                np_name                 :: sym_name,
+
                                         % specialized args
+                np_spec_args            :: list(higher_order_arg),
+
+                % Unspecialised argument vars in caller.
                 np_unspec_actuals       :: list(prog_var),
-                                        % Unspecialised argument vars in
-                                        % caller.
-                np_extra_act_ti_vars    :: list(tvar),
+
                                         % Extra typeinfo tvars in caller.
+                np_extra_act_ti_vars    :: list(tvar),
+
+                % Unspecialised argument types in requesting caller.
                 np_unspec_act_types     :: list(mer_type),
-                                        % Unspecialised argument types
-                                        % in requesting caller.
-                np_typeinfo_liveness    :: bool,
-                                        % Does the interface of the
-                                        % specialized version use type-info
+
+                % Does the interface of the specialized version use type-info
                                         % liveness?
-                np_call_tvarset         :: tvarset,
+                np_typeinfo_liveness    :: bool,
+
                                         % Caller's typevarset.
+                np_call_tvarset         :: tvarset,
+
+                % Is this a user-specified type specialization?
                 np_is_user_spec         :: bool
-                                        % Is this a user-specified type
-                                        % specialization?
             ).
 
     % Returned by traverse_proc_body.
@@ -515,7 +514,7 @@
         map.search(VersionInfoMap, !.Info ^ hoi_pred_proc_id, VersionInfo),
         VersionInfo = version_info(_, _, PredVars, _)
     ->
-        !:Info = !.Info ^ hoi_pred_vars := PredVars
+        !Info ^ hoi_pred_vars := PredVars
     ;
         true
     ),
@@ -2814,8 +2813,8 @@
     pred_info::out, higher_order_global_info::in,
     higher_order_global_info::out) is det.
 
-create_new_proc(NewPred, !.NewProcInfo, !NewPredInfo, !Info) :-
-    ModuleInfo = !.Info ^ hogi_module_info,
+create_new_proc(NewPred, !.NewProcInfo, !NewPredInfo, !GlobalInfo) :-
+    ModuleInfo = !.GlobalInfo ^ hogi_module_info,
 
     NewPred = new_pred(NewPredProcId, OldPredProcId, CallerPredProcId, _Name,
         HOArgs0, CallArgs, ExtraTypeInfoTVars0, CallerArgTypes0, _, _, _),
@@ -2938,7 +2937,7 @@
     % applied, but not TypeRenaming. Perhaps this is enough?
 
     % Record extra information about this version.
-    VersionInfoMap0 = !.Info ^ hogi_version_info,
+    VersionInfoMap0 = !.GlobalInfo ^ hogi_version_info,
     ArgsDepth = higher_order_args_depth(HOArgs),
 
     ( map.search(VersionInfoMap0, OldPredProcId, OldProcVersionInfo) ->
@@ -2959,7 +2958,7 @@
         PredVars, ParentVersions),
     map.det_insert(VersionInfoMap0, NewPredProcId, VersionInfo,
         VersionInfoMap),
-    !:Info = !.Info ^ hogi_version_info := VersionInfoMap,
+    !GlobalInfo ^ hogi_version_info := VersionInfoMap,
 
     % Fix up the argument vars, types and modes.
     in_mode(InMode),
Index: compiler/interval.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/interval.m,v
retrieving revision 1.36
diff -u -b -r1.36 interval.m
--- compiler/interval.m	30 Dec 2007 08:23:44 -0000	1.36
+++ compiler/interval.m	12 Jan 2008 20:42:36 -0000
@@ -105,29 +105,29 @@
 
 :- type interval_params
     --->    interval_params(
-                module_info     :: module_info,
-                var_types       :: vartypes,
-                at_most_zero_calls  :: bool
+                ip_module_info          :: module_info,
+                ip_var_types            :: vartypes,
+                ip_at_most_zero_calls   :: bool
             ).
 
 :- type interval_info
     --->    interval_info(
-                interval_params     :: interval_params,
-                flushed_later       :: set(prog_var),
-                accessed_later      :: set(prog_var),
-                branch_resume_map   :: map(goal_path, resume_save_status),
-                branch_end_map      :: map(goal_path, branch_end_info),
-                cond_end_map        :: map(goal_path, interval_id),
-                cur_interval        :: interval_id,
-                interval_counter    :: counter,
-                open_intervals      :: set(interval_id),
-                anchor_follow_map   :: map(anchor, anchor_follow_info),
-                model_non_anchors   :: set(anchor),
-                interval_start      :: map(interval_id, anchor),
-                interval_end        :: map(interval_id, anchor),
-                interval_succ       :: map(interval_id, list(interval_id)),
-                interval_vars       :: map(interval_id, set(prog_var)),
-                interval_delvars    :: map(interval_id, list(set(prog_var)))
+                ii_interval_params      :: interval_params,
+                ii_flushed_later        :: set(prog_var),
+                ii_accessed_later       :: set(prog_var),
+                ii_branch_resume_map    :: map(goal_path, resume_save_status),
+                ii_branch_end_map       :: map(goal_path, branch_end_info),
+                ii_cond_end_map         :: map(goal_path, interval_id),
+                ii_cur_interval         :: interval_id,
+                ii_interval_counter     :: counter,
+                ii_open_intervals       :: set(interval_id),
+                ii_anchor_follow_map    :: map(anchor, anchor_follow_info),
+                ii_model_non_anchors    :: set(anchor),
+                ii_interval_start       :: map(interval_id, anchor),
+                ii_interval_end         :: map(interval_id, anchor),
+                ii_interval_succ        :: map(interval_id, list(interval_id)),
+                ii_interval_vars        :: map(interval_id, set(prog_var)),
+                ii_interval_delvars     :: map(interval_id, list(set(prog_var)))
             ).
 
 :- type maybe_needs_flush
@@ -280,10 +280,10 @@
     ;
         GoalExpr = generic_call(GenericCall, ArgVars, ArgModes, _Detism),
         goal_info_get_maybe_need_across_call(GoalInfo, MaybeNeedAcrossCall),
-        IntParams = !.IntervalInfo ^ interval_params,
-        VarTypes = IntParams ^ var_types,
+        IntParams = !.IntervalInfo ^ ii_interval_params,
+        VarTypes = IntParams ^ ip_var_types,
         list.map(map.lookup(VarTypes), ArgVars, ArgTypes),
-        ModuleInfo = IntParams ^ module_info,
+        ModuleInfo = IntParams ^ ip_module_info,
         arg_info.compute_in_and_out_vars(ModuleInfo, ArgVars,
             ArgModes, ArgTypes, InputArgs, _OutputArgs),
 
@@ -307,11 +307,11 @@
         )
     ;
         GoalExpr = plain_call(PredId, ProcId, ArgVars, Builtin, _, _),
-        IntParams = !.IntervalInfo ^ interval_params,
-        ModuleInfo = IntParams ^ module_info,
+        IntParams = !.IntervalInfo ^ ii_interval_params,
+        ModuleInfo = IntParams ^ ip_module_info,
         module_info_pred_proc_info(ModuleInfo, PredId, ProcId,
             _PredInfo, ProcInfo),
-        VarTypes = IntParams ^ var_types,
+        VarTypes = IntParams ^ ip_var_types,
         arg_info.partition_proc_call_args(ProcInfo, VarTypes,
             ModuleInfo, ArgVars, InputArgs, _, _),
         set.to_sorted_list(InputArgs, Inputs),
@@ -331,11 +331,11 @@
     ;
         GoalExpr = call_foreign_proc(_Attributes, PredId, ProcId,
             Args, ExtraArgs, _MaybeTraceRuntimeCond, _PragmaCode),
-        IntParams = !.IntervalInfo ^ interval_params,
-        ModuleInfo = IntParams ^ module_info,
+        IntParams = !.IntervalInfo ^ ii_interval_params,
+        ModuleInfo = IntParams ^ ip_module_info,
         module_info_pred_proc_info(ModuleInfo, PredId, ProcId,
             _PredInfo, ProcInfo),
-        VarTypes = IntParams ^ var_types,
+        VarTypes = IntParams ^ ip_var_types,
         ArgVars = list.map(foreign_arg_var, Args),
         ExtraVars = list.map(foreign_arg_var, ExtraArgs),
         arg_info.partition_proc_call_args(ProcInfo, VarTypes,
@@ -380,8 +380,8 @@
         ;
             Unification = deconstruct(CellVar, ConsId, ArgVars, ArgModes,
                 _, _),
-            IntParams = !.IntervalInfo ^ interval_params,
-            ModuleInfo = IntParams ^ module_info,
+            IntParams = !.IntervalInfo ^ ii_interval_params,
+            ModuleInfo = IntParams ^ ip_module_info,
             ( shared_left_to_right_deconstruct(ModuleInfo, ArgModes) ->
                 Goal = hlds_goal(GoalExpr, GoalInfo),
                 use_cell(CellVar, ArgVars, ConsId, Goal, !IntervalInfo, !Acc)
@@ -442,10 +442,10 @@
         record_interval_start(AfterCallId, CallAnchor, !IntervalInfo),
         record_interval_end(BeforeCallId, CallAnchor, !IntervalInfo),
         InstMapDelta = goal_info_get_instmap_delta(GoalInfo),
-        IntParams = !.IntervalInfo ^ interval_params,
+        IntParams = !.IntervalInfo ^ ii_interval_params,
         (
             ( instmap_delta_is_reachable(InstMapDelta)
-            ; IntParams ^ at_most_zero_calls = no
+            ; IntParams ^ ip_at_most_zero_calls = no
             )
         ->
             record_interval_succ(BeforeCallId, AfterCallId, !IntervalInfo),
@@ -603,8 +603,8 @@
         assign_open_intervals_to_anchor(StartAnchor, !IntervalInfo)
     ).
 
-:- pred reached_cond_then(hlds_goal_info::in, interval_info::in,
-    interval_info::out) is det.
+:- pred reached_cond_then(hlds_goal_info::in,
+    interval_info::in, interval_info::out) is det.
 
 reached_cond_then(GoalInfo, !IntervalInfo) :-
     GoalPath = goal_info_get_goal_path(GoalInfo),
@@ -639,33 +639,33 @@
 :- pred get_open_intervals(interval_info::in, set(interval_id)::out) is det.
 
 get_open_intervals(IntervalInfo, OpenIntervals) :-
-    OpenIntervals = IntervalInfo ^ open_intervals.
+    OpenIntervals = IntervalInfo ^ ii_open_intervals.
 
 :- pred set_open_intervals(set(interval_id)::in,
     interval_info::in, interval_info::out) is det.
 
 set_open_intervals(OpenIntervals, !IntervalInfo) :-
-    !:IntervalInfo = !.IntervalInfo ^ open_intervals := OpenIntervals.
+    !:IntervalInfo = !.IntervalInfo ^ ii_open_intervals := OpenIntervals.
 
 :- pred no_open_intervals(interval_info::in, interval_info::out) is det.
 
 no_open_intervals(!IntervalInfo) :-
-    !:IntervalInfo = !.IntervalInfo ^ open_intervals := set.init.
+    !:IntervalInfo = !.IntervalInfo ^ ii_open_intervals := set.init.
 
 :- pred one_open_interval(interval_id::in, interval_info::in,
     interval_info::out) is det.
 
 one_open_interval(IntervalId, !IntervalInfo) :-
-    !:IntervalInfo = !.IntervalInfo ^ open_intervals :=
+    !:IntervalInfo = !.IntervalInfo ^ ii_open_intervals :=
         set.make_singleton_set(IntervalId).
 
 :- pred assign_open_intervals_to_anchor(anchor::in,
     interval_info::in, interval_info::out) is det.
 
 assign_open_intervals_to_anchor(Anchor, !IntervalInfo) :-
-    AnchorFollowMap0 = !.IntervalInfo ^ anchor_follow_map,
-    IntervalVarMap = !.IntervalInfo ^ interval_vars,
-    CurOpenIntervals = !.IntervalInfo ^ open_intervals,
+    AnchorFollowMap0 = !.IntervalInfo ^ ii_anchor_follow_map,
+    IntervalVarMap = !.IntervalInfo ^ ii_interval_vars,
+    CurOpenIntervals = !.IntervalInfo ^ ii_open_intervals,
     set.fold(gather_interval_vars(IntervalVarMap), CurOpenIntervals,
         set.init, CurOpenIntervalVars),
     ( map.search(AnchorFollowMap0, Anchor, AnchorFollowInfo0) ->
@@ -683,7 +683,7 @@
         svmap.det_insert(Anchor, AnchorFollowInfo,
             AnchorFollowMap0, AnchorFollowMap)
     ),
-    !:IntervalInfo = !.IntervalInfo ^ anchor_follow_map := AnchorFollowMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_anchor_follow_map := AnchorFollowMap.
 
 :- pred gather_interval_vars(map(interval_id, set(prog_var))::in,
     interval_id::in, set(prog_var)::in, set(prog_var)::out) is det.
@@ -697,89 +697,89 @@
 
 :- pred get_cur_interval(interval_id::out, interval_info::in) is det.
 
-get_cur_interval(IntervalInfo ^ cur_interval, IntervalInfo).
+get_cur_interval(IntervalInfo ^ ii_cur_interval, IntervalInfo).
 
-:- pred set_cur_interval(interval_id::in, interval_info::in,
-    interval_info::out) is det.
+:- pred set_cur_interval(interval_id::in,
+    interval_info::in, interval_info::out) is det.
 
-set_cur_interval(CurInterval, IntervalInfo,
-    IntervalInfo ^ cur_interval := CurInterval).
+set_cur_interval(CurInterval, !IntervalInfo) :-
+    !IntervalInfo ^ ii_cur_interval := CurInterval.
 
-:- pred new_interval_id(interval_id::out, interval_info::in,
-    interval_info::out) is det.
+:- pred new_interval_id(interval_id::out,
+    interval_info::in, interval_info::out) is det.
 
 new_interval_id(Id, !IntervalInfo) :-
-    Counter0 = !.IntervalInfo ^ interval_counter,
-    IntervalVars0 = !.IntervalInfo ^ interval_vars,
+    Counter0 = !.IntervalInfo ^ ii_interval_counter,
+    IntervalVars0 = !.IntervalInfo ^ ii_interval_vars,
     counter.allocate(Num, Counter0, Counter),
     Id = interval_id(Num),
     svmap.det_insert(Id, set.init, IntervalVars0, IntervalVars),
-    !:IntervalInfo = !.IntervalInfo ^ interval_counter := Counter,
-    !:IntervalInfo = !.IntervalInfo ^ interval_vars := IntervalVars.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_counter := Counter,
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_vars := IntervalVars.
 
 :- pred record_branch_end_info(goal_path::in,
     interval_info::in, interval_info::out) is det.
 
 record_branch_end_info(GoalPath, !IntervalInfo) :-
-    FlushedLater = !.IntervalInfo ^ flushed_later,
-    AccessedLater = !.IntervalInfo ^ accessed_later,
-    CurInterval = !.IntervalInfo ^ cur_interval,
-    BranchEndMap0 = !.IntervalInfo ^ branch_end_map,
+    FlushedLater = !.IntervalInfo ^ ii_flushed_later,
+    AccessedLater = !.IntervalInfo ^ ii_accessed_later,
+    CurInterval = !.IntervalInfo ^ ii_cur_interval,
+    BranchEndMap0 = !.IntervalInfo ^ ii_branch_end_map,
     BranchEndInfo = branch_end_info(FlushedLater, AccessedLater, CurInterval),
     svmap.det_insert(GoalPath, BranchEndInfo, BranchEndMap0, BranchEndMap),
-    !:IntervalInfo = !.IntervalInfo ^ branch_end_map := BranchEndMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_branch_end_map := BranchEndMap.
 
 :- pred record_cond_end(goal_path::in, interval_info::in, interval_info::out)
     is det.
 
 record_cond_end(GoalPath, !IntervalInfo) :-
-    CurInterval = !.IntervalInfo ^ cur_interval,
-    CondEndMap0 = !.IntervalInfo ^ cond_end_map,
+    CurInterval = !.IntervalInfo ^ ii_cur_interval,
+    CondEndMap0 = !.IntervalInfo ^ ii_cond_end_map,
     svmap.det_insert(GoalPath, CurInterval, CondEndMap0, CondEndMap),
-    !:IntervalInfo = !.IntervalInfo ^ cond_end_map := CondEndMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_cond_end_map := CondEndMap.
 
 :- pred record_interval_end(interval_id::in, anchor::in,
     interval_info::in, interval_info::out) is det.
 
 record_interval_end(Id, End, !IntervalInfo) :-
-    EndMap0 = !.IntervalInfo ^ interval_end,
+    EndMap0 = !.IntervalInfo ^ ii_interval_end,
     svmap.det_insert(Id, End, EndMap0, EndMap),
-    !:IntervalInfo = !.IntervalInfo ^ interval_end := EndMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_end := EndMap.
 
 :- pred record_interval_start(interval_id::in, anchor::in,
     interval_info::in, interval_info::out) is det.
 
 record_interval_start(Id, Start, !IntervalInfo) :-
-    StartMap0 = !.IntervalInfo ^ interval_start,
+    StartMap0 = !.IntervalInfo ^ ii_interval_start,
     svmap.det_insert(Id, Start, StartMap0, StartMap),
-    !:IntervalInfo = !.IntervalInfo ^ interval_start := StartMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_start := StartMap.
 
 :- pred record_interval_succ(interval_id::in, interval_id::in,
     interval_info::in, interval_info::out) is det.
 
 record_interval_succ(Id, Succ, !IntervalInfo) :-
-    SuccMap0 = !.IntervalInfo ^ interval_succ,
+    SuccMap0 = !.IntervalInfo ^ ii_interval_succ,
     ( map.search(SuccMap0, Id, Succ0) ->
         svmap.det_update(Id, [Succ | Succ0], SuccMap0, SuccMap)
     ;
         svmap.det_insert(Id, [Succ], SuccMap0, SuccMap)
     ),
-    !:IntervalInfo = !.IntervalInfo ^ interval_succ := SuccMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_succ := SuccMap.
 
 :- pred record_interval_no_succ(interval_id::in,
     interval_info::in, interval_info::out) is det.
 
 record_interval_no_succ(Id, !IntervalInfo) :-
-    SuccMap0 = !.IntervalInfo ^ interval_succ,
+    SuccMap0 = !.IntervalInfo ^ ii_interval_succ,
     ( map.search(SuccMap0, Id, _Succ0) ->
         unexpected(this_file, "record_interval_no_succ: already in succ map")
     ;
         svmap.det_insert(Id, [], SuccMap0, SuccMap)
     ),
-    !:IntervalInfo = !.IntervalInfo ^ interval_succ := SuccMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_succ := SuccMap.
 
 record_interval_vars(Id, NewVars, !IntervalInfo) :-
-    VarsMap0 = !.IntervalInfo ^ interval_vars,
+    VarsMap0 = !.IntervalInfo ^ ii_interval_vars,
     ( map.search(VarsMap0, Id, Vars0) ->
         svset.insert_list(NewVars, Vars0, Vars),
         svmap.det_update(Id, Vars, VarsMap0, VarsMap)
@@ -787,19 +787,19 @@
         set.list_to_set(NewVars, Vars),
         svmap.det_insert(Id, Vars, VarsMap0, VarsMap)
     ),
-    !:IntervalInfo = !.IntervalInfo ^ interval_vars := VarsMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_vars := VarsMap.
 
 delete_interval_vars(Id, ToDeleteVars, DeletedVars, !IntervalInfo) :-
-    VarsMap0 = !.IntervalInfo ^ interval_vars,
+    VarsMap0 = !.IntervalInfo ^ ii_interval_vars,
     map.lookup(VarsMap0, Id, Vars0),
     DeletedVars = set.intersect(Vars0, ToDeleteVars),
     Vars = set.difference(Vars0, DeletedVars),
     svmap.det_update(Id, Vars, VarsMap0, VarsMap),
-    !:IntervalInfo = !.IntervalInfo ^ interval_vars := VarsMap,
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_vars := VarsMap,
 
     % The deletions are recorded only for debugging. The algorithm itself
     % does not need this information to be recorded.
-    DeleteMap0 = !.IntervalInfo ^ interval_delvars,
+    DeleteMap0 = !.IntervalInfo ^ ii_interval_delvars,
     ( map.search(DeleteMap0, Id, Deletions0) ->
         Deletions = [DeletedVars | Deletions0],
         svmap.det_update(Id, Deletions, DeleteMap0, DeleteMap)
@@ -807,65 +807,68 @@
         Deletions = [DeletedVars],
         svmap.det_insert(Id, Deletions, DeleteMap0, DeleteMap)
     ),
-    !:IntervalInfo = !.IntervalInfo ^ interval_delvars := DeleteMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_interval_delvars := DeleteMap.
 
 :- pred require_in_regs(list(prog_var)::in, interval_info::in,
     interval_info::out) is det.
 
 require_in_regs(Vars, !IntervalInfo) :-
-    CurIntervalId = !.IntervalInfo ^ cur_interval,
+    CurIntervalId = !.IntervalInfo ^ ii_cur_interval,
     record_interval_vars(CurIntervalId, Vars, !IntervalInfo).
 
 :- pred require_flushed(set(prog_var)::in,
     interval_info::in, interval_info::out) is det.
 
 require_flushed(Vars, !IntervalInfo) :-
-    FlushedLater0 = !.IntervalInfo ^ flushed_later,
+    FlushedLater0 = !.IntervalInfo ^ ii_flushed_later,
     FlushedLater = set.union(FlushedLater0, Vars),
-    !:IntervalInfo = !.IntervalInfo ^ flushed_later := FlushedLater.
+    !:IntervalInfo = !.IntervalInfo ^ ii_flushed_later := FlushedLater.
 
 :- pred require_access(list(prog_var)::in,
     interval_info::in, interval_info::out) is det.
 
 require_access(Vars, !IntervalInfo) :-
-    AccessedLater0 = !.IntervalInfo ^ accessed_later,
+    AccessedLater0 = !.IntervalInfo ^ ii_accessed_later,
     svset.insert_list(Vars, AccessedLater0, AccessedLater),
-    !:IntervalInfo = !.IntervalInfo ^ accessed_later := AccessedLater.
+    !:IntervalInfo = !.IntervalInfo ^ ii_accessed_later := AccessedLater.
 
 :- pred record_branch_resume(goal_path::in, resume_save_status::in,
     interval_info::in, interval_info::out) is det.
 
 record_branch_resume(GoalPath, ResumeSaveStatus, !IntervalInfo) :-
-    BranchResumeMap0 = !.IntervalInfo ^ branch_resume_map,
+    BranchResumeMap0 = !.IntervalInfo ^ ii_branch_resume_map,
     svmap.det_insert(GoalPath, ResumeSaveStatus,
         BranchResumeMap0, BranchResumeMap),
-    !:IntervalInfo = !.IntervalInfo ^ branch_resume_map := BranchResumeMap.
+    !:IntervalInfo = !.IntervalInfo ^ ii_branch_resume_map := BranchResumeMap.
 
 :- pred record_model_non_anchor(anchor::in, interval_info::in,
     interval_info::out) is det.
 
 record_model_non_anchor(Anchor, !IntervalInfo) :-
-    ModelNonAnchors0 = !.IntervalInfo ^ model_non_anchors,
+    ModelNonAnchors0 = !.IntervalInfo ^ ii_model_non_anchors,
     svset.insert(Anchor, ModelNonAnchors0, ModelNonAnchors),
-    !:IntervalInfo = !.IntervalInfo ^ model_non_anchors := ModelNonAnchors.
+    !:IntervalInfo = !.IntervalInfo ^ ii_model_non_anchors := ModelNonAnchors.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
-:- type var_info
-    --->    var_info(
-                varset      :: prog_varset,
-                vartypes    :: vartypes
+:- type interval_var_info
+    --->    interval_var_info(
+                ivi_varset      :: prog_varset,
+                ivi_vartypes    :: vartypes
             ).
 
 record_decisions_in_goal(!Goal, VarSet0, VarSet, VarTypes0, VarTypes,
         !VarRename, InsertMap, MaybeFeature) :-
-    record_decisions_in_goal(!Goal, var_info(VarSet0, VarTypes0),
-        var_info(VarSet, VarTypes), !VarRename, InsertMap, MaybeFeature).
+    Info0 = interval_var_info(VarSet0, VarTypes0),
+    record_decisions_in_goal(!Goal, Info0, Info, !VarRename,
+        InsertMap, MaybeFeature),
+    Info = interval_var_info(VarSet, VarTypes).
 
 :- pred record_decisions_in_goal(hlds_goal::in, hlds_goal::out,
-    var_info::in, var_info::out, rename_map::in, rename_map::out,
-    insert_map::in, maybe(goal_feature)::in) is det.
+    interval_var_info::in, interval_var_info::out,
+    rename_map::in, rename_map::out, insert_map::in, maybe(goal_feature)::in)
+    is det.
 
 record_decisions_in_goal(Goal0, Goal, !VarInfo, !VarRename, InsertMap,
         MaybeFeature) :-
@@ -1019,7 +1022,7 @@
     ).
 
 :- pred insert_goals_after(hlds_goal::in, hlds_goal::out,
-    var_info::in, var_info::out, rename_map::out,
+    interval_var_info::in, interval_var_info::out, rename_map::out,
     list(insert_spec)::in, maybe(goal_feature)::in) is det.
 
 insert_goals_after(BranchesGoal, Goal, !VarInfo, VarRename, Inserts,
@@ -1029,7 +1032,7 @@
     BranchesGoal = hlds_goal(_, BranchesGoalInfo),
     conj_list_to_goal([BranchesGoal | InsertGoals], BranchesGoalInfo, Goal).
 
-:- pred make_inserted_goals(var_info::in, var_info::out,
+:- pred make_inserted_goals(interval_var_info::in, interval_var_info::out,
     rename_map::in, rename_map::out, list(insert_spec)::in,
     maybe(goal_feature)::in, list(hlds_goal)::out) is det.
 
@@ -1039,7 +1042,7 @@
     make_inserted_goal(!VarInfo, !VarRename, Spec, MaybeFeature, Goal),
     make_inserted_goals(!VarInfo, !VarRename, Specs, MaybeFeature, Goals).
 
-:- pred make_inserted_goal(var_info::in, var_info::out,
+:- pred make_inserted_goal(interval_var_info::in, interval_var_info::out,
     rename_map::in, rename_map::out, insert_spec::in,
     maybe(goal_feature)::in, hlds_goal::out) is det.
 
@@ -1061,10 +1064,10 @@
             GoalInfo2 = GoalInfo1
         ),
         Goal2 = hlds_goal(GoalExpr1, GoalInfo2),
-        !.VarInfo = var_info(VarSet0, VarTypes0),
+        !.VarInfo = interval_var_info(VarSet0, VarTypes0),
         create_shadow_vars(ArgVars, VarsToExtract, VarSet0, VarSet,
             VarTypes0, VarTypes, map.init, NewRename, map.init, VoidRename),
-        !:VarInfo = var_info(VarSet, VarTypes),
+        !:VarInfo = interval_var_info(VarSet, VarTypes),
         map.old_merge(!.VarRename, NewRename, !:VarRename),
         % We rename the original goal.
         rename_some_vars_in_goal(!.VarRename, Goal2, Goal3),
@@ -1075,9 +1078,10 @@
 
 make_inserted_goal(VarSet0, VarSet, VarTypes0, VarTypes, !RenameMap,
         InsertSpec, MaybeFeature, Goal) :-
-    make_inserted_goal(var_info(VarSet0, VarTypes0),
-        var_info(VarSet, VarTypes), !RenameMap, InsertSpec,
-        MaybeFeature, Goal).
+    Info0 = interval_var_info(VarSet0, VarTypes0),
+    make_inserted_goal(Info0, Info, !RenameMap, InsertSpec,
+        MaybeFeature, Goal),
+    Info = interval_var_info(VarSet, VarTypes).
 
 :- pred create_shadow_vars(list(prog_var)::in, set(prog_var)::in,
     prog_varset::in, prog_varset::out, vartypes::in, vartypes::out,
@@ -1111,8 +1115,9 @@
 %-----------------------------------------------------------------------------%
 
 :- pred record_decisions_at_call_site(hlds_goal::in, hlds_goal::out,
-    var_info::in, var_info::out, rename_map::in, rename_map::out,
-    bool::in, insert_map::in, maybe(goal_feature)::in) is det.
+    interval_var_info::in, interval_var_info::out,
+    rename_map::in, rename_map::out, bool::in, insert_map::in,
+    maybe(goal_feature)::in) is det.
 
 record_decisions_at_call_site(Goal0, Goal, !VarInfo, !VarRename,
         MustHaveMap, InsertMap, MaybeFeature) :-
@@ -1141,8 +1146,9 @@
 %-----------------------------------------------------------------------------%
 
 :- pred record_decisions_in_conj(list(hlds_goal)::in, list(hlds_goal)::out,
-    var_info::in, var_info::out, rename_map::in, rename_map::out,
-    conj_type::in, insert_map::in, maybe(goal_feature)::in) is det.
+    interval_var_info::in, interval_var_info::out,
+    rename_map::in, rename_map::out, conj_type::in, insert_map::in,
+    maybe(goal_feature)::in) is det.
 
 record_decisions_in_conj([], [], !VarInfo, !VarRename, _, _, _).
 record_decisions_in_conj([Goal0 | Goals0], Goals, !VarInfo, !VarRename,
@@ -1161,8 +1167,9 @@
     ).
 
 :- pred record_decisions_in_disj(list(hlds_goal)::in, list(hlds_goal)::out,
-    var_info::in, var_info::out, rename_map::in, list(insert_spec)::in,
-    insert_map::in, maybe(goal_feature)::in) is det.
+    interval_var_info::in, interval_var_info::out,
+    rename_map::in, list(insert_spec)::in, insert_map::in,
+    maybe(goal_feature)::in) is det.
 
 record_decisions_in_disj([], [], !VarInfo, _, _, _, _).
 record_decisions_in_disj([Goal0 | Goals0], [Goal | Goals], !VarInfo,
@@ -1177,8 +1184,8 @@
         Inserts, InsertMap, MaybeFeature).
 
 :- pred record_decisions_in_cases(list(case)::in, list(case)::out,
-    var_info::in, var_info::out, rename_map::in, insert_map::in,
-        maybe(goal_feature)::in) is det.
+    interval_var_info::in, interval_var_info::out,
+    rename_map::in, insert_map::in, maybe(goal_feature)::in) is det.
 
 record_decisions_in_cases([], [], !VarInfo, _, _, _).
 record_decisions_in_cases([Case0 | Cases0], [Case | Cases],
@@ -1230,16 +1237,16 @@
 % For debugging purposes.
 
 dump_interval_info(IntervalInfo, !IO) :-
-    map.keys(IntervalInfo ^ interval_start, StartIds),
-    map.keys(IntervalInfo ^ interval_end, EndIds),
-    map.keys(IntervalInfo ^ interval_vars, VarsIds),
-    map.keys(IntervalInfo ^ interval_succ, SuccIds),
+    map.keys(IntervalInfo ^ ii_interval_start, StartIds),
+    map.keys(IntervalInfo ^ ii_interval_end, EndIds),
+    map.keys(IntervalInfo ^ ii_interval_vars, VarsIds),
+    map.keys(IntervalInfo ^ ii_interval_succ, SuccIds),
     list.condense([StartIds, EndIds, VarsIds, SuccIds], IntervalIds0),
     list.sort_and_remove_dups(IntervalIds0, IntervalIds),
     io.write_string("INTERVALS:\n", !IO),
     list.foldl(dump_interval_info_id(IntervalInfo), IntervalIds, !IO),
 
-    map.to_assoc_list(IntervalInfo ^ anchor_follow_map, AnchorFollows),
+    map.to_assoc_list(IntervalInfo ^ ii_anchor_follow_map, AnchorFollows),
     io.write_string("\nANCHOR FOLLOW:\n", !IO),
     list.foldl(dump_anchor_follow, AnchorFollows, !IO).
 
@@ -1250,7 +1257,7 @@
     io.write_string("\ninterval ", !IO),
     io.write_int(interval_id_to_int(IntervalId), !IO),
     io.write_string(": ", !IO),
-    ( map.search(IntervalInfo ^ interval_succ, IntervalId, SuccIds) ->
+    ( map.search(IntervalInfo ^ ii_interval_succ, IntervalId, SuccIds) ->
         SuccNums = list.map(interval_id_to_int, SuccIds),
         io.write_string("succ [", !IO),
         write_int_list(SuccNums, !IO),
@@ -1258,21 +1265,21 @@
     ;
         io.write_string("no succ\n", !IO)
     ),
-    ( map.search(IntervalInfo ^ interval_start, IntervalId, Start) ->
+    ( map.search(IntervalInfo ^ ii_interval_start, IntervalId, Start) ->
         io.write_string("start ", !IO),
         io.write(Start, !IO),
         io.write_string("\n", !IO)
     ;
         io.write_string("no start\n", !IO)
     ),
-    ( map.search(IntervalInfo ^ interval_end, IntervalId, End) ->
+    ( map.search(IntervalInfo ^ ii_interval_end, IntervalId, End) ->
         io.write_string("end ", !IO),
         io.write(End, !IO),
         io.write_string("\n", !IO)
     ;
         io.write_string("no end\n", !IO)
     ),
-    ( map.search(IntervalInfo ^ interval_vars, IntervalId, Vars) ->
+    ( map.search(IntervalInfo ^ ii_interval_vars, IntervalId, Vars) ->
         list.map(term.var_to_int, set.to_sorted_list(Vars), VarNums),
         io.write_string("vars [", !IO),
         write_int_list(VarNums, !IO),
@@ -1280,7 +1287,7 @@
     ;
         io.write_string("no vars\n", !IO)
     ),
-    ( map.search(IntervalInfo ^ interval_delvars, IntervalId, Deletions) ->
+    ( map.search(IntervalInfo ^ ii_interval_delvars, IntervalId, Deletions) ->
         io.write_string("deletions", !IO),
         list.foldl(dump_deletion, Deletions, !IO),
         io.write_string("\n", !IO)
Index: compiler/lco.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lco.m,v
retrieving revision 1.52
diff -u -b -r1.52 lco.m
--- compiler/lco.m	22 Jan 2008 15:06:12 -0000	1.52
+++ compiler/lco.m	24 Jan 2008 01:18:49 -0000
@@ -171,23 +171,23 @@
 
 :- type lco_info
     --->    lco_info(
-                module_info         :: module_info,
-                cur_scc_variants    :: variant_map,
-                var_set             :: prog_varset,
-                var_types           :: vartypes,
-                permitted           :: permitted,
-                changed             :: changed
+                lco_module_info         :: module_info,
+                lco_cur_scc_variants    :: variant_map,
+                lco_var_set             :: prog_varset,
+                lco_var_types           :: vartypes,
+                lco_permitted           :: permitted,
+                lco_changed             :: changed
             ).
 
 :- type lco_const_info
     --->    lco_const_info(
-                lower_scc_variants  :: variant_map,
-                cur_scc             :: set(pred_proc_id),
-                cur_proc_id         :: pred_proc_id,
-                cur_proc_pred       :: pred_info,
-                cur_proc_proc       :: proc_info,
-                cur_proc_outputs    :: list(prog_var),
-                cur_proc_detism     :: determinism
+                lci_lower_scc_variants  :: variant_map,
+                lci_cur_scc             :: set(pred_proc_id),
+                lci_cur_proc_id         :: pred_proc_id,
+                lci_cur_proc_pred       :: pred_info,
+                lci_cur_proc_proc       :: proc_info,
+                lci_cur_proc_outputs    :: list(prog_var),
+                lci_cur_proc_detism     :: determinism
             ).
 
 %-----------------------------------------------------------------------------%
@@ -380,7 +380,7 @@
         ;
             ConjType = parallel_conj,
             GoalExpr = GoalExpr0,
-            !:Info = !.Info ^ permitted := not_permitted
+            !:Info = !.Info ^ lco_permitted := not_permitted
         )
     ;
         GoalExpr0 = disj(Goals0),
@@ -466,8 +466,8 @@
 lco_in_conj([RevGoal | RevGoals], !.Unifies, !.UnifyInputVars, MaybeGoals,
         !Info, ConstInfo) :-
     RevGoal = hlds_goal(RevGoalExpr, RevGoalInfo),
-    ModuleInfo = !.Info ^ module_info,
-    ProcInfo = ConstInfo ^ cur_proc_proc,
+    ModuleInfo = !.Info ^ lco_module_info,
+    ProcInfo = ConstInfo ^ lci_cur_proc_proc,
     proc_info_get_vartypes(ProcInfo, VarTypes),
     (
         RevGoalExpr = unify(_, _, _, Unification, _),
@@ -498,8 +498,9 @@
     ;
         RevGoalExpr = plain_call(PredId, ProcId, Args, Builtin, UnifyContext,
             SymName),
-        set.member(proc(PredId, ProcId), ConstInfo ^ cur_scc),
-        goal_info_get_determinism(RevGoalInfo) = ConstInfo ^ cur_proc_detism,
+        set.member(proc(PredId, ProcId), ConstInfo ^ lci_cur_scc),
+        goal_info_get_determinism(RevGoalInfo) =
+            ConstInfo ^ lci_cur_proc_detism,
 
         module_info_pred_proc_info(ModuleInfo, PredId, ProcId,
             _CalleePredInfo, CalleeProcInfo),
@@ -508,7 +509,7 @@
             _InArgs, OutArgs, UnusedArgs),
         UnusedArgs = [],
         list.length(OutArgs, NumOutArgs),
-        CurrProcOutArgs = ConstInfo ^ cur_proc_outputs,
+        CurrProcOutArgs = ConstInfo ^ lci_cur_proc_outputs,
         list.length(CurrProcOutArgs, NumCurrProcOutArgs),
         NumOutArgs = NumCurrProcOutArgs,
 
@@ -537,7 +538,7 @@
         UpdatedGoal = hlds_goal(UpdatedGoalExpr, UpdatedGoalInfo),
         Goals = list.reverse(RevGoals) ++ UpdatedUnifies ++ [UpdatedGoal],
         MaybeGoals = yes(Goals),
-        !:Info = !.Info ^ changed := changed
+        !:Info = !.Info ^ lco_changed := changed
     ;
         % The reversed conjunction does not follow the pattern we are looking
         % for, so we cannot optimize it.
@@ -632,15 +633,15 @@
     lco_info::in, lco_info::out) is det.
 
 make_address_var(Var, AddrVar, !Info) :-
-    VarSet0 = !.Info ^ var_set,
-    VarTypes0 = !.Info ^ var_types,
+    VarSet0 = !.Info ^ lco_var_set,
+    VarTypes0 = !.Info ^ lco_var_types,
     varset.lookup_name(VarSet0, Var, "SCCcallarg", Name),
     AddrName = "Addr" ++ Name,
     varset.new_named_var(VarSet0, AddrName, AddrVar, VarSet),
     map.lookup(VarTypes0, Var, FieldType),
     map.det_insert(VarTypes0, AddrVar, make_ref_type(FieldType), VarTypes),
-    !:Info = !.Info ^ var_set := VarSet,
-    !:Info = !.Info ^ var_types := VarTypes.
+    !:Info = !.Info ^ lco_var_set := VarSet,
+    !:Info = !.Info ^ lco_var_types := VarTypes.
 
 :- func make_ref_type(mer_type) = mer_type.
 
@@ -657,7 +658,7 @@
 
 ensure_variant_exists(PredId, ProcId, AddrArgNums, VariantPredProcId,
         SymName, VariantSymName, !Info) :-
-    CurSCCVariants0 = !.Info ^ cur_scc_variants,
+    CurSCCVariants0 = !.Info ^ lco_cur_scc_variants,
     ( map.search(CurSCCVariants0, proc(PredId, ProcId), ExistingVariant) ->
         ExistingVariant = variant_id(ExistingAddrArgNums, VariantPredProcId,
             VariantName),
@@ -670,11 +671,11 @@
         ),
         AddrArgNums = ExistingAddrArgNums
     ;
-        ModuleInfo0 = !.Info ^ module_info,
+        ModuleInfo0 = !.Info ^ lco_module_info,
         clone_pred_proc(PredId, ClonePredId, PredOrFunc,
             ModuleInfo0, ModuleInfo),
         VariantPredProcId = proc(ClonePredId, ProcId),
-        !:Info = !.Info ^ module_info := ModuleInfo,
+        !:Info = !.Info ^ lco_module_info := ModuleInfo,
         (
             SymName = unqualified(Name),
             create_variant_name(PredOrFunc, AddrArgNums, Name, VariantName),
@@ -688,7 +689,7 @@
             VariantName),
         map.det_insert(CurSCCVariants0, proc(PredId, ProcId), NewVariant,
             CurSCCVariants),
-        !:Info = !.Info ^ cur_scc_variants := CurSCCVariants
+        !:Info = !.Info ^ lco_cur_scc_variants := CurSCCVariants
     ).
 
 :- pred clone_pred_proc(pred_id::in, pred_id::out, pred_or_func::out,
Index: compiler/live_vars.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/live_vars.m,v
retrieving revision 1.135
diff -u -b -r1.135 live_vars.m
--- compiler/live_vars.m	21 Jan 2008 00:32:49 -0000	1.135
+++ compiler/live_vars.m	21 Jan 2008 04:13:44 -0000
@@ -35,10 +35,10 @@
 
 :- type alloc_data
     --->    alloc_data(
-                module_info         ::  module_info,
-                proc_info           ::  proc_info,
-                typeinfo_liveness   ::  bool,
-                opt_no_return_calls ::  bool
+                ad_module_info          ::  module_info,
+                ad_proc_info            ::  proc_info,
+                ad_typeinfo_liveness    ::  bool,
+                ad_opt_no_return_calls  ::  bool
             ).
 
 :- typeclass stack_alloc_info(T) where [
@@ -79,15 +79,17 @@
     %
 :- type parallel_stackvars
     --->    parallel_stackvars(
-                set(prog_var),
                     % Variables nonlocal to the parallel conjunction which need
                     % their own stack slots.
-                list(set(prog_var)),
+                set(prog_var),
+
                     % Variables local to parallel conjuncts prior to the
                     % current conjunct which need stack slots.
-                set(prog_var)
+                list(set(prog_var)),
+
                     % Accumulating set of variables local to the current
                     % parallel conjunct which need stack slots.
+                set(prog_var)
             ).
 
 %-----------------------------------------------------------------------------%
@@ -354,10 +356,10 @@
             ; GenericCall = class_method(_, _, _, _)
             ; GenericCall = event_call(_)
             ),
-            ProcInfo = AllocData ^ proc_info,
+            ProcInfo = AllocData ^ ad_proc_info,
             proc_info_get_vartypes(ProcInfo, VarTypes),
             map.apply_to_list(ArgVars, VarTypes, Types),
-            ModuleInfo = AllocData ^ module_info,
+            ModuleInfo = AllocData ^ ad_module_info,
             arg_info.partition_generic_call_args(ModuleInfo, ArgVars,
                 Types, Modes, _InVars, OutVars, _UnusedVars),
             build_live_sets_in_call(OutVars, GoalInfo0, GoalInfo,
@@ -367,8 +369,8 @@
     ;
         GoalExpr0 = plain_call(PredId, ProcId, ArgVars, Builtin, _, _),
         GoalExpr = GoalExpr0,
-        ModuleInfo = AllocData ^ module_info,
-        CallerProcInfo = AllocData ^ proc_info,
+        ModuleInfo = AllocData ^ ad_module_info,
+        CallerProcInfo = AllocData ^ ad_proc_info,
         proc_info_get_vartypes(CallerProcInfo, VarTypes),
         module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
         arg_info.partition_proc_call_args(ProcInfo, VarTypes, ModuleInfo,
@@ -403,8 +405,8 @@
         GoalExpr0 = call_foreign_proc(Attributes, PredId, ProcId, Args,
             _, _, _),
         GoalExpr = GoalExpr0,
-        ModuleInfo = AllocData ^ module_info,
-        CallerProcInfo = AllocData ^ proc_info,
+        ModuleInfo = AllocData ^ ad_module_info,
+        CallerProcInfo = AllocData ^ ad_proc_info,
         proc_info_get_vartypes(CallerProcInfo, VarTypes),
         module_info_pred_proc_info(ModuleInfo, PredId, ProcId, _, ProcInfo),
         ArgVars = list.map(foreign_arg_var, Args),
@@ -460,13 +462,13 @@
     % Might need to add more live variables with typeinfo liveness
     % calculation.
 
-    maybe_add_typeinfo_liveness(AllocData ^ proc_info,
-        AllocData ^ typeinfo_liveness, OutVars, ForwardVars0, ForwardVars),
+    maybe_add_typeinfo_liveness(AllocData ^ ad_proc_info,
+        AllocData ^ ad_typeinfo_liveness, OutVars, ForwardVars0, ForwardVars),
 
     Detism = goal_info_get_determinism(GoalInfo0),
     (
         Detism = detism_erroneous,
-        AllocData ^ opt_no_return_calls = yes
+        AllocData ^ ad_opt_no_return_calls = yes
     ->
         NeedAcrossCall = need_across_call(set.init, set.init, set.init)
     ;
Index: compiler/liveness.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/liveness.m,v
retrieving revision 1.161
diff -u -b -r1.161 liveness.m
--- compiler/liveness.m	21 Jan 2008 00:32:49 -0000	1.161
+++ compiler/liveness.m	21 Jan 2008 00:33:44 -0000
@@ -1620,7 +1620,7 @@
     ( set.equal(LivenessFirst, LivenessRest) ->
         true
     ;
-        VarSet = LiveInfo ^ varset,
+        VarSet = LiveInfo ^ li_varset,
         set.to_sorted_list(LivenessFirst, FirstVarsList),
         set.to_sorted_list(LivenessRest, RestVarsList),
         list.map(varset.lookup_name(VarSet), FirstVarsList, FirstVarNames),
@@ -1695,8 +1695,8 @@
     % to these.
     proc_info_get_vartypes(ProcInfo, VarTypes),
     proc_info_get_rtti_varmaps(ProcInfo, RttiVarMaps),
-    maybe_complete_with_typeinfo_vars(Deadness0, LiveInfo ^ typeinfo_liveness,
-        VarTypes, RttiVarMaps, Deadness).
+    maybe_complete_with_typeinfo_vars(Deadness0,
+        LiveInfo ^ li_typeinfo_liveness, VarTypes, RttiVarMaps, Deadness).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -1745,11 +1745,11 @@
 find_value_giving_occurrences([], _, _, !ValueVars).
 find_value_giving_occurrences([Var | Vars], LiveInfo, InstMapDelta,
         !ValueVars) :-
-    VarTypes = LiveInfo ^ vartypes,
+    VarTypes = LiveInfo ^ li_vartypes,
     map.lookup(VarTypes, Var, Type),
     (
         instmap_delta_search_var(InstMapDelta, Var, Inst),
-        ModuleInfo = LiveInfo ^ module_info,
+        ModuleInfo = LiveInfo ^ li_module_info,
         mode_to_arg_mode(ModuleInfo, (free -> Inst), Type, top_out)
     ->
         svset.insert(Var, !ValueVars)
@@ -1777,19 +1777,19 @@
     set(prog_var)::in, set(prog_var)::out) is det.
 
 liveness.maybe_complete_with_typeinfos(LiveInfo, Vars0, Vars) :-
-    maybe_complete_with_typeinfo_vars(Vars0, LiveInfo ^ typeinfo_liveness,
-        LiveInfo ^ vartypes, LiveInfo ^ rtti_varmaps, Vars).
+    maybe_complete_with_typeinfo_vars(Vars0, LiveInfo ^ li_typeinfo_liveness,
+        LiveInfo ^ li_vartypes, LiveInfo ^ li_rtti_varmaps, Vars).
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
 
 :- type live_info
     --->    live_info(
-                module_info         ::  module_info,
-                typeinfo_liveness   ::  bool,
-                vartypes            ::  vartypes,
-                rtti_varmaps        ::  rtti_varmaps,
-                varset              ::  prog_varset
+                li_module_info          :: module_info,
+                li_typeinfo_liveness    :: bool,
+                li_vartypes             :: vartypes,
+                li_rtti_varmaps         :: rtti_varmaps,
+                li_varset               :: prog_varset
             ).
 
 :- pred live_info_init(module_info::in, bool::in, vartypes::in,
Index: compiler/ml_code_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ml_code_util.m,v
retrieving revision 1.132
diff -u -b -r1.132 ml_code_util.m
--- compiler/ml_code_util.m	21 Jan 2008 00:32:51 -0000	1.132
+++ compiler/ml_code_util.m	21 Jan 2008 00:33:44 -0000
@@ -1020,7 +1020,7 @@
         HeadModes, PredOrFunc, CodeModel).
 
 ml_gen_proc_params(PredId, ProcId, FuncParams, !Info) :-
-    ModuleInfo = !.Info ^ module_info,
+    ModuleInfo = !.Info ^ mgi_module_info,
     module_info_pred_proc_info(ModuleInfo, PredId, ProcId, PredInfo, ProcInfo),
     proc_info_get_varset(ProcInfo, VarSet),
     proc_info_get_headvars(ProcInfo, HeadVars),
@@ -1047,8 +1047,8 @@
     HeadVars = RttiProcId ^ proc_headvars,
     ArgTypes = RttiProcId ^ proc_arg_types,
     ArgModes = RttiProcId ^ proc_arg_modes,
-    PredOrFunc = RttiProcId^pred_or_func,
-    Detism = RttiProcId^proc_interface_detism,
+    PredOrFunc = RttiProcId ^ pred_or_func,
+    Detism = RttiProcId ^ proc_interface_detism,
     determinism_to_code_model(Detism, CodeModel),
     HeadVarNames = list.map(
         (func(Var - Name) = Result :-
@@ -1066,7 +1066,7 @@
 
 ml_gen_params(HeadVarNames, HeadTypes, HeadModes, PredOrFunc,
         CodeModel, FuncParams, !Info) :-
-    ModuleInfo = !.Info ^ module_info,
+    ModuleInfo = !.Info ^ mgi_module_info,
     modes_to_arg_modes(ModuleInfo, HeadModes, HeadTypes, ArgModes),
     ml_gen_params_base(ModuleInfo, HeadVarNames,
         HeadTypes, ArgModes, PredOrFunc, CodeModel, FuncParams,
@@ -2143,9 +2143,9 @@
     ml_gen_info::in, ml_gen_info::out) is det.
 
 ml_gen_make_type_info_var(Type, Context, TypeInfoVar, TypeInfoGoals, !Info) :-
-    ModuleInfo0 = !.Info ^ module_info,
-    PredId = !.Info ^ pred_id,
-    ProcId = !.Info ^ proc_id,
+    ModuleInfo0 = !.Info ^ mgi_module_info,
+    PredId = !.Info ^ mgi_pred_id,
+    ProcId = !.Info ^ mgi_proc_id,
     module_info_pred_proc_info(ModuleInfo0, PredId, ProcId,
         PredInfo0, ProcInfo0),
 
@@ -2161,27 +2161,25 @@
         ModuleInfo1, ModuleInfo),
     proc_info_get_varset(ProcInfo, VarSet),
     proc_info_get_vartypes(ProcInfo, VarTypes),
-    !:Info = !.Info ^ module_info := ModuleInfo,
-    !:Info = !.Info ^ varset := VarSet,
-    !:Info = !.Info ^ var_types := VarTypes.
+    !:Info = !.Info ^ mgi_module_info := ModuleInfo,
+    !:Info = !.Info ^ mgi_varset := VarSet,
+    !:Info = !.Info ^ mgi_var_types := VarTypes.
 
 %-----------------------------------------------------------------------------%
 
 :- type fixup_newobj_info
     --->    fixup_newobj_info(
-                module_name :: mlds_module_name,
-                            % the current module
+                % The current module.
+                fnoi_module_name    :: mlds_module_name,
 
-                context     :: mlds_context,
-                            % the current context
+                % The current context.
+                fnoi_context        :: mlds_context,
 
-                locals      :: mlds_defns,
-                            % the local variable declarations
-                            % accumulated so far
-
-                next_id     :: counter
-                            % a counter used to allocate
-                            % variable names
+                % The local variable declarations accumulated so far.
+                fnoi_locals         :: mlds_defns,
+
+                % A counter used to allocate variable names.
+                fnoi_next_id        :: counter
             ).
 
     % Replace all heap allocation (new_object instructions) with stack
@@ -2197,14 +2195,14 @@
     Info0 = fixup_newobj_info(ModuleName, Context, [], counter.init(0)),
     fixup_newobj_in_stmt(Stmt0, Stmt, Info0, Info),
     Statement = statement(Stmt, Context),
-    Defns = Info ^ locals.
+    Defns = Info ^ fnoi_locals.
 
 :- pred fixup_newobj_in_statement(statement::in, statement::out,
     fixup_newobj_info::in, fixup_newobj_info::out) is det.
 
 fixup_newobj_in_statement(Statement0, Statement, !Info) :-
     Statement0 = statement(Stmt0, Context),
-    !:Info = !.Info ^ context := Context,
+    !:Info = !.Info ^ fnoi_context := Context,
     fixup_newobj_in_stmt(Stmt0, Stmt, !Info),
     Statement = statement(Stmt, Context).
 
@@ -2303,7 +2301,7 @@
         % length of the array is. We initialize it with null pointers and then
         % later generate assignment statements to fill in the values properly
         % (see below).
-        counter.allocate(Id, !.Fixup ^ next_id, NextId),
+        counter.allocate(Id, !.Fixup ^ fnoi_next_id, NextId),
         VarName = mlds_var_name("new_obj", yes(Id)),
         VarType = mlds_array_type(mlds_generic_type),
         NullPointers = list.duplicate(list.length(ArgRvals),
@@ -2312,11 +2310,11 @@
         % This is used for the type_infos allocated during tracing,
         % and we don't need to trace them.
         GCStatement = gc_no_stmt,
-        Context = !.Fixup ^ context,
+        Context = !.Fixup ^ fnoi_context,
         VarDecl = ml_gen_mlds_var_decl_init(var(VarName), VarType, Initializer,
             GCStatement, Context),
-        !:Fixup = !.Fixup ^ next_id := NextId,
-        !:Fixup= !.Fixup ^ locals := !.Fixup ^ locals ++ [VarDecl],
+        !:Fixup = !.Fixup ^ fnoi_next_id := NextId,
+        !:Fixup= !.Fixup ^ fnoi_locals := !.Fixup ^ fnoi_locals ++ [VarDecl],
 
         % Generate code to initialize the variable.
         %
@@ -2326,7 +2324,7 @@
         % atomic_statement occurs, rather than at the local variable
         % declaration.
 
-        VarLval = var(qual(!.Fixup ^ module_name, module_qual, VarName),
+        VarLval = var(qual(!.Fixup ^ fnoi_module_name, module_qual, VarName),
             VarType),
         PtrRval = unop(cast(PointerType), mem_addr(VarLval)),
         list.map_foldl(init_field_n(PointerType, PtrRval, Context),
@@ -2381,38 +2379,39 @@
                 % fresh variables for type_info variables needed
                 % for calls to private_builtin.gc_trace).
 
-                module_info         :: module_info,
-                pred_id             :: pred_id,
-                proc_id             :: proc_id,
-                varset              :: prog_varset,
-                var_types           :: vartypes,
-                byref_output_vars   :: list(prog_var),
-                                    % output arguments that are passed by
-                                    % reference
-                value_output_vars   :: list(prog_var),
-                                    % output arguments that are returned
-                                    % as values
+                mgi_module_info         :: module_info,
+                mgi_pred_id             :: pred_id,
+                mgi_proc_id             :: proc_id,
+                mgi_varset              :: prog_varset,
+                mgi_var_types           :: vartypes,
+
+                % Output arguments that are passed by reference.
+                mgi_byref_output_vars   :: list(prog_var),
+
+                % Output arguments that are returned as values.
+                mgi_value_output_vars   :: list(prog_var),
 
                 % These fields get updated as we traverse each procedure.
 
-                func_label          :: counter,
-                commit_label        :: counter,
-                label               :: counter,
-                cond_var            :: counter,
-                conv_var            :: counter,
-                const_num           :: counter,
-                const_var_name_map  :: map(prog_var, mlds_var_name),
-                success_cont_stack  :: stack(success_cont),
-                                    % A partial mapping from vars to lvals,
-                                    % used to override the normal lval
-                                    % that we use for a variable.
-                var_lvals           :: map(prog_var, mlds_lval),
-                                    % Definitions of functions or global
-                                    % constants which should be inserted
-                                    % before the definition of the function
-                                    % for the current procedure.
-                extra_defns         :: mlds_defns,
-                env_var_names       :: set(string)
+                mgi_func_label          :: counter,
+                mgi_commit_label        :: counter,
+                mgi_label               :: counter,
+                mgi_cond_var            :: counter,
+                mgi_conv_var            :: counter,
+                mgi_const_num           :: counter,
+                mgi_const_var_name_map  :: map(prog_var, mlds_var_name),
+
+                % A partial mapping from vars to lvals, used to override
+                % the normal lval that we use for a variable.
+                mgi_success_cont_stack  :: stack(success_cont),
+
+                % Definitions of functions or global constants which should be
+                % inserted before the definition of the function for the
+                % current procedure.
+                mgi_var_lvals           :: map(prog_var, mlds_lval),
+
+                mgi_extra_defns         :: mlds_defns,
+                mgi_env_var_names       :: set(string)
             ).
 
 ml_gen_info_init(ModuleInfo, PredId, ProcId) = Info :-
@@ -2426,12 +2425,10 @@
         VarTypes),
     ValueOutputVars = [],
 
-    % XXX This needs to start at 1 rather than 0 otherwise the
-    % transformation for adding the shadow stack for accurate garbage
-    % collection does not work properly and we will end up generating
-    % two C functions with the same name.
-    %
-    % ( See ml_elim_nested.gen_gc_trace_func/8 for details).
+    % XXX This needs to start at 1 rather than 0 otherwise the transformation
+    % for adding the shadow stack for accurate garbage collection does not work
+    % properly and we will end up generating two C functions with the same
+    % name (see ml_elim_nested.gen_gc_trace_func/8 for details).
     %
     counter.init(1, FuncLabelCounter),
     counter.init(0, CommitLabelCounter),
@@ -2466,22 +2463,22 @@
         EnvVarNames
     ).
 
-ml_gen_info_get_module_info(Info, Info ^ module_info).
+ml_gen_info_get_module_info(Info, Info ^ mgi_module_info).
 
 ml_gen_info_get_module_name(Info, ModuleName) :-
     ml_gen_info_get_module_info(Info, ModuleInfo),
     module_info_get_name(ModuleInfo, ModuleName).
 
-ml_gen_info_get_pred_id(Info, Info ^ pred_id).
-ml_gen_info_get_proc_id(Info, Info ^ proc_id).
-ml_gen_info_get_varset(Info, Info ^ varset).
-ml_gen_info_get_var_types(Info, Info ^ var_types).
-ml_gen_info_get_byref_output_vars(Info, Info ^ byref_output_vars).
-ml_gen_info_get_value_output_vars(Info, Info ^ value_output_vars).
+ml_gen_info_get_pred_id(Info, Info ^ mgi_pred_id).
+ml_gen_info_get_proc_id(Info, Info ^ mgi_proc_id).
+ml_gen_info_get_varset(Info, Info ^ mgi_varset).
+ml_gen_info_get_var_types(Info, Info ^ mgi_var_types).
+ml_gen_info_get_byref_output_vars(Info, Info ^ mgi_byref_output_vars).
+ml_gen_info_get_value_output_vars(Info, Info ^ mgi_value_output_vars).
 ml_gen_info_set_byref_output_vars(OutputVars, Info,
-        Info ^ byref_output_vars := OutputVars).
+        Info ^ mgi_byref_output_vars := OutputVars).
 ml_gen_info_set_value_output_vars(OutputVars, Info,
-        Info ^ value_output_vars := OutputVars).
+        Info ^ mgi_value_output_vars := OutputVars).
 
 ml_gen_info_use_gcc_nested_functions(Info, UseNestedFuncs) :-
     ml_gen_info_get_globals(Info, Globals),
@@ -2498,85 +2495,85 @@
     module_info_get_globals(ModuleInfo, Globals).
 
 ml_gen_info_new_label(Label, !Info) :-
-    Counter0 = !.Info ^ label,
+    Counter0 = !.Info ^ mgi_label,
     counter.allocate(Label, Counter0, Counter),
-    !:Info = !.Info ^ label := Counter.
+    !Info ^ mgi_label := Counter.
 
 ml_gen_info_new_func_label(Label, !Info) :-
-    Counter0 = !.Info ^ func_label,
+    Counter0 = !.Info ^ mgi_func_label,
     counter.allocate(Label, Counter0, Counter),
-    !:Info = !.Info ^ func_label := Counter.
+    !Info ^ mgi_func_label := Counter.
 
 ml_gen_info_bump_counters(!Info) :-
-    FuncLabelCounter0 = !.Info ^ func_label,
-    ConstNumCounter0 = !.Info ^ const_num,
+    FuncLabelCounter0 = !.Info ^ mgi_func_label,
+    ConstNumCounter0 = !.Info ^ mgi_const_num,
     counter.allocate(FuncLabel, FuncLabelCounter0, _),
     counter.allocate(ConstNum, ConstNumCounter0, _),
     FuncLabelCounter = counter.init(FuncLabel + 10000),
     ConstNumCounter = counter.init(ConstNum + 10000),
-    !:Info = !.Info ^ func_label := FuncLabelCounter,
-    !:Info = !.Info ^ const_num := ConstNumCounter.
+    !Info ^ mgi_func_label := FuncLabelCounter,
+    !Info ^ mgi_const_num := ConstNumCounter.
 
 ml_gen_info_new_commit_label(CommitLabel, !Info) :-
-    Counter0 = !.Info ^ commit_label,
+    Counter0 = !.Info ^ mgi_commit_label,
     counter.allocate(CommitLabel, Counter0, Counter),
-    !:Info = !.Info ^ commit_label := Counter.
+    !Info ^ mgi_commit_label := Counter.
 
 ml_gen_info_new_cond_var(CondVar, !Info) :-
-    Counter0 = !.Info ^ cond_var,
+    Counter0 = !.Info ^ mgi_cond_var,
     counter.allocate(CondVar, Counter0, Counter),
-    !:Info = !.Info ^ cond_var := Counter.
+    !Info ^ mgi_cond_var := Counter.
 
 ml_gen_info_new_conv_var(ConvVar, !Info) :-
-    Counter0 = !.Info ^ conv_var,
+    Counter0 = !.Info ^ mgi_conv_var,
     counter.allocate(ConvVar, Counter0, Counter),
-    !:Info = !.Info ^ conv_var := Counter.
+    !Info ^ mgi_conv_var := Counter.
 
 ml_gen_info_new_const(ConstVar, !Info) :-
-    Counter0 = !.Info ^ const_num,
+    Counter0 = !.Info ^ mgi_const_num,
     counter.allocate(ConstVar, Counter0, Counter),
-    !:Info = !.Info ^ const_num := Counter.
+    !Info ^ mgi_const_num := Counter.
 
 ml_gen_info_set_const_var_name(Var, Name, !Info) :-
-    !:Info = !.Info ^ const_var_name_map :=
-        map.set(!.Info ^ const_var_name_map, Var, Name).
+    !Info ^ mgi_const_var_name_map :=
+        map.set(!.Info ^ mgi_const_var_name_map, Var, Name).
 
 ml_gen_info_lookup_const_var_name(Info, Var, Name) :-
-    Name = map.lookup(Info ^ const_var_name_map, Var).
+    Name = map.lookup(Info ^ mgi_const_var_name_map, Var).
 
 ml_gen_info_search_const_var_name(Info, Var, Name) :-
-    Name = map.search(Info ^ const_var_name_map, Var).
+    Name = map.search(Info ^ mgi_const_var_name_map, Var).
 
 ml_gen_info_push_success_cont(SuccCont, !Info) :-
-    !:Info = !.Info ^ success_cont_stack :=
-        stack.push(!.Info ^ success_cont_stack, SuccCont).
+    !Info ^ mgi_success_cont_stack :=
+        stack.push(!.Info ^ mgi_success_cont_stack, SuccCont).
 
 ml_gen_info_pop_success_cont(!Info) :-
-    Stack0 = !.Info ^ success_cont_stack,
+    Stack0 = !.Info ^ mgi_success_cont_stack,
     stack.pop_det(Stack0, _SuccCont, Stack),
-    !:Info = !.Info ^ success_cont_stack := Stack.
+    !Info ^ mgi_success_cont_stack := Stack.
 
 ml_gen_info_current_success_cont(Info, SuccCont) :-
-    stack.top_det(Info ^ success_cont_stack, SuccCont).
+    stack.top_det(Info ^ mgi_success_cont_stack, SuccCont).
 
 ml_gen_info_set_var_lval(Var, Lval, !Info) :-
-    !:Info = !.Info ^ var_lvals := map.set(!.Info ^ var_lvals, Var, Lval).
+    !Info ^ mgi_var_lvals := map.set(!.Info ^ mgi_var_lvals, Var, Lval).
 
-ml_gen_info_get_var_lvals(Info, Info ^ var_lvals).
+ml_gen_info_get_var_lvals(Info, Info ^ mgi_var_lvals).
 ml_gen_info_set_var_lvals(VarLvals, !Info) :-
-    !:Info = !.Info ^ var_lvals := VarLvals.
+    !Info ^ mgi_var_lvals := VarLvals.
 
 ml_gen_info_add_extra_defn(ExtraDefn, !Info) :-
-    !:Info = !.Info ^ extra_defns := [ExtraDefn | !.Info ^ extra_defns].
+    !Info ^ mgi_extra_defns := [ExtraDefn | !.Info ^ mgi_extra_defns].
 
-ml_gen_info_get_extra_defns(Info, Info ^ extra_defns).
+ml_gen_info_get_extra_defns(Info, Info ^ mgi_extra_defns).
 
 ml_gen_info_add_env_var_name(Name, !Info) :-
-    EnvVarNames0 = !.Info ^ env_var_names,
+    EnvVarNames0 = !.Info ^ mgi_env_var_names,
     set.insert(EnvVarNames0, Name, EnvVarNames),
-    !:Info = !.Info ^ env_var_names := EnvVarNames.
+    !Info ^ mgi_env_var_names := EnvVarNames.
 
-ml_gen_info_get_env_vars(Info, Info ^ env_var_names).
+ml_gen_info_get_env_vars(Info, Info ^ mgi_env_var_names).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/mode_constraints.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mode_constraints.m,v
retrieving revision 1.45
diff -u -b -r1.45 mode_constraints.m
--- compiler/mode_constraints.m	22 Jan 2008 15:06:12 -0000	1.45
+++ compiler/mode_constraints.m	24 Jan 2008 01:18:49 -0000
@@ -296,7 +296,7 @@
     --->    number_robdd_info(
                 n_mc_info       :: mode_constraint_info,
                 n_module_info   :: module_info,
-                vartypes        :: vartypes
+                n_vartypes      :: vartypes
             ).
 
 :- instance has_mc_info(number_robdd_info) where [
@@ -493,7 +493,7 @@
     !.RHS = rhs_lambda_goal(_, _, _, _, LambdaNonLocals, LambdaVars, _, _,
         LambdaGoal0),
     Vars = LambdaNonLocals,
-    VarTypes = !.NRInfo ^ vartypes,
+    VarTypes = !.NRInfo ^ n_vartypes,
     ModuleInfo = !.NRInfo ^ module_info,
     fill_goal_path_slots_in_goal(LambdaGoal0, VarTypes, ModuleInfo,
         LambdaGoal1),
Index: compiler/polymorphism.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/polymorphism.m,v
retrieving revision 1.325
diff -u -b -r1.325 polymorphism.m
--- compiler/polymorphism.m	22 Jan 2008 15:06:14 -0000	1.325
+++ compiler/polymorphism.m	24 Jan 2008 01:18:50 -0000
@@ -1963,7 +1963,7 @@
     (
         % Optimize common case.
         ExistQVars = [],
-        rtti_varmaps_no_tvars(!.Info ^ rtti_varmaps)
+        rtti_varmaps_no_tvars(!.Info ^ poly_rtti_varmaps)
     ->
         Goal = Goal0
     ;
@@ -2069,7 +2069,8 @@
 make_typeclass_info_var(Constraint, Seen, ExistQVars,
         Context, !ExtraGoals, !Info, MaybeVar) :-
     (
-        rtti_search_typeclass_info_var(!.Info ^ rtti_varmaps, Constraint, Var)
+        rtti_search_typeclass_info_var(!.Info ^ poly_rtti_varmaps, Constraint,
+            Var)
     ->
         % We already have a typeclass_info for this constraint, either from
         % a parameter to the pred or from an existentially quantified goal
@@ -2079,7 +2080,7 @@
         % We don't have the typeclass_info, we must either have a proof that
         % tells us how to make it, or it will be produced by an existentially
         % typed goal that we will process later on.
-        map.search(!.Info ^ proof_map, Constraint, Proof)
+        map.search(!.Info ^ poly_proof_map, Constraint, Proof)
     ->
         make_typeclass_info_from_proof(Constraint, Seen, Proof, ExistQVars,
             Context, MaybeVar, !ExtraGoals, !Info)
@@ -2127,9 +2128,9 @@
 make_typeclass_info_from_instance(Constraint, Seen, ClassId, InstanceNum,
         ExistQVars, Context, MaybeVar, !ExtraGoals, !Info) :-
     Constraint = constraint(_ClassName, ConstrainedTypes),
-    TypeVarSet = !.Info ^ typevarset,
-    Proofs0 = !.Info ^ proof_map,
-    ModuleInfo = !.Info ^ module_info,
+    TypeVarSet = !.Info ^ poly_typevarset,
+    Proofs0 = !.Info ^ poly_proof_map,
+    ModuleInfo = !.Info ^ poly_module_info,
 
     module_info_get_instance_table(ModuleInfo, InstanceTable),
     map.lookup(InstanceTable, ClassId, InstanceList),
@@ -2532,7 +2533,7 @@
     % If we have already allocated a location for this type_info, then all
     % we need to do is to extract the type_info variable from its location.
     (
-        rtti_search_type_info_locn(!.Info ^ rtti_varmaps, TypeVar,
+        rtti_search_type_info_locn(!.Info ^ poly_rtti_varmaps, TypeVar,
             TypeInfoLocnPrime)
     ->
         TypeInfoLocn = TypeInfoLocnPrime
@@ -2546,8 +2547,8 @@
         % will be stored in the typeclass_info variable produced by the
         % predicate, not in a type_info variable. maybe_extract_type_info
         % will fix this up when the typeclass_info is created.
-        %
-        get_tvar_kind(!.Info ^ tvar_kinds, TypeVar, Kind),
+
+        get_tvar_kind(!.Info ^ poly_tvar_kinds, TypeVar, Kind),
         Type = type_variable(TypeVar, Kind),
         new_type_info_var(Type, type_info, Var, !Info),
         TypeInfoLocn = type_info(Var),
@@ -2804,7 +2805,7 @@
 
 make_head_vars([], _, [], !Info).
 make_head_vars([TypeVar | TypeVars], TypeVarSet, TypeInfoVars, !Info) :-
-    get_tvar_kind(!.Info ^ tvar_kinds, TypeVar, Kind),
+    get_tvar_kind(!.Info ^ poly_tvar_kinds, TypeVar, Kind),
     Type = type_variable(TypeVar, Kind),
     new_type_info_var(Type, type_info, Var, !Info),
     ( varset.search_name(TypeVarSet, TypeVar, TypeVarName) ->
@@ -3264,37 +3265,31 @@
 :- type poly_info
     --->    poly_info(
                 % The first two fields are from the proc_info.
-                varset              :: prog_varset,
-                vartypes            :: vartypes,
+                poly_varset             :: prog_varset,
+                poly_vartypes           :: vartypes,
 
                 % The next two fields from the pred_info.
-                typevarset          :: tvarset,
-                tvar_kinds          :: tvar_kind_map,
+                poly_typevarset         :: tvarset,
+                poly_tvar_kinds         :: tvar_kind_map,
+
+                % Gives information about the locations of type_infos
+                % and typeclass_infos.
+                poly_rtti_varmaps       :: rtti_varmaps,
+
+                % Specifies why each constraint that was eliminated from the
+                % pred was able to be eliminated (this allows us to efficiently
+                % construct the dictionary).
+                % Note that the rtti_varmaps is separate from the
+                % constraint_proof_map, since the second is the information
+                % calculated by typecheck.m, while the first is the information
+                % calculated here in polymorphism.m.
+                poly_proof_map          :: constraint_proof_map,
 
-                rtti_varmaps        :: rtti_varmaps,
-                                    % Gives information about the locations
-                                    % of type_infos and typeclass_infos.
-
-                proof_map           :: constraint_proof_map,
-                                    % Specifies why each constraint
-                                    % that was eliminated from the
-                                    % pred was able to be eliminated
-                                    % (this allows us to efficiently
-                                    % construct the dictionary)
-
-                                    % Note that the two maps above
-                                    % are separate since the second
-                                    % is the information calculated
-                                    % by typecheck.m, while the
-                                    % first is the information
-                                    % calculated here in polymorphism.m
-
-                constraint_map      :: constraint_map,
-                                    % Specifies the constraints at each
-                                    % location in the goal.
+                % Specifies the constraints at each location in the goal.
+                poly_constraint_map     :: constraint_map,
 
-                pred_info           :: pred_info,
-                module_info         :: module_info
+                poly_pred_info          :: pred_info,
+                poly_module_info        :: module_info
             ).
 
 %---------------------------------------------------------------------------%
@@ -3354,15 +3349,15 @@
 :- pred poly_info_get_pred_info(poly_info::in, pred_info::out) is det.
 :- pred poly_info_get_module_info(poly_info::in, module_info::out) is det.
 
-poly_info_get_varset(PolyInfo, PolyInfo ^ varset).
-poly_info_get_var_types(PolyInfo, PolyInfo ^ vartypes).
-poly_info_get_typevarset(PolyInfo, PolyInfo ^ typevarset).
-poly_info_get_tvar_kinds(PolyInfo, PolyInfo ^ tvar_kinds).
-poly_info_get_rtti_varmaps(PolyInfo, PolyInfo ^ rtti_varmaps).
-poly_info_get_proofs(PolyInfo, PolyInfo ^ proof_map).
-poly_info_get_constraint_map(PolyInfo, PolyInfo ^ constraint_map).
-poly_info_get_pred_info(PolyInfo, PolyInfo ^ pred_info).
-poly_info_get_module_info(PolyInfo, PolyInfo ^ module_info).
+poly_info_get_varset(PolyInfo, PolyInfo ^ poly_varset).
+poly_info_get_var_types(PolyInfo, PolyInfo ^ poly_vartypes).
+poly_info_get_typevarset(PolyInfo, PolyInfo ^ poly_typevarset).
+poly_info_get_tvar_kinds(PolyInfo, PolyInfo ^ poly_tvar_kinds).
+poly_info_get_rtti_varmaps(PolyInfo, PolyInfo ^ poly_rtti_varmaps).
+poly_info_get_proofs(PolyInfo, PolyInfo ^ poly_proof_map).
+poly_info_get_constraint_map(PolyInfo, PolyInfo ^ poly_constraint_map).
+poly_info_get_pred_info(PolyInfo, PolyInfo ^ poly_pred_info).
+poly_info_get_module_info(PolyInfo, PolyInfo ^ poly_module_info).
 
 :- pred poly_info_set_varset(prog_varset::in,
     poly_info::in, poly_info::out) is det.
@@ -3381,16 +3376,23 @@
 :- pred poly_info_set_module_info(module_info::in,
     poly_info::in, poly_info::out) is det.
 
-poly_info_set_varset(VarSet, PI, PI ^ varset := VarSet).
-poly_info_set_varset_and_types(VarSet, VarTypes, PI,
-    (PI ^ varset := VarSet) ^ vartypes := VarTypes).
-poly_info_set_typevarset(TVarSet, PI, PI ^ typevarset := TVarSet).
-poly_info_set_tvar_kinds(TVarKinds, PI, PI ^ tvar_kinds := TVarKinds).
-poly_info_set_rtti_varmaps(RttiVarMaps, PI, PI ^ rtti_varmaps := RttiVarMaps).
-poly_info_set_proofs(Proofs, PI, PI ^ proof_map := Proofs).
-poly_info_set_constraint_map(ConstraintMap, PI,
-    PI ^ constraint_map := ConstraintMap).
-poly_info_set_module_info(ModuleInfo, PI, PI ^ module_info := ModuleInfo).
+poly_info_set_varset(VarSet, !PI) :-
+    !PI ^ poly_varset := VarSet.
+poly_info_set_varset_and_types(VarSet, VarTypes, !PI) :-
+    !PI ^ poly_varset := VarSet,
+    !PI ^ poly_vartypes := VarTypes.
+poly_info_set_typevarset(TVarSet, !PI) :-
+    !PI ^ poly_typevarset := TVarSet.
+poly_info_set_tvar_kinds(TVarKinds, !PI) :-
+    !PI ^ poly_tvar_kinds := TVarKinds.
+poly_info_set_rtti_varmaps(RttiVarMaps, !PI) :-
+    !PI ^ poly_rtti_varmaps := RttiVarMaps.
+poly_info_set_proofs(Proofs, !PI) :-
+    !PI ^ poly_proof_map := Proofs.
+poly_info_set_constraint_map(ConstraintMap, !PI) :-
+    !PI ^ poly_constraint_map := ConstraintMap.
+poly_info_set_module_info(ModuleInfo, !PI) :-
+    !PI ^ poly_module_info := ModuleInfo.
 
 %---------------------------------------------------------------------------%
 
Index: compiler/prog_rep.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/prog_rep.m,v
retrieving revision 1.57
diff -u -b -r1.57 prog_rep.m
--- compiler/prog_rep.m	30 Dec 2007 08:23:54 -0000	1.57
+++ compiler/prog_rep.m	12 Jan 2008 20:28:43 -0000
@@ -73,12 +73,12 @@
 %---------------------------------------------------------------------------%
 
 :- type prog_rep_info
-    --->    info(
-                filename    :: string,
-                vartypes    :: vartypes,
-                var_num_map :: var_num_map,
-                var_num_rep :: var_num_rep,
-                module_info :: module_info
+    --->    prog_rep_info(
+                pri_filename    :: string,
+                pri_vartypes    :: vartypes,
+                pri_var_num_map :: var_num_map,
+                pri_var_num_rep :: var_num_rep,
+                pri_module_info :: module_info
             ).
 
 represent_proc_as_bytecodes(HeadVars, Goal, InstMap0, VarTypes, VarNumMap,
@@ -92,7 +92,7 @@
     ;
         VarNumRep = short
     ),
-    Info = info(FileName, VarTypes, VarNumMap, VarNumRep, ModuleInfo),
+    Info = prog_rep_info(FileName, VarTypes, VarNumMap, VarNumRep, ModuleInfo),
     var_num_rep_byte(VarNumRep, VarNumRepByte),
 
     string_to_byte_list(FileName, FileNameBytes, !StackInfo),
@@ -266,7 +266,7 @@
         GoalExpr = plain_call(PredId, _, Args, Builtin, _, _),
         atomic_goal_info_to_byte_list(GoalInfo, InstMap0, Info,
             AtomicBytes, _BoundVars, !StackInfo),
-        module_info_pred_info(Info ^ module_info, PredId, PredInfo),
+        module_info_pred_info(Info ^ pri_module_info, PredId, PredInfo),
         ModuleSymName = pred_info_module(PredInfo),
         ModuleName = sym_name_to_string(ModuleSymName),
         PredName = pred_info_name(PredInfo),
@@ -305,12 +305,12 @@
 :- pred lhs_final_is_ground(prog_rep_info::in, uni_mode::in) is semidet.
 
 lhs_final_is_ground(Info, (_ - _) -> (LHSFinalInst - _)) :-
-    inst_is_ground(Info ^ module_info, LHSFinalInst).
+    inst_is_ground(Info ^ pri_module_info, LHSFinalInst).
 
 :- pred rhs_is_input(prog_rep_info::in, uni_mode::in) is semidet.
 
 rhs_is_input(Info, (_ - RHSInitialInst) -> (_ - RHSFinalInst)) :-
-    mode_is_input(Info ^ module_info, RHSInitialInst -> RHSFinalInst).
+    mode_is_input(Info ^ pri_module_info, RHSInitialInst -> RHSFinalInst).
 
 :- pred filter_input_args(prog_rep_info::in, list(uni_mode)::in,
     list(prog_var)::in, list(maybe(prog_var))::out) is det.
@@ -340,7 +340,7 @@
     Detism = goal_info_get_determinism(GoalInfo),
     Context = goal_info_get_context(GoalInfo),
     term.context_file(Context, FileName0),
-    ( FileName0 = Info ^ filename ->
+    ( FileName0 = Info ^ pri_filename ->
         FileName = ""
     ;
         FileName = FileName0
@@ -348,8 +348,8 @@
     term.context_line(Context, LineNo),
     InstMapDelta = goal_info_get_instmap_delta(GoalInfo),
     instmap.apply_instmap_delta(InstMap0, InstMapDelta, InstMap),
-    instmap_changed_vars(InstMap0, InstMap, Info ^ vartypes,
-        Info ^ module_info, ChangedVars),
+    instmap_changed_vars(InstMap0, InstMap, Info ^ pri_vartypes,
+        Info ^ pri_module_info, ChangedVars),
     set.to_sorted_list(ChangedVars, BoundVars),
     string_to_byte_list(FileName, FileNameBytes, !StackInfo),
     Bytes = [represent_determinism(Detism)] ++
@@ -479,12 +479,12 @@
 :- func var_to_byte_list(prog_rep_info, prog_var) = list(int).
 
 var_to_byte_list(Info, Var) = Bytes :-
-    map.lookup(Info ^ var_num_map, Var, VarNum - _),
+    map.lookup(Info ^ pri_var_num_map, Var, VarNum - _),
     (
-        Info ^ var_num_rep = byte,
+        Info ^ pri_var_num_rep = byte,
         Bytes = [VarNum]
     ;
-        Info ^ var_num_rep = short,
+        Info ^ pri_var_num_rep = short,
         short_to_byte_list(VarNum, Bytes)
     ).
 
Index: compiler/qual_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/qual_info.m,v
retrieving revision 1.23
diff -u -b -r1.23 qual_info.m
--- compiler/qual_info.m	22 Jan 2008 15:06:16 -0000	1.23
+++ compiler/qual_info.m	24 Jan 2008 01:18:50 -0000
@@ -24,8 +24,8 @@
 :- import_module parse_tree.prog_data.
 :- import_module recompilation.
 
-:- import_module bool.
 :- import_module list.
+:- import_module bool.
 
 %-----------------------------------------------------------------------------%
 
@@ -111,31 +111,29 @@
     %
 :- type qual_info
     --->    qual_info(
-                eqv_map             :: eqv_map,
                                     % Used to expand equivalence types.
+                qual_eqv_map            :: eqv_map,
 
-                tvarset             :: tvarset,
                                     % All type variables for predicate.
+                qual_tvarset            :: tvarset,
+
+                % Map from clause type variable to actual type variable
+                % in tvarset.
+                qual_tvar_renaming      :: tvar_renaming,
 
-                tvar_renaming       :: tvar_renaming,
-                                    % Map from clause type variable to
-                                    % actual type variable in tvarset.
-
-                tvar_name_map       :: tvar_name_map,
-                                    % Type variables in tvarset occurring
-                                    % in the predicate's argument types
-                                    % indexed by name.
+                % Type variables in tvarset occurring in the predicate's
+                % argument types indexed by name.
+                qual_tvar_name_map      :: tvar_name_map,
 
-                vartypes            :: vartypes,
+                qual_vartypes           :: vartypes,
 
-                mq_info             :: mq_info,
                                     % Module qualification info.
+                qual_mq_info            :: mq_info,
 
-                import_status       :: import_status,
+                qual_import_status      :: import_status,
 
-                found_syntax_error  :: bool
-                                    % Was there a syntax error in an Aditi
-                                    % update.
+                % Was there a syntax error in a field update?
+                qual_found_syntax_error :: bool
             ).
 
 init_qual_info(MQInfo0, EqvMap, QualInfo) :-
@@ -156,31 +154,31 @@
     !:QualInfo = qual_info(EqvMap, TVarSet, Renaming, TVarNameMap,
         VarTypes, MQInfo, Status, no).
 
-qual_info_get_tvarset(Info, Info ^ tvarset).
-qual_info_get_var_types(Info, Info ^ vartypes).
-qual_info_get_mq_info(Info, Info ^ mq_info).
-qual_info_get_import_status(Info, Info ^ import_status).
-qual_info_get_found_syntax_error(Info, Info ^ found_syntax_error).
+qual_info_get_tvarset(Info, Info ^ qual_tvarset).
+qual_info_get_var_types(Info, Info ^ qual_vartypes).
+qual_info_get_mq_info(Info, Info ^ qual_mq_info).
+qual_info_get_import_status(Info, Info ^ qual_import_status).
+qual_info_get_found_syntax_error(Info, Info ^ qual_found_syntax_error).
 
-qual_info_set_mq_info(MQInfo, Info, Info ^ mq_info := MQInfo).
-qual_info_set_var_types(VarTypes, Info, Info ^ vartypes := VarTypes).
+qual_info_set_mq_info(MQInfo, Info, Info ^ qual_mq_info := MQInfo).
+qual_info_set_var_types(VarTypes, Info, Info ^ qual_vartypes := VarTypes).
 qual_info_set_found_syntax_error(FoundError, Info,
-    Info ^ found_syntax_error := FoundError).
+    Info ^ qual_found_syntax_error := FoundError).
 
 apply_to_recompilation_info(Pred, !QualInfo) :-
-    MQInfo0 = !.QualInfo ^ mq_info,
+    MQInfo0 = !.QualInfo ^ qual_mq_info,
     mq_info_get_recompilation_info(MQInfo0, MaybeRecompInfo0),
     (
         MaybeRecompInfo0 = yes(RecompInfo0),
         Pred(RecompInfo0, RecompInfo),
         mq_info_set_recompilation_info(yes(RecompInfo), MQInfo0, MQInfo),
-        !:QualInfo = !.QualInfo ^ mq_info := MQInfo
+        !:QualInfo = !.QualInfo ^ qual_mq_info := MQInfo
     ;
         MaybeRecompInfo0 = no
     ).
 
 set_module_recompilation_info(QualInfo, !ModuleInfo) :-
-    mq_info_get_recompilation_info(QualInfo ^ mq_info, RecompInfo),
+    mq_info_get_recompilation_info(QualInfo ^ qual_mq_info, RecompInfo),
     module_info_set_maybe_recompilation_info(RecompInfo, !ModuleInfo).
 
 %-----------------------------------------------------------------------------%
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.224
diff -u -b -r1.224 simplify.m
--- compiler/simplify.m	22 Jan 2008 15:06:16 -0000	1.224
+++ compiler/simplify.m	24 Jan 2008 01:18:50 -0000
@@ -428,11 +428,9 @@
     simplify_info_get_module_info(Info, !:ModuleInfo),
     simplify_info_get_error_specs(Info, !:ErrorSpecs),
     (
-        Info ^ format_calls = yes,
-        (
-            Simplifications ^ do_warn_known_bad_format = yes
-        ;
-            Simplifications ^ do_warn_unknown_format = yes
+        Info ^ simp_format_calls = yes,
+        ( Simplifications ^ do_warn_known_bad_format = yes
+        ; Simplifications ^ do_warn_unknown_format = yes
         )
     ->
         % We must use the original goal, Goal0, here. This is because excess
@@ -566,7 +564,7 @@
 
         simplify_info_get_module_info(!.Info, ModuleInfo0),
         recompute_instmap_delta(RecomputeAtomic, Goal2, Goal3, VarTypes1,
-            !.Info ^ inst_varset, InstMap0, ModuleInfo0, ModuleInfo1),
+            !.Info ^ simp_inst_varset, InstMap0, ModuleInfo0, ModuleInfo1),
         simplify_info_set_module_info(ModuleInfo1, !Info)
     ;
         Goal3 = Goal1
@@ -1487,7 +1485,7 @@
             (
                 CanSwitch = cond_can_switch_on(SwitchVar),
                 Context = goal_info_get_context(CondInfo),
-                VarSet = !.Info ^ varset,
+                VarSet = !.Info ^ simp_varset,
                 Pieces0 = [words("Warning: this if-then-else"),
                     words("could be replaced by a switch")],
                 ( varset.search_name(VarSet, SwitchVar, SwitchVarName) ->
@@ -2004,13 +2002,13 @@
 inequality_goal(TI, X, Y, Inequality, Invert, GoalInfo, GoalExpr, GoalInfo,
         !Info) :-
     % Construct the variable to hold the comparison result.
-    VarSet0 = !.Info ^ varset,
+    VarSet0 = !.Info ^ simp_varset,
     varset.new_var(VarSet0, R, VarSet),
-    !:Info = !.Info ^ varset := VarSet,
+    !:Info = !.Info ^ simp_varset := VarSet,
 
     % We have to add the type of R to the var_types.
     simplify_info_get_var_types(!.Info, VarTypes0),
-    VarTypes = VarTypes0 ^ elem(R) := comparison_result_type,
+    map.det_insert(VarTypes0, R, comparison_result_type, VarTypes),
     simplify_info_set_var_types(VarTypes, !Info),
 
     % Construct the call to compare/3.
@@ -3356,45 +3354,53 @@
 
 :- type simplify_info
     --->    simplify_info(
-                det_info                :: det_info,
-                error_specs             :: list(error_spec),
-                simplifications         :: simplifications,
-                common_info             :: common_info,
+                simp_det_info                :: det_info,
+                simp_error_specs             :: list(error_spec),
+                simp_simplifications         :: simplifications,
+
                                         % Info about common subexpressions.
-                instmap                 :: instmap,
-                varset                  :: prog_varset,
-                inst_varset             :: inst_varset,
-                requantify              :: bool,
-                                        % Does the goal need requantification.
-                recompute_atomic        :: bool,
-                                        % Do we need to recompute
-                                        % instmap_deltas for atomic goals
-                rerun_det               :: bool,
-                                        % Does determinism analysis need to
-                                        % be rerun.
-                cost_delta              :: int,
-                                        % Measure of the improvement in
-                                        % the goal from simplification.
-                lambdas                 :: int,
-                                        % Count of the number of lambdas
-                                        % which enclose the current goal.
-                rtti_varmaps            :: rtti_varmaps,
-                                        % Information about type_infos and
-                                        % typeclass_infos.
-                format_calls            :: bool,
-                                        % Do we have any calls to
-                                        % string.format, stream.format and
+                simp_common_info             :: common_info,
+
+                simp_instmap                 :: instmap,
+                simp_varset                  :: prog_varset,
+                simp_inst_varset             :: inst_varset,
+
+                % Does the goal need requantification?
+                simp_requantify              :: bool,       % ZZZ
+
+                % Do we need to recompute instmap_deltas for atomic goals?
+                simp_recompute_atomic        :: bool,
+
+                % Does determinism analysis need to be rerun?
+                simp_rerun_det               :: bool,
+
+                % Measure of the improvement in the goal from simplification.
+                simp_cost_delta              :: int,
+
+                % Count of the number of lambdas which enclose
+                % the current goal.
+                simp_lambdas                 :: int,
+
+                % Information about type_infos and typeclass_infos.
+                simp_rtti_varmaps            :: rtti_varmaps,
+
+                % Do we have any calls to string.format, stream.format and
                                         % io.format?
-                inside_dupl_for_switch  :: bool,
-                                        % Are we currently inside a goal
-                                        % that was duplicated for a switch?
-                has_parallel_conj       :: bool,
+                simp_format_calls            :: bool,
+
+                % Are we currently inside a goal that was duplicated
+                % for a switch?
+                simp_inside_dupl_for_switch  :: bool,
+
                                         % Have we seen a parallel conjunction?
-                found_contains_trace    :: bool,
-                                        % Have we seen a goal with a feature
-                                        % that says it contains a trace goal?
-                has_user_event          :: bool
+                simp_has_parallel_conj       :: bool,
+
+                % Have we seen a goal with a feature that says it contains
+                % a trace goal?
+                simp_found_contains_trace    :: bool,
+
                                         % Have we seen an event call?
+                simp_has_user_event          :: bool
             ).
 
 simplify_info_init(DetInfo, Simplifications, InstMap, ProcInfo, Info) :-
@@ -3411,15 +3417,15 @@
     simplify_info::in, simplify_info::out) is det.
 
 simplify_info_reinit(Simplifications, InstMap0, !Info) :-
-    !:Info = !.Info ^ simplifications := Simplifications,
-    !:Info = !.Info ^ common_info := common_info_init,
-    !:Info = !.Info ^ instmap := InstMap0,
-    !:Info = !.Info ^ requantify := no,
-    !:Info = !.Info ^ recompute_atomic := no,
-    !:Info = !.Info ^ rerun_det := no,
-    !:Info = !.Info ^ lambdas := 0,
-    !:Info = !.Info ^ has_parallel_conj := no,
-    !:Info = !.Info ^ has_user_event := no.
+    !:Info = !.Info ^ simp_simplifications := Simplifications,
+    !:Info = !.Info ^ simp_common_info := common_info_init,
+    !:Info = !.Info ^ simp_instmap := InstMap0,
+    !:Info = !.Info ^ simp_requantify := no,
+    !:Info = !.Info ^ simp_recompute_atomic := no,
+    !:Info = !.Info ^ simp_rerun_det := no,
+    !:Info = !.Info ^ simp_lambdas := 0,
+    !:Info = !.Info ^ simp_has_parallel_conj := no,
+    !:Info = !.Info ^ simp_has_user_event := no.
 
     % exported for common.m
 :- interface.
@@ -3480,28 +3486,28 @@
     is det.
 :- pred simplify_info_get_has_user_event(simplify_info::in, bool::out) is det.
 
-simplify_info_get_det_info(Info, Info ^ det_info).
-simplify_info_get_error_specs(Info, Info ^ error_specs).
-simplify_info_get_simplifications(Info, Info ^ simplifications).
-simplify_info_get_common_info(Info, Info ^ common_info).
-simplify_info_get_instmap(Info, Info ^ instmap).
-simplify_info_get_varset(Info, Info ^ varset).
+simplify_info_get_det_info(Info, Info ^ simp_det_info).
+simplify_info_get_error_specs(Info, Info ^ simp_error_specs).
+simplify_info_get_simplifications(Info, Info ^ simp_simplifications).
+simplify_info_get_common_info(Info, Info ^ simp_common_info).
+simplify_info_get_instmap(Info, Info ^ simp_instmap).
+simplify_info_get_varset(Info, Info ^ simp_varset).
 simplify_info_get_var_types(Info, VarTypes) :-
-    det_info_get_vartypes(Info ^ det_info, VarTypes).
+    det_info_get_vartypes(Info ^ simp_det_info, VarTypes).
 simplify_info_requantify(Info) :-
-    Info ^ requantify = yes.
+    Info ^ simp_requantify = yes.
 simplify_info_recompute_atomic(Info) :-
-    Info ^ recompute_atomic = yes.
+    Info ^ simp_recompute_atomic = yes.
 simplify_info_rerun_det(Info) :-
-    Info ^ rerun_det = yes.
-simplify_info_get_cost_delta(Info, Info ^ cost_delta).
-simplify_info_get_rtti_varmaps(Info, Info ^ rtti_varmaps).
-simplify_info_get_format_calls(Info, Info ^ format_calls).
+    Info ^ simp_rerun_det = yes.
+simplify_info_get_cost_delta(Info, Info ^ simp_cost_delta).
+simplify_info_get_rtti_varmaps(Info, Info ^ simp_rtti_varmaps).
+simplify_info_get_format_calls(Info, Info ^ simp_format_calls).
 simplify_info_get_inside_duplicated_for_switch(Info,
-    Info ^ inside_dupl_for_switch).
-simplify_info_get_has_parallel_conj(Info, Info ^ has_parallel_conj).
-simplify_info_get_found_contains_trace(Info, Info ^ found_contains_trace).
-simplify_info_get_has_user_event(Info, Info ^ has_user_event).
+    Info ^ simp_inside_dupl_for_switch).
+simplify_info_get_has_parallel_conj(Info, Info ^ simp_has_parallel_conj).
+simplify_info_get_found_contains_trace(Info, Info ^ simp_found_contains_trace).
+simplify_info_get_has_user_event(Info, Info ^ simp_has_user_event).
 
 simplify_info_get_module_info(Info, ModuleInfo) :-
     simplify_info_get_det_info(Info, DetInfo),
@@ -3560,30 +3566,31 @@
 :- pred simplify_info_set_module_info(module_info::in,
     simplify_info::in, simplify_info::out) is det.
 
-simplify_info_set_det_info(Det, Info, Info ^ det_info := Det).
-simplify_info_set_error_specs(Specs, Info, Info ^ error_specs := Specs).
-simplify_info_set_simplifications(Simp, Info, Info ^ simplifications := Simp).
-simplify_info_set_instmap(InstMap, Info, Info ^ instmap := InstMap).
-simplify_info_set_common_info(Common, Info, Info ^ common_info := Common).
-simplify_info_set_varset(VarSet, Info, Info ^ varset := VarSet).
-simplify_info_set_var_types(VarTypes, Info, Info ^ det_info := DetInfo) :-
-    det_info_set_vartypes(VarTypes, Info  ^  det_info, DetInfo).
-simplify_info_set_requantify(Info, Info ^ requantify := yes).
-simplify_info_set_recompute_atomic(Info, Info ^ recompute_atomic := yes).
-simplify_info_set_rerun_det(Info, Info ^ rerun_det := yes).
-simplify_info_set_cost_delta(Delta, Info, Info ^ cost_delta := Delta).
-simplify_info_set_rtti_varmaps(Rtti, Info, Info ^ rtti_varmaps := Rtti).
-simplify_info_set_format_calls(FC, Info, Info ^ format_calls := FC).
+simplify_info_set_det_info(Det, Info, Info ^ simp_det_info := Det).
+simplify_info_set_error_specs(Specs, Info, Info ^ simp_error_specs := Specs).
+simplify_info_set_simplifications(Simp, Info,
+    Info ^ simp_simplifications := Simp).
+simplify_info_set_instmap(InstMap, Info, Info ^ simp_instmap := InstMap).
+simplify_info_set_common_info(Common, Info, Info ^ simp_common_info := Common).
+simplify_info_set_varset(VarSet, Info, Info ^ simp_varset := VarSet).
+simplify_info_set_var_types(VarTypes, Info, Info ^ simp_det_info := DetInfo) :-
+    det_info_set_vartypes(VarTypes, Info ^ simp_det_info, DetInfo).
+simplify_info_set_requantify(Info, Info ^ simp_requantify := yes).
+simplify_info_set_recompute_atomic(Info, Info ^ simp_recompute_atomic := yes).
+simplify_info_set_rerun_det(Info, Info ^ simp_rerun_det := yes).
+simplify_info_set_cost_delta(Delta, Info, Info ^ simp_cost_delta := Delta).
+simplify_info_set_rtti_varmaps(Rtti, Info, Info ^ simp_rtti_varmaps := Rtti).
+simplify_info_set_format_calls(FC, Info, Info ^ simp_format_calls := FC).
 simplify_info_set_inside_duplicated_for_switch(IDFS, Info,
-    Info ^ inside_dupl_for_switch := IDFS).
+    Info ^ simp_inside_dupl_for_switch := IDFS).
 simplify_info_set_has_parallel_conj(MHPC, Info,
-    Info ^ has_parallel_conj := MHPC).
+    Info ^ simp_has_parallel_conj := MHPC).
 simplify_info_set_found_contains_trace(FCT, Info,
-    Info ^ found_contains_trace := FCT).
-simplify_info_set_has_user_event(HUE, Info, Info ^ has_user_event := HUE).
+    Info ^ simp_found_contains_trace := FCT).
+simplify_info_set_has_user_event(HUE, Info, Info ^ simp_has_user_event := HUE).
 
 simplify_info_incr_cost_delta(Incr, Info,
-    Info ^ cost_delta := Info ^ cost_delta + Incr).
+    Info ^ simp_cost_delta := Info ^ simp_cost_delta + Incr).
 
 simplify_info_add_error_spec(Spec, !Info) :-
     ( simplify_do_warn_simple_code(!.Info) ->
@@ -3597,17 +3604,20 @@
     Specs = [Spec | Specs0],
     simplify_info_set_error_specs(Specs, !Info).
 
-simplify_info_enter_lambda(Info, Info ^ lambdas := Info ^ lambdas + 1).
-simplify_info_leave_lambda(Info, Info ^ lambdas := LambdaCount) :-
-    LambdaCount1 = Info ^ lambdas - 1,
-    ( LambdaCount1 >= 0 ->
-        LambdaCount = LambdaCount1
+simplify_info_enter_lambda(!Info) :-
+    !Info ^ simp_lambdas := !.Info ^ simp_lambdas + 1.
+
+simplify_info_leave_lambda(!Info) :-
+    LambdaCount = !.Info ^ simp_lambdas - 1,
+    ( LambdaCount >= 0 ->
+        !Info ^ simp_lambdas := LambdaCount
     ;
         unexpected(this_file,
             "simplify_info_leave_lambda: Left too many lambdas")
     ).
+
 simplify_info_inside_lambda(Info) :-
-    Info ^ lambdas > 0.
+    Info ^ simp_lambdas > 0.
 
 simplify_info_set_module_info(ModuleInfo, !Info) :-
     simplify_info_get_det_info(!.Info, DetInfo0),
@@ -3629,8 +3639,8 @@
 :- pred simplify_info_update_instmap(hlds_goal::in,
     simplify_info::in, simplify_info::out) is det.
 
-simplify_info_update_instmap(Goal, Info, Info ^ instmap := InstMap) :-
-    update_instmap(Goal, Info ^ instmap, InstMap).
+simplify_info_update_instmap(Goal, Info, Info ^ simp_instmap := InstMap) :-
+    update_instmap(Goal, Info ^ simp_instmap, InstMap).
 
 :- type before_after
     --->    before
Index: compiler/size_prof.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/size_prof.m,v
retrieving revision 1.55
diff -u -b -r1.55 size_prof.m
--- compiler/size_prof.m	30 Dec 2007 08:23:56 -0000	1.55
+++ compiler/size_prof.m	12 Jan 2008 20:13:58 -0000
@@ -200,17 +200,17 @@
 
 :- type size_prof.info
     --->    size_prof_info(
-                type_ctor_map           :: type_ctor_map,
-                type_info_map           :: type_info_map,
-                rev_type_ctor_map       :: rev_type_ctor_map,
-                rev_type_info_map       :: rev_type_info_map,
-                target_type_info_map    :: type_info_map,
-                known_size_map          :: known_size_map,
-                varset                  :: prog_varset,
-                vartypes                :: vartypes,
-                transform_op            :: construct_transform,
-                rtti_varmaps            :: rtti_varmaps,
-                module_info             :: module_info
+                spi_type_ctor_map           :: type_ctor_map,
+                spi_type_info_map           :: type_info_map,
+                spi_rev_type_ctor_map       :: rev_type_ctor_map,
+                spi_rev_type_info_map       :: rev_type_info_map,
+                spi_target_type_info_map    :: type_info_map,
+                spi_known_size_map          :: known_size_map,
+                spi_varset                  :: prog_varset,
+                spi_vartypes                :: vartypes,
+                spi_transform_op            :: construct_transform,
+                spi_rtti_varmaps            :: rtti_varmaps,
+                spi_module_info             :: module_info
             ).
 
 process_proc_msg(Transform, PredId, ProcId, ProcInfo0, ProcInfo,
@@ -266,8 +266,8 @@
     proc_info_get_headvars(!.ProcInfo, HeadVars),
     proc_info_get_inst_varset(!.ProcInfo, InstVarSet),
     implicitly_quantify_clause_body(HeadVars, _Warnings, Goal1, Goal2,
-        Info ^ varset, VarSet, Info ^ vartypes, VarTypes,
-        Info ^ rtti_varmaps, RttiVarMaps),
+        Info ^ spi_varset, VarSet, Info ^ spi_vartypes, VarTypes,
+        Info ^ spi_rtti_varmaps, RttiVarMaps),
     recompute_instmap_delta(no, Goal2, Goal, VarTypes, InstVarSet,
         InstMap0, !ModuleInfo),
     proc_info_set_goal(Goal, !ProcInfo),
@@ -318,16 +318,16 @@
         % We don't want to save type_ctor_info variables across calls,
         % because saving/restoring them is more expensive than defining
         % them again.
-        !:Info = !.Info ^ type_ctor_map := map.init,
-        !:Info = !.Info ^ rev_type_ctor_map := map.init,
+        !:Info = !.Info ^ spi_type_ctor_map := map.init,
+        !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
         GoalExpr = GoalExpr0
     ;
         GoalExpr0 = generic_call(_, _, _, _),
         % We don't want to save type_ctor_info variables across calls,
         % because saving/restoring them is more expensive than defining
         % them again.
-        !:Info = !.Info ^ type_ctor_map := map.init,
-        !:Info = !.Info ^ rev_type_ctor_map := map.init,
+        !:Info = !.Info ^ spi_type_ctor_map := map.init,
+        !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
         GoalExpr = GoalExpr0
     ;
         GoalExpr0 = call_foreign_proc(_, _, _, _, _, _, _),
@@ -343,42 +343,42 @@
             % optimal. However, it ought to be more robust than any better
             % transformation, and there is no point in spending time on a
             % better transformation while parallel conjunctions are rare.
-            TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-            TypeInfoMap0 = !.Info ^ type_info_map,
-            RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-            TypeCtorMap0 = !.Info ^ type_ctor_map,
-            KnownSizeMap0 = !.Info ^ known_size_map,
+            TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+            TypeInfoMap0 = !.Info ^ spi_type_info_map,
+            RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+            TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+            KnownSizeMap0 = !.Info ^ spi_known_size_map,
             process_par_conj(Goals0, Goals, !Info, TargetTypeInfoMap0,
                 TypeInfoMap0, TypeCtorMap0, KnownSizeMap0),
-            !:Info = !.Info ^ target_type_info_map := TargetTypeInfoMap0,
-            !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-            !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap0,
-            !:Info = !.Info ^ type_ctor_map := map.init,
-            !:Info = !.Info ^ rev_type_ctor_map := map.init,
-            !:Info = !.Info ^ known_size_map := KnownSizeMap0
+            !:Info = !.Info ^ spi_target_type_info_map := TargetTypeInfoMap0,
+            !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+            !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap0,
+            !:Info = !.Info ^ spi_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0
         ),
         GoalExpr = conj(ConjType, Goals)
     ;
         GoalExpr0 = switch(SwitchVar, CanFail, Cases0),
         (
             Cases0 = [First0 | Later0],
-            TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-            TypeInfoMap0 = !.Info ^ type_info_map,
-            RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-            TypeCtorMap0 = !.Info ^ type_ctor_map,
-            RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
-            KnownSizeMap0 = !.Info ^ known_size_map,
+            TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+            TypeInfoMap0 = !.Info ^ spi_type_info_map,
+            RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+            TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+            RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
+            KnownSizeMap0 = !.Info ^ spi_known_size_map,
             process_switch(First0, First, Later0, Later, !Info,
                 TargetTypeInfoMap0,
                 TypeInfoMap0, RevTypeInfoMap0,
                 TypeCtorMap0, RevTypeCtorMap0,
                 TypeInfoMap, KnownSizeMap0, KnownSizeMap),
-            !:Info = !.Info ^ type_info_map := TypeInfoMap,
+            !:Info = !.Info ^ spi_type_info_map := TypeInfoMap,
             % The rev_type_info_map field is updated by
             % the call to update_rev_maps below.
-            !:Info = !.Info ^ type_ctor_map := map.init,
-            !:Info = !.Info ^ rev_type_ctor_map := map.init,
-            !:Info = !.Info ^ known_size_map := KnownSizeMap,
+            !:Info = !.Info ^ spi_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_known_size_map := KnownSizeMap,
             Cases = [First | Later]
         ;
             Cases0 = [],
@@ -391,31 +391,31 @@
         GoalExpr0 = disj(Disjuncts0),
         (
             Disjuncts0 = [First0 | Later0],
-            TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-            TypeInfoMap0 = !.Info ^ type_info_map,
-            RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-            TypeCtorMap0 = !.Info ^ type_ctor_map,
-            RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
-            KnownSizeMap0 = !.Info ^ known_size_map,
+            TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+            TypeInfoMap0 = !.Info ^ spi_type_info_map,
+            RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+            TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+            RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
+            KnownSizeMap0 = !.Info ^ spi_known_size_map,
             process_disj(First0, First, Later0, Later, !Info,
                 TargetTypeInfoMap0,
                 TypeInfoMap0, RevTypeInfoMap0,
                 TypeCtorMap0, RevTypeCtorMap0,
                 TypeInfoMap, KnownSizeMap0, KnownSizeMap),
-            !:Info = !.Info ^ type_info_map := TypeInfoMap,
+            !:Info = !.Info ^ spi_type_info_map := TypeInfoMap,
             % The rev_type_info_map field is updated by
             % the call to update_rev_maps below.
-            !:Info = !.Info ^ type_ctor_map := map.init,
-            !:Info = !.Info ^ rev_type_ctor_map := map.init,
-            !:Info = !.Info ^ known_size_map := KnownSizeMap,
+            !:Info = !.Info ^ spi_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_known_size_map := KnownSizeMap,
             Disjuncts = [First | Later]
         ;
             Disjuncts0 = [],
             % An empty disj represents `fail'.
-            !:Info = !.Info ^ type_info_map := map.init,
-            !:Info = !.Info ^ rev_type_ctor_map := map.init,
-            !:Info = !.Info ^ type_info_map := map.init,
-            !:Info = !.Info ^ rev_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_type_info_map := map.init,
+            !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
+            !:Info = !.Info ^ spi_type_info_map := map.init,
+            !:Info = !.Info ^ spi_rev_type_ctor_map := map.init,
             Disjuncts = []
         ),
         update_rev_maps(!Info),
@@ -423,60 +423,59 @@
         GoalExpr = disj(Disjuncts)
     ;
         GoalExpr0 = if_then_else(Quant, Cond0, Then0, Else0),
-        TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-        TypeInfoMap0 = !.Info ^ type_info_map,
-        RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-        TypeCtorMap0 = !.Info ^ type_ctor_map,
-        RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
-        KnownSizeMap0 = !.Info ^ known_size_map,
+        TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+        TypeInfoMap0 = !.Info ^ spi_type_info_map,
+        RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+        TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+        RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
+        KnownSizeMap0 = !.Info ^ spi_known_size_map,
 
-        !:Info = !.Info ^ target_type_info_map := map.init,
+        !:Info = !.Info ^ spi_target_type_info_map := map.init,
         process_goal(Cond0, Cond, !Info),
-        !:Info = !.Info ^ target_type_info_map := TargetTypeInfoMap0,
+        !:Info = !.Info ^ spi_target_type_info_map := TargetTypeInfoMap0,
         process_goal(Then0, Then, !Info),
-        TargetTypeInfoMapThen = !.Info ^ target_type_info_map,
-        TypeInfoMapThen = !.Info ^ type_info_map,
-        KnownSizeMapThen = !.Info ^ known_size_map,
+        TargetTypeInfoMapThen = !.Info ^ spi_target_type_info_map,
+        TypeInfoMapThen = !.Info ^ spi_type_info_map,
+        KnownSizeMapThen = !.Info ^ spi_known_size_map,
 
         map.union(select_first, TargetTypeInfoMapThen,
             TargetTypeInfoMap0, ElseTargetTypeInfoMap),
-        !:Info = !.Info ^ target_type_info_map :=
-            ElseTargetTypeInfoMap,
-        !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-        !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap0,
-        !:Info = !.Info ^ type_ctor_map := TypeCtorMap0,
-        !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap0,
-        !:Info = !.Info ^ known_size_map := KnownSizeMap0,
+        !:Info = !.Info ^ spi_target_type_info_map := ElseTargetTypeInfoMap,
+        !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+        !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap0,
+        !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap0,
+        !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap0,
+        !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0,
         process_goal(Else0, Else, !Info),
-        TypeInfoMapElse = !.Info ^ type_info_map,
-        KnownSizeMapElse = !.Info ^ known_size_map,
+        TypeInfoMapElse = !.Info ^ spi_type_info_map,
+        KnownSizeMapElse = !.Info ^ spi_known_size_map,
 
         TypeInfoMap = map.common_subset(TypeInfoMapThen, TypeInfoMapElse),
         KnownSizeMap = map.common_subset(KnownSizeMapThen, KnownSizeMapElse),
-        !:Info = !.Info ^ type_info_map := TypeInfoMap,
-        !:Info = !.Info ^ type_ctor_map := map.init,
-        !:Info = !.Info ^ known_size_map := KnownSizeMap,
+        !:Info = !.Info ^ spi_type_info_map := TypeInfoMap,
+        !:Info = !.Info ^ spi_type_ctor_map := map.init,
+        !:Info = !.Info ^ spi_known_size_map := KnownSizeMap,
         update_rev_maps(!Info),
         update_target_map(!Info),
         GoalExpr = if_then_else(Quant, Cond, Then, Else)
     ;
         GoalExpr0 = negation(NegGoal0),
-        TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-        TypeInfoMap0 = !.Info ^ type_info_map,
-        RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-        TypeCtorMap0 = !.Info ^ type_ctor_map,
-        RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
-        KnownSizeMap0 = !.Info ^ known_size_map,
+        TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+        TypeInfoMap0 = !.Info ^ spi_type_info_map,
+        RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+        TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+        RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
+        KnownSizeMap0 = !.Info ^ spi_known_size_map,
         process_goal(NegGoal0, NegGoal, !Info),
         % Variables constructed in negated goals are not available after the
         % negated goal fails and the negation succeeds. The sizes we learn
         % in NegGoal0 don't apply after NegGoal0 fails.
-        !:Info = !.Info ^ target_type_info_map := TargetTypeInfoMap0,
-        !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-        !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap0,
-        !:Info = !.Info ^ type_ctor_map := TypeCtorMap0,
-        !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap0,
-        !:Info = !.Info ^ known_size_map := KnownSizeMap0,
+        !:Info = !.Info ^ spi_target_type_info_map := TargetTypeInfoMap0,
+        !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+        !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap0,
+        !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap0,
+        !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap0,
+        !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0,
         GoalExpr = negation(NegGoal)
     ;
         GoalExpr0 = scope(Reason, SomeGoal0),
@@ -516,10 +515,10 @@
 process_par_conj([], [], !Info, _, _, _, _).
 process_par_conj([Goal0 | Goals0], [Goal | Goals], !Info, TargetTypeInfoMap0,
         TypeInfoMap0, TypeCtorMap0, KnownSizeMap0) :-
-    !:Info = !.Info ^ target_type_info_map := TargetTypeInfoMap0,
-    !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-    !:Info = !.Info ^ type_ctor_map := TypeCtorMap0,
-    !:Info = !.Info ^ known_size_map := KnownSizeMap0,
+    !:Info = !.Info ^ spi_target_type_info_map := TargetTypeInfoMap0,
+    !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+    !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap0,
+    !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0,
     process_goal(Goal0, Goal, !Info),
     process_par_conj(Goals0, Goals, !Info, TargetTypeInfoMap0,
         TypeInfoMap0, TypeCtorMap0, KnownSizeMap0).
@@ -535,25 +534,24 @@
 process_disj(First0, First, Later0, Later, !Info, TargetTypeInfoMap,
         TypeInfoMap0, RevTypeInfoMap0, TypeCtorMap0, RevTypeCtorMap0,
         TypeInfoMap, KnownSizeMap0, KnownSizeMap) :-
-    !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-    !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap0,
-    !:Info = !.Info ^ type_ctor_map := TypeCtorMap0,
-    !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap0,
-    !:Info = !.Info ^ known_size_map := KnownSizeMap0,
+    !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+    !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap0,
+    !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap0,
+    !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap0,
+    !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0,
     process_goal(First0, First, !Info),
-    TypeInfoMapFirst = !.Info ^ type_info_map,
-    KnownSizeMapFirst = !.Info ^ known_size_map,
+    TypeInfoMapFirst = !.Info ^ spi_type_info_map,
+    KnownSizeMapFirst = !.Info ^ spi_known_size_map,
     (
         Later0 = [Head0 | Tail0],
         map.union(select_first, TypeInfoMapFirst,
             TargetTypeInfoMap, LaterTargetTypeInfoMap),
-        !:Info = !.Info ^ target_type_info_map := LaterTargetTypeInfoMap,
+        !:Info = !.Info ^ spi_target_type_info_map := LaterTargetTypeInfoMap,
         process_disj(Head0, Head, Tail0, Tail, !Info, TargetTypeInfoMap,
             TypeInfoMap0, RevTypeInfoMap0, TypeCtorMap0, RevTypeCtorMap0,
             TypeInfoMapLater, KnownSizeMap0, KnownSizeMapLater),
         TypeInfoMap = map.common_subset(TypeInfoMapFirst, TypeInfoMapLater),
-        KnownSizeMap = map.common_subset(KnownSizeMapFirst,
-            KnownSizeMapLater),
+        KnownSizeMap = map.common_subset(KnownSizeMapFirst, KnownSizeMapLater),
         Later = [Head | Tail]
     ;
         Later0 = [],
@@ -573,27 +571,26 @@
 process_switch(First0, First, Later0, Later, !Info, TargetTypeInfoMap,
         TypeInfoMap0, RevTypeInfoMap0, TypeCtorMap0, RevTypeCtorMap0,
         TypeInfoMap, KnownSizeMap0, KnownSizeMap) :-
-    !:Info = !.Info ^ type_info_map := TypeInfoMap0,
-    !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap0,
-    !:Info = !.Info ^ type_ctor_map := TypeCtorMap0,
-    !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap0,
-    !:Info = !.Info ^ known_size_map := KnownSizeMap0,
+    !:Info = !.Info ^ spi_type_info_map := TypeInfoMap0,
+    !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap0,
+    !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap0,
+    !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap0,
+    !:Info = !.Info ^ spi_known_size_map := KnownSizeMap0,
     First0 = case(FirstMainConsId, FirstOtherConsIds, FirstGoal0),
     process_goal(FirstGoal0, FirstGoal, !Info),
-    TypeInfoMapFirst = !.Info ^ type_info_map,
-    KnownSizeMapFirst = !.Info ^ known_size_map,
+    TypeInfoMapFirst = !.Info ^ spi_type_info_map,
+    KnownSizeMapFirst = !.Info ^ spi_known_size_map,
     First = case(FirstMainConsId, FirstOtherConsIds, FirstGoal),
     (
         Later0 = [Head0 | Tail0],
         map.union(select_first, TargetTypeInfoMap,
             TypeInfoMapFirst, LaterTargetTypeInfoMap),
-        !:Info = !.Info ^ target_type_info_map := LaterTargetTypeInfoMap,
+        !:Info = !.Info ^ spi_target_type_info_map := LaterTargetTypeInfoMap,
         process_switch(Head0, Head, Tail0, Tail, !Info, TargetTypeInfoMap,
             TypeInfoMap0, RevTypeInfoMap0, TypeCtorMap0, RevTypeCtorMap0,
             TypeInfoMapLater, KnownSizeMap0, KnownSizeMapLater),
         TypeInfoMap = map.common_subset(TypeInfoMapFirst, TypeInfoMapLater),
-        KnownSizeMap = map.common_subset(KnownSizeMapFirst,
-            KnownSizeMapLater),
+        KnownSizeMap = map.common_subset(KnownSizeMapFirst, KnownSizeMapLater),
         Later = [Head | Tail]
     ;
         Later0 = [],
@@ -611,15 +608,16 @@
 
 process_construct(LHS, RHS, UniMode, UnifyContext, Var, ConsId, Args, ArgModes,
         How, Unique, GoalInfo, GoalExpr, !Info) :-
-    map.lookup(!.Info ^ vartypes, Var, VarType),
+    map.lookup(!.Info ^ spi_vartypes, Var, VarType),
     ( type_to_ctor_and_args(VarType, VarTypeCtorPrime, _VarTypeArgs) ->
         VarTypeCtor = VarTypeCtorPrime
     ;
         unexpected(this_file,
             "size_prof.process_construct: constructing term of variable type")
     ),
-    VarTypeCtorModule = type_ctor_module(!.Info ^ module_info, VarTypeCtor),
-    VarTypeCtorName = type_ctor_name(!.Info ^ module_info, VarTypeCtor),
+    ModuleInfo = !.Info ^ spi_module_info,
+    VarTypeCtorModule = type_ctor_module(ModuleInfo, VarTypeCtor),
+    VarTypeCtorName = type_ctor_name(ModuleInfo, VarTypeCtor),
     (
         ctor_is_type_info_related(VarTypeCtorModule, VarTypeCtorName)
     ->
@@ -674,15 +672,16 @@
     info::in, info::out) is det.
 
 process_deconstruct(Var, ConsId, Args, ArgModes, Goal0, GoalExpr, !Info) :-
-    map.lookup(!.Info ^ vartypes, Var, VarType),
+    map.lookup(!.Info ^ spi_vartypes, Var, VarType),
     ( type_to_ctor_and_args(VarType, VarTypeCtorPrime, _VarTypeArgs) ->
         VarTypeCtor = VarTypeCtorPrime
     ;
         unexpected(this_file,
             "process_deconstruct: deconstructing term of variable type")
     ),
-    VarTypeCtorModule = type_ctor_module(!.Info ^ module_info, VarTypeCtor),
-    VarTypeCtorName = type_ctor_name(!.Info ^ module_info, VarTypeCtor),
+    ModuleInfo = !.Info ^ spi_module_info,
+    VarTypeCtorModule = type_ctor_module(ModuleInfo, VarTypeCtor),
+    VarTypeCtorName = type_ctor_name(ModuleInfo, VarTypeCtor),
     (
         ctor_is_type_info_related(VarTypeCtorModule, VarTypeCtorName)
     ->
@@ -771,7 +770,7 @@
         TermSizeProfBuiltin = mercury_term_size_prof_builtin_module,
         goal_util.generate_simple_call(TermSizeProfBuiltin,
             "increment_size", pf_predicate, only_mode, detism_det,
-            purity_impure, [Var, SizeVar], [], [], !.Info ^ module_info,
+            purity_impure, [Var, SizeVar], [], [], !.Info ^ spi_module_info,
             Context, UpdateGoal),
         % Put UnifyGoal first in case it fails.
         Goals = [UnifyGoal] ++ ArgGoals ++ SizeGoals ++ [UpdateGoal],
@@ -795,11 +794,11 @@
 
 process_args([], !KnownSize, !MaybeSizeVar, _, [], !Info).
 process_args([Arg | Args], !KnownSize, !MaybeSizeVar, Context, Goals, !Info) :-
-    map.lookup(!.Info ^ vartypes, Arg, Type),
-    ( map.search(!.Info ^ known_size_map, Arg, ArgSize) ->
+    map.lookup(!.Info ^ spi_vartypes, Arg, Type),
+    ( map.search(!.Info ^ spi_known_size_map, Arg, ArgSize) ->
         !:KnownSize = !.KnownSize + ArgSize,
         ArgGoals = []
-    ; zero_size_type(!.Info ^ module_info, Type) ->
+    ; zero_size_type(!.Info ^ spi_module_info, Type) ->
         ArgGoals = []
     ;
         make_type_info(Context, Type, TypeInfoVar, TypeInfoGoals, !Info),
@@ -825,20 +824,20 @@
         SizeVar = SizeVar0,
         Goals = []
     ;
-        VarSet0 = !.Info ^ varset,
-        VarTypes0 = !.Info ^ vartypes,
+        VarSet0 = !.Info ^ spi_varset,
+        VarTypes0 = !.Info ^ spi_vartypes,
         make_int_const_construction_alloc(KnownSize,
             yes("KnownSize"), KnownSizeGoal, KnownSizeVar,
             VarSet0, VarSet1, VarTypes0, VarTypes1),
-        !:Info = !.Info ^ varset := VarSet1,
-        !:Info = !.Info ^ vartypes := VarTypes1,
+        !:Info = !.Info ^ spi_varset := VarSet1,
+        !:Info = !.Info ^ spi_vartypes := VarTypes1,
         get_new_var(int_type, "FinalSizeVar", SizeVar, !Info),
         TermSizeProfModule = mercury_term_size_prof_builtin_module,
         goal_util.generate_simple_call(TermSizeProfModule,
             "term_size_plus", pf_function, mode_no(0), detism_det, purity_pure,
             [SizeVar0, KnownSizeVar, SizeVar], [],
             [SizeVar - ground(shared, none)],
-            !.Info ^ module_info, Context, AddGoal),
+            !.Info ^ spi_module_info, Context, AddGoal),
         Goals = [KnownSizeGoal, AddGoal]
     ).
 
@@ -853,7 +852,7 @@
     list(hlds_goal)::out, info::in, info::out) is det.
 
 make_type_info(Context, Type, TypeInfoVar, TypeInfoGoals, !Info) :-
-    ( map.search(!.Info ^ type_info_map, Type, TypeInfoVarPrime) ->
+    ( map.search(!.Info ^ spi_type_info_map, Type, TypeInfoVarPrime) ->
         TypeInfoVar = TypeInfoVarPrime,
         TypeInfoGoals = []
     ; type_has_variable_arity_ctor(Type, TypeCtor, ArgTypes) ->
@@ -872,37 +871,37 @@
                 no, TypeInfoVar, TypeInfoGoals, !Info)
         )
     ; Type = type_variable(TVar, _) ->
-        rtti_lookup_type_info_locn(!.Info ^ rtti_varmaps, TVar, TVarLocn),
+        rtti_lookup_type_info_locn(!.Info ^ spi_rtti_varmaps, TVar, TVarLocn),
         (
             TVarLocn = type_info(TypeInfoVar),
             TypeInfoGoals = []
         ;
             TVarLocn = typeclass_info(TypeClassInfoVar, Slot),
-            TargetTypeInfoMap = !.Info ^ target_type_info_map,
-            VarSet0 = !.Info ^ varset,
-            VarTypes0 = !.Info ^ vartypes,
+            TargetTypeInfoMap = !.Info ^ spi_target_type_info_map,
+            VarSet0 = !.Info ^ spi_varset,
+            VarTypes0 = !.Info ^ spi_vartypes,
             ( map.search(TargetTypeInfoMap, Type, TargetVar) ->
                 TypeInfoVar = TargetVar,
                 VarSet1 = VarSet0,
                 VarTypes1 = VarTypes0
             ;
-                RttiVarMaps0 = !.Info ^ rtti_varmaps,
+                RttiVarMaps0 = !.Info ^ spi_rtti_varmaps,
                 polymorphism.new_type_info_var_raw(Type, type_info,
                     TypeInfoVar, VarSet0, VarSet1, VarTypes0, VarTypes1,
                     RttiVarMaps0, RttiVarMaps),
-                !:Info = !.Info ^ rtti_varmaps := RttiVarMaps
+                !:Info = !.Info ^ spi_rtti_varmaps := RttiVarMaps
             ),
             make_int_const_construction_alloc(Slot, yes("TypeClassInfoSlot"),
                 SlotGoal, SlotVar, VarSet1, VarSet, VarTypes1, VarTypes),
-            !:Info = !.Info ^ varset := VarSet,
-            !:Info = !.Info ^ vartypes := VarTypes,
+            !:Info = !.Info ^ spi_varset := VarSet,
+            !:Info = !.Info ^ spi_vartypes := VarTypes,
             PrivateBuiltin = mercury_private_builtin_module,
             goal_util.generate_simple_call(PrivateBuiltin,
                 "type_info_from_typeclass_info", pf_predicate, only_mode,
                 detism_det, purity_pure,
                 [TypeClassInfoVar, SlotVar, TypeInfoVar], [],
                 [TypeInfoVar - ground(shared, none)],
-                !.Info ^ module_info, Context, ExtractGoal),
+                !.Info ^ spi_module_info, Context, ExtractGoal),
             record_type_info_var(Type, TypeInfoVar, !Info),
             TypeInfoGoals = [SlotGoal, ExtractGoal]
         )
@@ -931,12 +930,12 @@
     (
         CtorIsVarArity = yes,
         list.length(ArgTypes, Arity),
-        VarSet0 = !.Info ^ varset,
-        VarTypes0 = !.Info ^ vartypes,
+        VarSet0 = !.Info ^ spi_varset,
+        VarTypes0 = !.Info ^ spi_vartypes,
         make_int_const_construction_alloc(Arity, yes("TupleArity"), ArityGoal,
             ArityVar, VarSet0, VarSet1, VarTypes0, VarTypes1),
-        !:Info = !.Info ^ varset := VarSet1,
-        !:Info = !.Info ^ vartypes := VarTypes1,
+        !:Info = !.Info ^ spi_varset := VarSet1,
+        !:Info = !.Info ^ spi_vartypes := VarTypes1,
         FrontGoals = list.append(TypeCtorGoals, [ArityGoal]),
         ArgVars = [TypeCtorVar, ArityVar | ArgTypeInfoVars]
     ;
@@ -944,10 +943,10 @@
         FrontGoals = TypeCtorGoals,
         ArgVars = [TypeCtorVar | ArgTypeInfoVars]
     ),
-    VarSet2 = !.Info ^ varset,
-    VarTypes2 = !.Info ^ vartypes,
-    RttiVarMaps0 = !.Info ^ rtti_varmaps,
-    TargetTypeInfoMap = !.Info ^ target_type_info_map,
+    VarSet2 = !.Info ^ spi_varset,
+    VarTypes2 = !.Info ^ spi_vartypes,
+    RttiVarMaps0 = !.Info ^ spi_rtti_varmaps,
+    TargetTypeInfoMap = !.Info ^ spi_target_type_info_map,
     ( map.search(TargetTypeInfoMap, Type, PrefTIVar) ->
         MaybePreferredVar = yes(PrefTIVar)
     ;
@@ -956,11 +955,10 @@
     polymorphism.init_type_info_var(Type, ArgVars, MaybePreferredVar,
         TypeInfoVar, TypeInfoGoal, VarSet2, VarSet, VarTypes2, VarTypes,
         RttiVarMaps0, RttiVarMaps),
-    !:Info = !.Info ^ varset := VarSet,
-    !:Info = !.Info ^ vartypes := VarTypes,
-    !:Info = !.Info ^ rtti_varmaps := RttiVarMaps,
-    TypeInfoGoals = list.condense([ArgTypeInfoGoals, FrontGoals,
-        [TypeInfoGoal]]).
+    !:Info = !.Info ^ spi_varset := VarSet,
+    !:Info = !.Info ^ spi_vartypes := VarTypes,
+    !:Info = !.Info ^ spi_rtti_varmaps := RttiVarMaps,
+    TypeInfoGoals = ArgTypeInfoGoals ++ FrontGoals ++ [TypeInfoGoal].
 
     % Create a type_ctor_info for a given type constructor as cheaply as
     % possible, with the cheapest method being the reuse of an existing
@@ -971,7 +969,7 @@
     list(hlds_goal)::out, info::in, info::out) is det.
 
 make_type_ctor_info(TypeCtor, TypeArgs, TypeCtorVar, TypeCtorGoals, !Info) :-
-    ( map.search(!.Info ^ type_ctor_map, TypeCtor, TypeCtorVarPrime) ->
+    ( map.search(!.Info ^ spi_type_ctor_map, TypeCtor, TypeCtorVarPrime) ->
         TypeCtorVar = TypeCtorVarPrime,
         TypeCtorGoals = []
     ;
@@ -983,17 +981,17 @@
         ;
             construct_type(TypeCtor, [], Type)
         ),
-        VarSet0 = !.Info ^ varset,
-        VarTypes0 = !.Info ^ vartypes,
-        RttiVarMaps0 = !.Info ^ rtti_varmaps,
+        VarSet0 = !.Info ^ spi_varset,
+        VarTypes0 = !.Info ^ spi_vartypes,
+        RttiVarMaps0 = !.Info ^ spi_rtti_varmaps,
         polymorphism.init_const_type_ctor_info_var(Type, TypeCtor,
-            TypeCtorVar, TypeCtorGoal, !.Info ^ module_info,
+            TypeCtorVar, TypeCtorGoal, !.Info ^ spi_module_info,
             VarSet0, VarSet, VarTypes0, VarTypes,
             RttiVarMaps0, RttiVarMaps),
         TypeCtorGoals = [TypeCtorGoal],
-        !:Info = !.Info ^ varset := VarSet,
-        !:Info = !.Info ^ vartypes := VarTypes,
-        !:Info = !.Info ^ rtti_varmaps := RttiVarMaps
+        !:Info = !.Info ^ spi_varset := VarSet,
+        !:Info = !.Info ^ spi_vartypes := VarTypes,
+        !:Info = !.Info ^ spi_rtti_varmaps := RttiVarMaps
     ).
 
 %-----------------------------------------------------------------------------%
@@ -1027,7 +1025,7 @@
     goal_util.generate_simple_call(TermSizeProfBuiltin, Pred, pf_predicate,
         only_mode, detism_det, purity_pure, Args,
         [], [SizeVar - ground(shared, none)],
-        !.Info ^ module_info, Context, SizeGoal),
+        !.Info ^ spi_module_info, Context, SizeGoal),
     MaybeSizeVar = yes(SizeVar).
 
 %---------------------------------------------------------------------------%
@@ -1039,16 +1037,16 @@
     info::in, info::out) is det.
 
 get_new_var(Type, Prefix, Var, !Info) :-
-    VarSet0 = !.Info ^ varset,
-    VarTypes0 = !.Info ^ vartypes,
+    VarSet0 = !.Info ^ spi_varset,
+    VarTypes0 = !.Info ^ spi_vartypes,
     varset.new_var(VarSet0, Var, VarSet1),
     term.var_to_int(Var, VarNum),
     string.int_to_string(VarNum, VarNumStr),
     string.append(Prefix, VarNumStr, Name),
     varset.name_var(VarSet1, Var, Name, VarSet),
     map.set(VarTypes0, Var, Type, VarTypes),
-    !:Info = !.Info ^ varset := VarSet,
-    !:Info = !.Info ^ vartypes := VarTypes.
+    !:Info = !.Info ^ spi_varset := VarSet,
+    !:Info = !.Info ^ spi_vartypes := VarTypes.
 
 %---------------------------------------------------------------------------%
 
@@ -1077,20 +1075,20 @@
         !Info) :-
     TypeCtor = type_ctor(qualified(TypeCtorModule, TypeCtorName),
         TypeCtorArity),
-    TypeCtorMap0 = !.Info ^ type_ctor_map,
-    RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
+    TypeCtorMap0 = !.Info ^ spi_type_ctor_map,
+    RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
     map.set(TypeCtorMap0, TypeCtor, Var, TypeCtorMap),
     map.set(RevTypeCtorMap0, Var, TypeCtor, RevTypeCtorMap),
-    !:Info = !.Info ^ type_ctor_map := TypeCtorMap,
-    !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap.
+    !:Info = !.Info ^ spi_type_ctor_map := TypeCtorMap,
+    !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap.
 
 :- pred record_known_type_info(prog_var::in, prog_var::in, list(prog_var)::in,
     info::in, info::out) is det.
 
 record_known_type_info(Var, TypeCtorInfoVar, ArgTypeInfoVars, !Info) :-
-    RevTypeCtorMap0 = !.Info ^ rev_type_ctor_map,
+    RevTypeCtorMap0 = !.Info ^ spi_rev_type_ctor_map,
     ( map.search(RevTypeCtorMap0, TypeCtorInfoVar, TypeCtor0) ->
-        RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
+        RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
         ( list.map(map.search(RevTypeInfoMap0), ArgTypeInfoVars, ArgTypes) ->
             list.length(ArgTypes, Arity),
             % Just in case TypeCtorInfo0 has fake arity, e.g. if it is a tuple.
@@ -1115,8 +1113,8 @@
     is det.
 
 record_type_info_var(Type, Var, !Info) :-
-    RevTypeInfoMap0 = !.Info ^ rev_type_info_map,
-    TypeInfoMap0 = !.Info ^ type_info_map,
+    RevTypeInfoMap0 = !.Info ^ spi_rev_type_info_map,
+    TypeInfoMap0 = !.Info ^ spi_type_info_map,
     map.set(TypeInfoMap0, Type, Var, TypeInfoMap),
     ( map.insert(RevTypeInfoMap0, Var, Type, RevTypeInfoMap1) ->
         RevTypeInfoMap = RevTypeInfoMap1
@@ -1126,15 +1124,15 @@
         % holds the typeinfo for more than one type.
         RevTypeInfoMap = RevTypeInfoMap0
     ),
-    !:Info = !.Info ^ type_info_map := TypeInfoMap,
-    !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap.
+    !:Info = !.Info ^ spi_type_info_map := TypeInfoMap,
+    !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap.
 
 :- pred record_known_size(prog_var::in, int::in, info::in, info::out) is det.
 
 record_known_size(Var, KnownSize, !Info) :-
-    KnownSizeMap0 = !.Info ^ known_size_map,
+    KnownSizeMap0 = !.Info ^ spi_known_size_map,
     map.det_insert(KnownSizeMap0, Var, KnownSize, KnownSizeMap),
-    !:Info = !.Info ^ known_size_map := KnownSizeMap.
+    !:Info = !.Info ^ spi_known_size_map := KnownSizeMap.
 
 :- pred record_typeinfo_in_type_info_varmap(rtti_varmaps::in, tvar::in,
     info::in, info::out) is det.
@@ -1152,10 +1150,10 @@
         % We could record this information and then look for calls that
         % extract typeinfos from typeclass_infos, but code that does
         % that is rare enough that it is not worth optimizing.
-        % TypeClassInfoMap0 = !.Info ^ type_class_info_map,
+        % TypeClassInfoMap0 = !.Info ^ spi_type_class_info_map,
         % map.det_insert(TypeClassInfoMap0,
         %   TypeClassInfoVar - Offset, Type, TypeClassInfoMap),
-        % !:Info = !.Info ^ type_class_info_map := TypeClassInfoMap
+        % !:Info = !.Info ^ spi_type_class_info_map := TypeClassInfoMap
     ).
 
 %---------------------------------------------------------------------------%
@@ -1176,15 +1174,15 @@
 :- pred update_rev_maps(info::in, info::out) is det.
 
 update_rev_maps(!Info) :-
-    map.to_sorted_assoc_list(!.Info ^ type_info_map, TypeInfoList),
-    map.to_sorted_assoc_list(!.Info ^ type_ctor_map, TypeCtorList),
+    map.to_sorted_assoc_list(!.Info ^ spi_type_info_map, TypeInfoList),
+    map.to_sorted_assoc_list(!.Info ^ spi_type_ctor_map, TypeCtorList),
     map.init(VarCounts0),
     count_appearances(TypeInfoList, VarCounts0, VarCounts1),
     count_appearances(TypeCtorList, VarCounts1, VarCounts),
     construct_rev_map(TypeInfoList, VarCounts, map.init, RevTypeInfoMap),
     construct_rev_map(TypeCtorList, VarCounts, map.init, RevTypeCtorMap),
-    !:Info = !.Info ^ rev_type_info_map := RevTypeInfoMap,
-    !:Info = !.Info ^ rev_type_ctor_map := RevTypeCtorMap.
+    !:Info = !.Info ^ spi_rev_type_info_map := RevTypeInfoMap,
+    !:Info = !.Info ^ spi_rev_type_ctor_map := RevTypeCtorMap.
 
 :- pred count_appearances(assoc_list(T, prog_var)::in,
     map(prog_var, int)::in, map(prog_var, int)::out) is det.
@@ -1228,12 +1226,12 @@
 :- pred update_target_map(info::in, info::out) is det.
 
 update_target_map(!Info) :-
-    TargetTypeInfoMap0 = !.Info ^ target_type_info_map,
-    TypeInfoMap = !.Info ^ type_info_map,
+    TargetTypeInfoMap0 = !.Info ^ spi_target_type_info_map,
+    TypeInfoMap = !.Info ^ spi_type_info_map,
     map.to_sorted_assoc_list(TargetTypeInfoMap0, TargetTypeInfoList),
     list.foldl(include_in_target_map(TypeInfoMap), TargetTypeInfoList,
         map.init, TargetTypeInfoMap),
-    !:Info = !.Info ^ target_type_info_map := TargetTypeInfoMap.
+    !:Info = !.Info ^ spi_target_type_info_map := TargetTypeInfoMap.
 
 :- pred include_in_target_map(type_info_map::in, pair(mer_type, prog_var)::in,
     type_info_map::in, type_info_map::out) is det.
@@ -1250,7 +1248,7 @@
 :- func compute_functor_size(list(prog_var), info) = int.
 
 compute_functor_size(Args, Info) = FunctorSize :-
-    TransformOp = Info ^ transform_op,
+    TransformOp = Info ^ spi_transform_op,
     (
         TransformOp = term_cells,
         FunctorSize = 1
@@ -1294,7 +1292,7 @@
 
 binds_arg_in_cell(Info, (CellInitInst - _ArgInitInst) ->
         (CellFinalInst - _ArgFinalInst)) :-
-    ModuleInfo = Info ^ module_info,
+    ModuleInfo = Info ^ spi_module_info,
     inst_is_free(ModuleInfo, CellInitInst),
     inst_is_bound(ModuleInfo, CellFinalInst).
 
Index: compiler/stack_opt.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/stack_opt.m,v
retrieving revision 1.35
diff -u -b -r1.35 stack_opt.m
--- compiler/stack_opt.m	23 Nov 2007 07:35:25 -0000	1.35
+++ compiler/stack_opt.m	12 Jan 2008 20:51:36 -0000
@@ -135,12 +135,12 @@
 
 :- type stack_opt_params
     --->    stack_opt_params(
-                matching_params     :: matching_params,
-                all_path_node_ratio :: int,
-                fixpoint_loop       :: bool,
-                full_path           :: bool,
-                on_stack            :: bool,
-                non_candidate_vars  :: set(prog_var)
+                sop_matching_params     :: matching_params,
+                sop_all_path_node_ratio :: int,
+                sop_fixpoint_loop       :: bool,
+                sop_full_path           :: bool,
+                sop_on_stack            :: bool,
+                sop_non_candidate_vars  :: set(prog_var)
             ).
 
 :- type matching_result
@@ -158,9 +158,9 @@
 
 :- type stack_opt_info
     --->    stack_opt_info(
-                stack_opt_params    :: stack_opt_params,
-                left_anchor_inserts :: insert_map,
-                matching_results    :: list(matching_result)
+                soi_stack_opt_params    :: stack_opt_params,
+                soi_left_anchor_inserts :: insert_map,
+                soi_matching_results    :: list(matching_result)
             ).
 
 stack_opt_cell(PredId, ProcId, !ProcInfo, !ModuleInfo, !IO) :-
@@ -288,7 +288,7 @@
     ;
         true
     ),
-    InsertMap = StackOptInfo ^ left_anchor_inserts,
+    InsertMap = StackOptInfo ^ soi_left_anchor_inserts,
     ( map.is_empty(InsertMap) ->
         Changed = no
     ;
@@ -368,9 +368,9 @@
     stack_opt_info::out) is det.
 
 use_cell(CellVar, FieldVarList, ConsId, Goal, !IntervalInfo, !StackOptInfo) :-
-    FlushedLater = !.IntervalInfo ^ flushed_later,
-    StackOptParams = !.StackOptInfo ^ stack_opt_params,
-    NonCandidateVars = StackOptParams ^ non_candidate_vars,
+    FlushedLater = !.IntervalInfo ^ ii_flushed_later,
+    StackOptParams = !.StackOptInfo ^ soi_stack_opt_params,
+    NonCandidateVars = StackOptParams ^ sop_non_candidate_vars,
     set.list_to_set(FieldVarList, FieldVars),
     set.intersect(FieldVars, FlushedLater, FlushedLaterFieldVars),
     set.difference(FlushedLaterFieldVars, NonCandidateVars,
@@ -381,8 +381,8 @@
         true
     ;
         ConsId = cons(_Name, _Arity),
-        IntParams = !.IntervalInfo ^ interval_params,
-        VarTypes = IntParams ^ var_types,
+        IntParams = !.IntervalInfo ^ ii_interval_params,
+        VarTypes = IntParams ^ ip_var_types,
         map.lookup(VarTypes, CellVar, Type),
         (
             type_is_tuple(Type, _)
@@ -390,7 +390,7 @@
             FreeOfCost = no
         ;
             type_to_ctor_and_args(Type, TypeCtor, _),
-            ModuleInfo = IntParams ^ module_info,
+            ModuleInfo = IntParams ^ ip_module_info,
             module_info_get_type_table(ModuleInfo, TypeTable),
             map.lookup(TypeTable, TypeCtor, TypeDefn),
             hlds_data.get_type_defn_body(TypeDefn, TypeBody),
@@ -421,7 +421,7 @@
             FreeOfCost = no,
             (
                 AfterModelNon = no,
-                OnStack = StackOptParams ^ on_stack,
+                OnStack = StackOptParams ^ sop_on_stack,
                 set.difference(CandidateArgVars0, RelevantAfterVars,
                     CandidateArgVars),
                 (
@@ -470,7 +470,7 @@
     CostNodes = set.union_list(CostNodeSets),
     set.count(BenefitNodes, NumBenefitNodes),
     set.count(CostNodes, NumCostNodes),
-    AllPathNodeRatio = StackOptParams ^ all_path_node_ratio,
+    AllPathNodeRatio = StackOptParams ^ sop_all_path_node_ratio,
     ( NumBenefitNodes * 100 >= NumCostNodes * AllPathNodeRatio ->
         ViaCellVars = ViaCellVars0
     ;
@@ -499,7 +499,7 @@
         )
     ;
         CandidateArgVars1 = set.intersect_list(PathViaCellVars),
-        FixpointLoop = StackOptParams ^ fixpoint_loop,
+        FixpointLoop = StackOptParams ^ sop_fixpoint_loop,
         (
             FixpointLoop = no,
             BenefitNodeSets = BenefitNodeSets0,
@@ -525,7 +525,7 @@
         ViaCellVars = set.init
     ;
         PathInfo = match_path_info(FirstSegment, LaterSegments),
-        MatchingParams = StackOptParams ^ matching_params,
+        MatchingParams = StackOptParams ^ sop_matching_params,
         find_via_cell_vars(CellVar, CandidateArgVars, CellVarFlushedLater,
             FirstSegment, LaterSegments, MatchingParams,
             BenefitNodes, CostNodes, ViaCellVars)
@@ -555,9 +555,9 @@
             ArgVars, ViaCellVars, GoalPath,
             PotentialIntervals, InsertIntervals,
             PotentialAnchors, InsertAnchors),
-        MatchingResults0 = !.StackOptInfo ^ matching_results,
+        MatchingResults0 = !.StackOptInfo ^ soi_matching_results,
         MatchingResults = [MatchingResult | MatchingResults0],
-        !:StackOptInfo = !.StackOptInfo ^ matching_results := MatchingResults
+        !StackOptInfo ^ soi_matching_results := MatchingResults
     ).
 
 :- pred record_cell_var_for_interval(prog_var::in, set(prog_var)::in,
@@ -582,13 +582,13 @@
 
 add_anchor_inserts(Goal, ArgVarsViaCellVar, InsertIntervals, Anchor,
         !IntervalInfo, !StackOptInfo, !InsertAnchors) :-
-    map.lookup(!.IntervalInfo ^ anchor_follow_map, Anchor, AnchorFollow),
+    map.lookup(!.IntervalInfo ^ ii_anchor_follow_map, Anchor, AnchorFollow),
     AnchorFollow = anchor_follow_info(_, AnchorIntervals),
     set.intersect(AnchorIntervals, InsertIntervals,
         AnchorInsertIntervals),
     ( set.non_empty(AnchorInsertIntervals) ->
         Insert = insert_spec(Goal, ArgVarsViaCellVar),
-        InsertMap0 = !.StackOptInfo ^ left_anchor_inserts,
+        InsertMap0 = !.StackOptInfo ^ soi_left_anchor_inserts,
         ( map.search(InsertMap0, Anchor, Inserts0) ->
             Inserts = [Insert | Inserts0],
             svmap.det_update(Anchor, Inserts, InsertMap0, InsertMap)
@@ -596,7 +596,7 @@
             Inserts = [Insert],
             svmap.det_insert(Anchor, Inserts, InsertMap0, InsertMap)
         ),
-        !:StackOptInfo = !.StackOptInfo ^ left_anchor_inserts := InsertMap,
+        !StackOptInfo ^ soi_left_anchor_inserts := InsertMap,
         svset.insert(Anchor, !InsertAnchors)
     ;
         true
@@ -694,7 +694,8 @@
 anchor_requires_close(_, anchor_proc_end) = yes.
 anchor_requires_close(IntervalInfo, anchor_branch_start(_, GoalPath)) =
         resume_save_status_requires_close(ResumeSaveStatus) :-
-    map.lookup(IntervalInfo ^ branch_resume_map, GoalPath, ResumeSaveStatus).
+    map.lookup(IntervalInfo ^ ii_branch_resume_map, GoalPath,
+        ResumeSaveStatus).
 anchor_requires_close(_, anchor_cond_then(_)) = no.
 anchor_requires_close(_, anchor_branch_end(BranchType, _)) = NeedsClose :-
     (
@@ -760,8 +761,8 @@
 
 find_all_branches_from_cur_interval(RelevantVars, MatchInfo, IntervalInfo,
         StackOptInfo) :-
-    IntervalId = IntervalInfo ^ cur_interval,
-    map.lookup(IntervalInfo ^ interval_vars, IntervalId, IntervalVars),
+    IntervalId = IntervalInfo ^ ii_cur_interval,
+    map.lookup(IntervalInfo ^ ii_interval_vars, IntervalId, IntervalVars),
     IntervalRelevantVars = set.intersect(RelevantVars, IntervalVars),
     Path0 = path(current_is_before_first_flush, IntervalRelevantVars,
         set.init, [], set.init, set.init),
@@ -783,8 +784,8 @@
 
 find_all_branches(RelevantVars, IntervalId, MaybeSearchAnchor0,
         IntervalInfo, StackOptInfo, !AllPaths) :-
-    map.lookup(IntervalInfo ^ interval_end, IntervalId, End),
-    map.lookup(IntervalInfo ^ interval_succ, IntervalId, SuccessorIds),
+    map.lookup(IntervalInfo ^ ii_interval_end, IntervalId, End),
+    map.lookup(IntervalInfo ^ ii_interval_succ, IntervalId, SuccessorIds),
     (
         SuccessorIds = [],
         expect(unify(may_have_no_successor(End), yes), this_file,
@@ -810,7 +811,7 @@
             !:AllPaths = !.AllPaths ^ used_after_scope := set.init
         ;
             End = anchor_branch_end(_, EndGoalPath),
-            map.lookup(IntervalInfo ^ branch_end_map, EndGoalPath,
+            map.lookup(IntervalInfo ^ ii_branch_end_map, EndGoalPath,
                 BranchEndInfo),
             OnStackAfterBranch = BranchEndInfo ^ flushed_after_branch,
             AccessedAfterBranch = BranchEndInfo ^ accessed_after_branch,
@@ -842,8 +843,8 @@
     ;
         AnchorRequiresClose = no
     ),
-    StackOptParams = StackOptInfo ^ stack_opt_params,
-    FullPath = StackOptParams ^ full_path,
+    StackOptParams = StackOptInfo ^ soi_stack_opt_params,
+    FullPath = StackOptParams ^ sop_full_path,
     (
         FullPath = yes,
         End = anchor_branch_start(branch_disj, EndGoalPath)
@@ -851,7 +852,8 @@
         MaybeSearchAnchor1 = yes(anchor_branch_end(branch_disj, EndGoalPath)),
         one_after_another(RelevantVars, MaybeSearchAnchor1,
             IntervalInfo, StackOptInfo, SuccessorIds, !AllPaths),
-        map.lookup(IntervalInfo ^ branch_end_map, EndGoalPath, BranchEndInfo),
+        map.lookup(IntervalInfo ^ ii_branch_end_map, EndGoalPath,
+            BranchEndInfo),
         ContinueId = BranchEndInfo ^ interval_after_branch,
         apply_interval_find_all_branches(RelevantVars, MaybeSearchAnchor0,
             IntervalInfo, StackOptInfo, ContinueId, !AllPaths)
@@ -871,11 +873,11 @@
             MaybeSearchAnchorCond, IntervalInfo, StackOptInfo,
             CondStartId, !AllPaths),
         MaybeSearchAnchorEnd = yes(anchor_branch_end(branch_ite, EndGoalPath)),
-        CondEndMap = IntervalInfo ^ cond_end_map,
+        CondEndMap = IntervalInfo ^ ii_cond_end_map,
         map.lookup(CondEndMap, EndGoalPath, ThenStartId),
         one_after_another(RelevantVars, MaybeSearchAnchorEnd,
             IntervalInfo, StackOptInfo, [ThenStartId, ElseStartId], !AllPaths),
-        map.lookup(IntervalInfo ^ branch_end_map, EndGoalPath,
+        map.lookup(IntervalInfo ^ ii_branch_end_map, EndGoalPath,
             BranchEndInfo),
         ContinueId = BranchEndInfo ^ interval_after_branch,
         apply_interval_find_all_branches(RelevantVars, MaybeSearchAnchor0,
@@ -888,7 +890,8 @@
             MaybeSearchAnchor1, IntervalInfo, StackOptInfo, !.AllPaths),
             SuccessorIds, AllPathsList),
         consolidate_after_join(AllPathsList, !:AllPaths),
-        map.lookup(IntervalInfo ^ branch_end_map, EndGoalPath, BranchEndInfo),
+        map.lookup(IntervalInfo ^ ii_branch_end_map, EndGoalPath,
+            BranchEndInfo),
         ContinueId = BranchEndInfo ^ interval_after_branch,
         apply_interval_find_all_branches(RelevantVars, MaybeSearchAnchor0,
             IntervalInfo, StackOptInfo, ContinueId, !AllPaths)
@@ -933,19 +936,19 @@
 
 apply_interval_find_all_branches(RelevantVars, MaybeSearchAnchor0,
         IntervalInfo, StackOptInfo, IntervalId, !AllPaths) :-
-    map.lookup(IntervalInfo ^ interval_vars, IntervalId, IntervalVars),
+    map.lookup(IntervalInfo ^ ii_interval_vars, IntervalId, IntervalVars),
     RelevantIntervalVars = set.intersect(RelevantVars, IntervalVars),
     !.AllPaths = all_paths(Paths0, AfterModelNon0, RelevantAfter),
     Paths1 = set.map(add_interval_to_path(IntervalId, RelevantIntervalVars),
         Paths0),
-    map.lookup(IntervalInfo ^ interval_start, IntervalId, Start),
+    map.lookup(IntervalInfo ^ ii_interval_start, IntervalId, Start),
     (
         % Check if intervals starting at Start use any RelevantVars.
         ( Start = anchor_call_site(_)
         ; Start = anchor_branch_end(_, _)
         ; Start = anchor_branch_start(_, _)
         ),
-        map.search(IntervalInfo ^ anchor_follow_map, Start, StartInfo),
+        map.search(IntervalInfo ^ ii_anchor_follow_map, Start, StartInfo),
         StartInfo = anchor_follow_info(AnchorFollowVars, _),
         set.intersect(RelevantVars, AnchorFollowVars, NeededVars),
         set.non_empty(NeededVars)
@@ -954,7 +957,7 @@
     ;
         Paths2 = Paths1
     ),
-    ( set.member(Start, IntervalInfo ^ model_non_anchors) ->
+    ( set.member(Start, IntervalInfo ^ ii_model_non_anchors) ->
         AfterModelNon = yes
     ;
         AfterModelNon = AfterModelNon0
@@ -1019,12 +1022,12 @@
 :- pred dump_stack_opt_info(stack_opt_info::in, io::di, io::uo) is det.
 
 dump_stack_opt_info(StackOptInfo, !IO) :-
-    map.to_assoc_list(StackOptInfo ^ left_anchor_inserts, Inserts),
+    map.to_assoc_list(StackOptInfo ^ soi_left_anchor_inserts, Inserts),
     io.write_string("\nANCHOR INSERT:\n", !IO),
     list.foldl(dump_anchor_inserts, Inserts, !IO),
 
     io.write_string("\nMATCHING RESULTS:\n", !IO),
-    list.foldl(dump_matching_result, StackOptInfo ^ matching_results, !IO),
+    list.foldl(dump_matching_result, StackOptInfo ^ soi_matching_results, !IO),
     io.write_string("\n", !IO).
 
 :- pred dump_anchor_inserts(pair(anchor, list(insert_spec))::in,
Index: compiler/store_alloc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/store_alloc.m,v
retrieving revision 1.108
diff -u -b -r1.108 store_alloc.m
--- compiler/store_alloc.m	21 Jan 2008 00:32:53 -0000	1.108
+++ compiler/store_alloc.m	21 Jan 2008 00:33:45 -0000
@@ -118,8 +118,8 @@
 
 :- type store_alloc_info
     --->    store_alloc_info(
-                module_info     :: module_info,
-                stack_slots     :: stack_slots
+                sai_module_info     :: module_info,
+                sai_stack_slots     :: stack_slots
                                 % Maps each var to its stack slot
                                 % (if it has one).
             ).
Index: compiler/structure_reuse.direct.choose_reuse.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/structure_reuse.direct.choose_reuse.m,v
retrieving revision 1.12
diff -u -b -r1.12 structure_reuse.direct.choose_reuse.m
--- compiler/structure_reuse.direct.choose_reuse.m	14 Jan 2008 04:43:25 -0000	1.12
+++ compiler/structure_reuse.direct.choose_reuse.m	15 Jan 2008 03:55:49 -0000
@@ -140,10 +140,10 @@
     %
 :- type background_info
     --->    background(
-                strategy    :: reuse_strategy,
-                module_info :: module_info,
-                proc_info   :: proc_info,
-                vartypes    :: vartypes
+                back_strategy       :: reuse_strategy,
+                back_module_info    :: module_info,
+                back_proc_info      :: proc_info,
+                back_vartypes       :: vartypes
             ).
 
 :- func background_info_init(reuse_strategy, module_info, proc_info) =
@@ -309,21 +309,22 @@
     (
         Conditions = [First | Rest],
         list.foldl(
-            reuse_as_least_upper_bound(Background ^ module_info,
-                Background ^ proc_info),
+            reuse_as_least_upper_bound(Background ^ back_module_info,
+                Background ^ back_proc_info),
             Rest, First, Condition)
     ;
         Conditions = [],
-        unexpected(choose_reuse.this_file, "match_get_condition: " ++
-            "no reuse conditions.\n")
+        unexpected(choose_reuse.this_file,
+            "match_get_condition: no reuse conditions.\n")
     ).
 
     % Add a construction as a potential place for reusing the garbage
     % produced by any of the deconstructions listed in the match.
     % This changes the value of the match.
     %
-:- pred match_add_construction(construction_spec::in, match::in,
-        match::out) is det.
+:- pred match_add_construction(construction_spec::in,
+    match::in, match::out) is det.
+
 match_add_construction(ConSpec, Match0, Match) :-
     Match0 = match(DeconSpecs0, ConSpecs0, Value0, Degree0),
     ConSpecs = [ConSpec | ConSpecs0],
@@ -483,8 +484,8 @@
         % Add the conditions involved in the reuses to the existing
         % conditions.
         %
-        ModuleInfo = Background ^ module_info,
-        ProcInfo   = Background ^ proc_info,
+        ModuleInfo = Background ^ back_module_info,
+        ProcInfo   = Background ^ back_proc_info,
         reuse_as_least_upper_bound(ModuleInfo, ProcInfo,
             match_get_condition(Background, Match), !ReuseAs),
 
@@ -552,8 +553,7 @@
 
             ProgramPoint = program_point_init(GoalInfo),
             (
-                Condition = dead_cell_table_search(ProgramPoint,
-                    DeadCellTable)
+                Condition = dead_cell_table_search(ProgramPoint, DeadCellTable)
             ->
                 ReuseAs = reuse_as_init_with_one_condition(Condition),
                 DeconstructionSpec = deconstruction_spec_init(Var,
@@ -601,7 +601,7 @@
             !IO)
     ;
         GoalExpr = negation(Goal),
-        % if Goal contains deconstructions, they should not be reused within
+        % If Goal contains deconstructions, they should not be reused within
         % Cont.
         compute_match_table_with_continuation(Background, DeadCellTable,
             Goal, [], !Table, !IO),
@@ -627,8 +627,8 @@
             !Table, !IO)
     ;
         GoalExpr = shorthand(_),
-        unexpected(choose_reuse.this_file, "compute_match_table: " ++
-            "shorthand goal.")
+        unexpected(choose_reuse.this_file,
+            "compute_match_table: shorthand goal.")
     ).
 
 :- pred compute_match_table_in_disjs(background_info::in, dead_cell_table::in,
@@ -668,11 +668,11 @@
         ExtraTables, !IO) :-
     CommonDeadVars = common_vars(DisjTables),
     (
-        CommonDeadVars = [_ | _]
-    ->
+        CommonDeadVars = [_ | _],
         list.filter_map(process_common_var(Background, Cont, DisjTables),
             CommonDeadVars, ExtraTables)
     ;
+        CommonDeadVars = [],
         ExtraTables = []
     ).
 
@@ -680,7 +680,7 @@
 
 common_vars(Tables) = CommonVars :-
     (
-        Tables = [ First | RestTables ],
+        Tables = [First | RestTables],
         CommonVars = list.foldl(common_var_with_list, RestTables,
             map.keys(First))
     ;
@@ -911,8 +911,8 @@
         ReuseType) :-
     DeconSpec = decon(DeadVar, _, DeadCons, DeadCellArgs, _),
 
-    ModuleInfo = Background ^ module_info,
-    Vartypes = Background ^ vartypes,
+    ModuleInfo = Background ^ back_module_info,
+    Vartypes = Background ^ back_vartypes,
     NewNumArgs = list.length(NewCellArgs),
     DeadNumArgs = list.length(DeadCellArgs),
 
@@ -930,7 +930,7 @@
 
     % Verify whether the cons_ids and arities match the reuse constraint
     % specified by the user.
-    Constraint = Background ^ strategy,
+    Constraint = Background ^ back_strategy,
     DiffArity = DeadArity - NewArity,
     ( NewCons = DeadCons -> SameCons = yes ; SameCons = no),
     (
@@ -961,7 +961,6 @@
     Weight > 0,
     ReuseType = reuse_type(SameCons, ReuseFields, float(Weight)).
 
-
 :- func glb_reuse_types(list(reuse_type)) = reuse_type is semidet.
 
 glb_reuse_types([First|Rest]) =
@@ -997,7 +996,6 @@
 needs_update_and(does_not_need_update, does_not_need_update) =
     does_not_need_update.
 
-
 %-----------------------------------------------------------------------------%
 
     % has_secondary_tag(Var, ConsId, HasSecTag) returns `yes' iff the
Index: compiler/term_pass1.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_pass1.m,v
retrieving revision 1.39
diff -u -b -r1.39 term_pass1.m
--- compiler/term_pass1.m	21 Jan 2008 00:32:55 -0000	1.39
+++ compiler/term_pass1.m	21 Jan 2008 01:13:37 -0000
@@ -35,14 +35,14 @@
 %-----------------------------------------------------------------------------%
 
 :- type arg_size_result
-    --->    ok(
-                list(pair(pred_proc_id, int)),
+    --->    arg_size_ok(
                 % Gives the gamma of each procedure in the SCC.
+                list(pair(pred_proc_id, int)),
 
-                used_args
                 % Gives the output suppliers of each procedure in the SCC.
+                used_args
             )
-    ;       error(
+    ;       arg_size_error(
                 list(termination_error_context)
             ).
 
@@ -77,8 +77,8 @@
 %-----------------------------------------------------------------------------%
 
 :- type pass1_result
-    --->    ok(
-                list(path_info),
+    --->    term_pass1_ok(
+                list(term_path_info),
                         % One entry for each path through the
                         % code.
                 used_args,
@@ -88,7 +88,7 @@
                         % the SCC in which the set of active vars is not a
                         % subset of the input arguments.
             )
-    ;       error(
+    ;       term_pass1_error(
                 list(termination_error_context)
             ).
 
@@ -97,35 +97,35 @@
     find_arg_sizes_in_scc_fixpoint(SCC, PassInfo,
         InitOutputSupplierMap, Result, TermErrors, !ModuleInfo, !IO),
     (
-        Result = ok(Paths, OutputSupplierMap, SubsetErrors),
+        Result = term_pass1_ok(Paths, OutputSupplierMap, SubsetErrors),
         (
             SubsetErrors = [_ | _],
-            ArgSize = error(SubsetErrors)
+            ArgSize = arg_size_error(SubsetErrors)
         ;
             SubsetErrors = [],
             (
                 Paths = [],
                 get_context_from_scc(SCC, !.ModuleInfo, Context),
                 ArgSizeError = termination_error_context(no_eqns, Context),
-                ArgSize = error([ArgSizeError])
+                ArgSize = arg_size_error([ArgSizeError])
             ;
                 Paths = [_ | _],
                 solve_equations(Paths, SCC, MaybeSolution, !IO),
                 (
                     MaybeSolution = yes(Solution),
-                    ArgSize = ok(Solution, OutputSupplierMap)
+                    ArgSize = arg_size_ok(Solution, OutputSupplierMap)
                 ;
                     MaybeSolution = no,
                     get_context_from_scc(SCC, !.ModuleInfo, Context),
                     ArgSizeError = termination_error_context(solver_failed,
                         Context),
-                    ArgSize = error([ArgSizeError])
+                    ArgSize = arg_size_error([ArgSizeError])
                 )
             )
         )
     ;
-        Result = error(Errors),
-        ArgSize = error(Errors)
+        Result = term_pass1_error(Errors),
+        ArgSize = arg_size_error(Errors)
     ).
 
 %-----------------------------------------------------------------------------%
@@ -159,11 +159,11 @@
     find_arg_sizes_in_scc_pass(SCC, PassInfo, OutputSupplierMap0, [], [],
         Result0, [], TermErrors0, !ModuleInfo, !IO),
     (
-        Result0 = error(_),
+        Result0 = term_pass1_error(_),
         Result = Result0,
         TermErrors = TermErrors0
     ;
-        Result0 = ok(_, OutputSupplierMap1, _),
+        Result0 = term_pass1_ok(_, OutputSupplierMap1, _),
         ( OutputSupplierMap1 = OutputSupplierMap0 ->
             Result = Result0,
             TermErrors = TermErrors0
@@ -174,14 +174,14 @@
     ).
 
 :- pred find_arg_sizes_in_scc_pass(list(pred_proc_id)::in,
-    pass_info::in, used_args::in, list(path_info)::in,
+    pass_info::in, used_args::in, list(term_path_info)::in,
     termination_error_contexts::in, pass1_result::out,
     termination_error_contexts::in, termination_error_contexts::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
 find_arg_sizes_in_scc_pass([], _, OutputSupplierMap, Paths, SubsetErrors,
         Result, !TermErrors, !ModuleInfo, !IO) :-
-    Result = ok(Paths, OutputSupplierMap, SubsetErrors).
+    Result = term_pass1_ok(Paths, OutputSupplierMap, SubsetErrors).
 find_arg_sizes_in_scc_pass([PPId | PPIds], PassInfo,
         OutputSupplierMap0, Paths0, SubsetErrors0, Result,
         !TermErrors, !ModuleInfo, !IO) :-
@@ -191,7 +191,7 @@
     PassInfo = pass_info(_, MaxErrors, _),
     list.take_upto(MaxErrors, !TermErrors),
     (
-        Result1 = error(_),
+        Result1 = term_pass1_error(_),
         Result = Result1,
 
         % The error does not necessarily mean that this SCC is nonterminating.
@@ -204,7 +204,7 @@
             OtherTermErrors, !ModuleInfo, !IO),
         list.append(OtherTermErrors, !TermErrors)
     ;
-        Result1 = ok(Paths1, OutputSupplierMap1, SubsetErrors1),
+        Result1 = term_pass1_ok(Paths1, OutputSupplierMap1, SubsetErrors1),
         Paths = Paths0 ++ Paths1,
         SubsetErrors = SubsetErrors0 ++ SubsetErrors1,
         find_arg_sizes_in_scc_pass(PPIds, PassInfo,
@@ -233,17 +233,17 @@
     Goal = maybe_strip_equality_pretest(Goal0),
     map.init(EmptyMap),
     PassInfo = pass_info(FunctorInfo, MaxErrors, MaxPaths),
-    init_traversal_params(FunctorInfo, PPId, Context, VarTypes,
+    init_term_traversal_params(FunctorInfo, PPId, Context, VarTypes,
         OutputSupplierMap0, EmptyMap, MaxErrors, MaxPaths, Params),
 
     partition_call_args(!.ModuleInfo, ArgModes, Args, InVars, OutVars),
-    Path0 = path_info(PPId, no, 0, [], OutVars),
+    Path0 = term_path_info(PPId, no, 0, [], OutVars),
     set.singleton_set(PathSet0, Path0),
-    Info0 = ok(PathSet0, []),
-    traverse_goal(Goal, Params, Info0, Info, !ModuleInfo, !IO),
+    Info0 = term_traversal_ok(PathSet0, []),
+    term_traverse_goal(Goal, Params, Info0, Info, !ModuleInfo, !IO),
 
     (
-        Info = ok(Paths, TermErrors),
+        Info = term_traversal_ok(Paths, TermErrors),
         set.to_sorted_list(Paths, PathList),
         upper_bound_active_vars(PathList, AllActiveVars),
         map.lookup(OutputSupplierMap0, PPId, OutputSuppliers0),
@@ -259,10 +259,10 @@
                 Context),
             SubsetErrors = [SubsetErrorContext]
         ),
-        Result = ok(PathList, OutputSupplierMap, SubsetErrors)
+        Result = term_pass1_ok(PathList, OutputSupplierMap, SubsetErrors)
     ;
-        Info = error(Errors, TermErrors),
-        Result = error(Errors)
+        Info = term_traversal_error(Errors, TermErrors),
+        Result = term_pass1_error(Errors)
     ).
 
 :- pred update_output_suppliers(list(prog_var)::in, bag(prog_var)::in,
@@ -281,9 +281,9 @@
     ( bag.contains(ActiveVars, Arg) ->
         OutputSupplier = yes
     ;
-        % This guarantees that the set of output suppliers can only
-        % increase, which in turn guarantees that our fixpoint
-        % computation is monotonic and therefore terminates.
+        % This guarantees that the set of output suppliers can only increase,
+        % which in turn guarantees that our fixpoint computation is
+        % monotonic and therefore terminates.
         OutputSupplier = OutputSupplier0
     ),
     update_output_suppliers(Args, ActiveVars,
@@ -396,7 +396,7 @@
 % Solve the list of constraints
 %
 
-:- pred solve_equations(list(path_info)::in, list(pred_proc_id)::in,
+:- pred solve_equations(list(term_path_info)::in, list(pred_proc_id)::in,
     maybe(list(pair(pred_proc_id, int)))::out, io::di, io::uo) is det.
 
 solve_equations(Paths, PPIds, Result, !IO) :-
@@ -416,8 +416,8 @@
         Result = no
     ).
 
-:- pred convert_equations(list(path_info)::in, varset::out, lp.equations::out,
-    objective::out, map(pred_proc_id, var)::out) is semidet.
+:- pred convert_equations(list(term_path_info)::in, varset::out,
+    lp.equations::out, objective::out, map(pred_proc_id, var)::out) is semidet.
 
 convert_equations(Paths, Varset, Equations, Objective, PPVars) :-
     varset.init(Varset0),
@@ -430,14 +430,14 @@
     Convert = (pred(Var::in, Coeff::out) is det :- Coeff = Var - 1.0),
     list.map(Convert, Vars, Objective).
 
-:- pred convert_equations_2(list(path_info)::in,
+:- pred convert_equations_2(list(term_path_info)::in,
     map(pred_proc_id, var)::in, map(pred_proc_id, var)::out,
     varset::in, varset::out,
     set(lp.equation)::in, set(lp.equation)::out) is semidet.
 
 convert_equations_2([], !PPVars, !Varset, !Eqns).
 convert_equations_2([Path | Paths], !PPVars, !Varset, !Eqns) :-
-    Path = path_info(ThisPPId, _, IntGamma, PPIds, _),
+    Path = term_path_info(ThisPPId, _, IntGamma, PPIds, _),
     FloatGamma = float(IntGamma),
     Eqn = eqn(Coeffs, (>=), FloatGamma),
     pred_proc_var(ThisPPId, ThisVar, !Varset, !PPVars),
Index: compiler/term_pass2.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_pass2.m,v
retrieving revision 1.32
diff -u -b -r1.32 term_pass2.m
--- compiler/term_pass2.m	23 Nov 2007 07:35:28 -0000	1.32
+++ compiler/term_pass2.m	12 Jan 2008 23:51:02 -0000
@@ -73,12 +73,12 @@
 :- type call_weight_graph == map(pred_proc_id, call_weight_dst_map).
 :- type call_weight_dst_map == map(pred_proc_id, pair(prog_context, int)).
 
-:- type pass2_result
-    --->    ok(
+:- type term_pass2_result
+    --->    term_pass2_ok(
                 call_weight_info,
                 used_args
             )
-    ;       error(
+    ;       term_pass2_error(
                 termination_error_contexts
             ).
 
@@ -309,7 +309,7 @@
     prove_termination_in_scc_fixpoint(SCC, FixDir, PassInfo,
         InitRecSuppliers, Result, !ModuleInfo, !IO),
     (
-        Result = ok(CallInfo, _),
+        Result = term_pass2_ok(CallInfo, _),
         CallInfo = call_weight_info(InfCalls, CallWeights),
         (
             InfCalls = [_ | _],
@@ -331,14 +331,14 @@
             )
         )
     ;
-        Result = error(Errors),
+        Result = term_pass2_error(Errors),
         Termination = can_loop(Errors)
     ).
 
 %-----------------------------------------------------------------------------%
 
 :- pred prove_termination_in_scc_fixpoint(list(pred_proc_id)::in,
-    fixpoint_dir::in, pass_info::in, used_args::in, pass2_result::out,
+    fixpoint_dir::in, pass_info::in, used_args::in, term_pass2_result::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
 prove_termination_in_scc_fixpoint(SCC, FixDir, PassInfo,
@@ -350,7 +350,7 @@
         RecSupplierMap0, NewRecSupplierMap0, CallInfo0, Result1, !ModuleInfo,
         !IO),
     (
-        Result1 = ok(_, RecSupplierMap1),
+        Result1 = term_pass2_ok(_, RecSupplierMap1),
         ( RecSupplierMap1 = RecSupplierMap0 ->
             % We are at a fixed point, so further analysis
             % will not get any better results.
@@ -360,7 +360,7 @@
                 PassInfo, RecSupplierMap1, Result, !ModuleInfo, !IO)
         )
     ;
-        Result1 = error(_),
+        Result1 = term_pass2_error(_),
         Result = Result1
     ).
 
@@ -371,11 +371,11 @@
     %
 :- pred prove_termination_in_scc_pass(list(pred_proc_id)::in, fixpoint_dir::in,
     pass_info::in, used_args::in, used_args::in,
-    call_weight_info::in, pass2_result::out, module_info::in, module_info::out,
-    io::di, io::uo) is det.
+    call_weight_info::in, term_pass2_result::out,
+    module_info::in, module_info::out, io::di, io::uo) is det.
 
 prove_termination_in_scc_pass([], _, _, _, NewRecSupplierMap, CallInfo,
-        ok(CallInfo, NewRecSupplierMap), !ModuleInfo, !IO).
+        term_pass2_ok(CallInfo, NewRecSupplierMap), !ModuleInfo, !IO).
 prove_termination_in_scc_pass([PPId | PPIds], FixDir, PassInfo,
         RecSupplierMap, NewRecSupplierMap0, CallInfo0, Result,
         !ModuleInfo, !IO) :-
@@ -390,13 +390,13 @@
     proc_info_get_vartypes(ProcInfo, VarTypes),
     map.init(EmptyMap),
     PassInfo = pass_info(FunctorInfo, MaxErrors, MaxPaths),
-    init_traversal_params(FunctorInfo, PPId, Context, VarTypes,
+    init_term_traversal_params(FunctorInfo, PPId, Context, VarTypes,
         EmptyMap, RecSupplierMap, MaxErrors, MaxPaths, Params),
     set.init(PathSet0),
-    Info0 = ok(PathSet0, []),
-    traverse_goal(Goal, Params, Info0, Info, !ModuleInfo, !IO),
+    Info0 = term_traversal_ok(PathSet0, []),
+    term_traverse_goal(Goal, Params, Info0, Info, !ModuleInfo, !IO),
     (
-        Info = ok(Paths, CanLoop),
+        Info = term_traversal_ok(Paths, CanLoop),
         expect(unify(CanLoop, []), this_file,
             "can_loop detected in pass2 but not pass1"),
         set.to_sorted_list(Paths, PathList),
@@ -414,10 +414,10 @@
             PassInfo, RecSupplierMap, NewRecSupplierMap1, CallInfo1, Result,
             !ModuleInfo, !IO)
     ;
-        Info = error(Errors, CanLoop),
+        Info = term_traversal_error(Errors, CanLoop),
         expect(unify(CanLoop, []), this_file, 
             "can_loop detected in pass2 but not pass1"),
-        Result = error(Errors)
+        Result = term_pass2_error(Errors)
     ).
 
 %-----------------------------------------------------------------------------%
@@ -475,12 +475,12 @@
     % p. If there is no finite upper bound, then we insert the details of the
     % call into the list of "infinite" calls.
     %
-:- pred add_call_arcs(list(path_info)::in, bag(prog_var)::in,
+:- pred add_call_arcs(list(term_path_info)::in, bag(prog_var)::in,
     call_weight_info::in, call_weight_info::out) is det.
 
 add_call_arcs([], _RecInputSuppliers, !CallInfo).
 add_call_arcs([Path | Paths], RecInputSuppliers, !CallInfo) :-
-    Path = path_info(PPId, CallSite, GammaConst, GammaVars, ActiveVars),
+    Path = term_path_info(PPId, CallSite, GammaConst, GammaVars, ActiveVars),
     (
         CallSite = yes(CallPPIdPrime - ContextPrime),
         CallPPId = CallPPIdPrime,
Index: compiler/term_traversal.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/term_traversal.m,v
retrieving revision 1.59
diff -u -b -r1.59 term_traversal.m
--- compiler/term_traversal.m	21 Jan 2008 00:32:55 -0000	1.59
+++ compiler/term_traversal.m	21 Jan 2008 04:14:26 -0000
@@ -37,75 +37,71 @@
 
 %-----------------------------------------------------------------------------%
 
-:- type traversal_info
-    --->    ok(
-                set(path_info),
-                    % Information about the paths we have followed. With
-                    % a conjunction of length N, each of whose elements
-                    % is a branched control structure, the number of
-                    % paths through the conjunction is 2^N. The reason
-                    % why we use a set of path_infos instead of a list
-                    % is that this can postpone the representation
-                    % getting too big if (as is at least moderately
-                    % likely) many of the paths have identical
+:- type term_traversal_info
+    --->    term_traversal_ok(
+                % Information about the paths we have followed. With a
+                % conjunction of length N, each of whose elements is a
+                % branched control structure, the number of paths through
+                % the conjunction is 2^N. The reason why we use a set of
+                % term_path_infos instead of a list is that this can postpone
+                % the representation getting too big if (as is at least
+                % moderately likely) many of the paths have identical
                     % properties.
+                set(term_path_info),
                 
+                % Have we processed a call to a procedure whose maybe
+                % termination info was yes(can_loop(_))? If yes, record
+                % the error here. (This is not an error in pass 1, but
+                % we want to find this out in pass 1 so we can avoid
+                % doing pass 2.)
                 list(termination_error_context)
-                    % Have we processed a call to a procedure whose
-                    % maybe termination info was yes(can_loop(_))?  If
-                    % yes, record the error here.  (This is not an error
-                    % in pass 1, but we want to find this out in pass 1
-                    % so we can avoid doing pass 2.)
         )
-    ;   
-        error(
-                list(termination_error_context),
+    ;       term_traversal_error(
                     % Errors which are fatal in both passes.
+                list(termination_error_context),
                 
+                % Have we processed a call to a procedure whose maybe
+                % termination info was yes(can_loop(_))? If yes, record
+                % the error here. (This is not an error in pass 1, but
+                % we want to find this out in pass 1 so we can avoid
+                % doing pass 2.)
                 list(termination_error_context)
-                    % Have we processed a call to a procedure whose
-                    % maybe termination info was yes(can_loop(_))?  If
-                    % yes, record the error here.  (This is not an error
-                    % in pass 1, but we want to find this out in pass 1
-                    % so we can avoid doing pass 2.)
         ).
 
-:- type path_info
-    --->    path_info(
-            
+:- type term_path_info
+    --->    term_path_info(
+                % The identity of the procedure that this path is within.
                 pred_proc_id,
-                    % The identify of the procedure
-                    % that this path is within.
             
-                maybe(pair(pred_proc_id, prog_context)),
-                    % If no, path was started at the end
-                    % of the procedure given by field 1.
-                    % If yes, the arg names the procedure
-                    % at the call to which the path started
-                    % and the context of the call.
+                % If no, path was started at the end of the procedure
+                % given by field 1. If yes, the arg names the procedure
+                % at the call to which the path started and the context
+                % of the call.
+                %
                     % In pass 1, all starts should be no.
                     % In pass 2, all starts should be yes.
+                maybe(pair(pred_proc_id, prog_context)),
             
+                % These three fields describe the right hand side
+                % of the inequation we are propagating.
                 int,
                 list(pred_proc_id),
                 bag(prog_var)
-                    % These three fields describe the right hand side
-                    % of the inequation we are propagating.
         ).
 
-:- type traversal_params.
+:- type term_traversal_params.
 
-:- pred init_traversal_params(functor_info::in,
+:- pred init_term_traversal_params(functor_info::in,
     pred_proc_id::in, prog_context::in, vartypes::in,
     used_args::in, used_args::in, int::in, int::in,
-    traversal_params::out) is det.
+    term_traversal_params::out) is det.
 
-:- pred traverse_goal(
-    hlds_goal::in, traversal_params::in,
-    traversal_info::in, traversal_info::out,
+:- pred term_traverse_goal(hlds_goal::in, term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
-:- pred upper_bound_active_vars(list(path_info)::in, bag(prog_var)::out) is det.
+:- pred upper_bound_active_vars(list(term_path_info)::in, bag(prog_var)::out)
+    is det.
 
 %-----------------------------------------------------------------------------%
 %-----------------------------------------------------------------------------%
@@ -123,7 +119,7 @@
 
 %-----------------------------------------------------------------------------%
 
-traverse_goal(Goal, Params, !Info, !ModuleInfo, !IO) :-
+term_traverse_goal(Goal, Params, !Info, !ModuleInfo, !IO) :-
     Goal = hlds_goal(GoalExpr, GoalInfo),
     (
         Detism = goal_info_get_determinism(GoalInfo),
@@ -238,7 +234,7 @@
             % In pass 1, RecInputSuppliersMap will be empty.
             compute_rec_start_vars(Args, RecInputSuppliers, Bag),
             PathStart = yes(CallPPId - Context),
-            NewPath = path_info(PPId, PathStart, 0, [], Bag),
+            NewPath = term_path_info(PPId, PathStart, 0, [], Bag),
             add_path(NewPath, !Info)
         ;
             true
@@ -313,18 +309,18 @@
     ;
         GoalExpr = conj(_, Goals),
         list.reverse(Goals, RevGoals),
-        traverse_conj(RevGoals, Params, !Info, !ModuleInfo, !IO)
+        term_traverse_conj(RevGoals, Params, !Info, !ModuleInfo, !IO)
     ;
         GoalExpr = disj(Goals),
-        traverse_disj(Goals, Params, !Info, !ModuleInfo, !IO)
+        term_traverse_disj(Goals, Params, !Info, !ModuleInfo, !IO)
     ;
         GoalExpr = switch(_, _, Cases),
-        traverse_switch(Cases, Params, !Info, !ModuleInfo, !IO)
+        term_traverse_switch(Cases, Params, !Info, !ModuleInfo, !IO)
     ;
         GoalExpr = if_then_else(_, Cond, Then, Else),
-        traverse_conj([Then, Cond], Params, !.Info, CondThenInfo,
+        term_traverse_conj([Then, Cond], Params, !.Info, CondThenInfo,
             !ModuleInfo, !IO),
-        traverse_goal(Else, Params, !.Info, ElseInfo, !ModuleInfo, !IO),
+        term_traverse_goal(Else, Params, !.Info, ElseInfo, !ModuleInfo, !IO),
         combine_paths(CondThenInfo, ElseInfo, Params, !:Info)
     ;
         GoalExpr = negation(SubGoal),
@@ -332,10 +328,10 @@
         % it cannot bind any active variables. However, we must traverse it
         % during pass 1 to ensure that it does not call any non-terminating
         % procedures. Pass 2 relies on pass 1 having done this.
-        traverse_goal(SubGoal, Params, !Info, !ModuleInfo, !IO)
+        term_traverse_goal(SubGoal, Params, !Info, !ModuleInfo, !IO)
     ;
         GoalExpr = scope(_, SubGoal),
-        traverse_goal(SubGoal, Params, !Info, !ModuleInfo, !IO)
+        term_traverse_goal(SubGoal, Params, !Info, !ModuleInfo, !IO)
     ;
         GoalExpr = shorthand(_),
         % These should have been expanded out by now.
@@ -347,102 +343,131 @@
     % traverse_conj should be invoked with a reversed list of goals.
     % This is to keep stack consumption down.
     %
-:- pred traverse_conj(hlds_goals::in, traversal_params::in,
-    traversal_info::in, traversal_info::out,
+:- pred term_traverse_conj(hlds_goals::in, term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
-traverse_conj([], _, !Info, !ModuleInfo, !IO).
-traverse_conj([Goal | Goals], Params, !Info, !ModuleInfo, !IO) :-
-    traverse_goal(Goal, Params, !Info, !ModuleInfo, !IO),
-    traverse_conj(Goals, Params, !Info, !ModuleInfo, !IO).
-
-:- pred traverse_disj(hlds_goals::in, traversal_params::in,
-    traversal_info::in, traversal_info::out, module_info::in,
-    module_info::out, io::di, io::uo) is det.
+term_traverse_conj([], _, !Info, !ModuleInfo, !IO).
+term_traverse_conj([Goal | Goals], Params, !Info, !ModuleInfo, !IO) :-
+    term_traverse_goal(Goal, Params, !Info, !ModuleInfo, !IO),
+    term_traverse_conj(Goals, Params, !Info, !ModuleInfo, !IO).
+
+:- pred term_traverse_disj(hlds_goals::in, term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out,
+    module_info::in, module_info::out, io::di, io::uo) is det.
 
-traverse_disj([], _, _, ok(Empty, []), !ModuleInfo, !IO) :-
+term_traverse_disj([], _, _, term_traversal_ok(Empty, []), !ModuleInfo, !IO) :-
     set.init(Empty).
-traverse_disj([Goal | Goals], Params, !Info, !ModuleInfo, !IO) :-
-    traverse_goal(Goal, Params, !.Info, GoalInfo, !ModuleInfo, !IO),
-    traverse_disj(Goals, Params, !.Info, GoalsInfo, !ModuleInfo, !IO),
+term_traverse_disj([Goal | Goals], Params, !Info, !ModuleInfo, !IO) :-
+    term_traverse_goal(Goal, Params, !.Info, GoalInfo, !ModuleInfo, !IO),
+    term_traverse_disj(Goals, Params, !.Info, GoalsInfo, !ModuleInfo, !IO),
     combine_paths(GoalInfo, GoalsInfo, Params, !:Info).
 
-:- pred traverse_switch(list(case)::in, traversal_params::in,
-    traversal_info::in, traversal_info::out,
+:- pred term_traverse_switch(list(case)::in, term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out,
     module_info::in, module_info::out, io::di, io::uo) is det.
 
-traverse_switch([], _, _, ok(Empty, []), !ModuleInfo, !IO) :-
+term_traverse_switch([], _, _, term_traversal_ok(Empty, []),
+        !ModuleInfo, !IO) :-
     set.init(Empty).
-traverse_switch([case(_, _, Goal) | Cases], Params, !Info, !ModuleInfo, !IO) :-
-    traverse_goal(Goal, Params, !.Info, GoalInfo, !ModuleInfo, !IO),
-    traverse_switch(Cases, Params, !.Info, CasesInfo, !ModuleInfo, !IO),
+term_traverse_switch([case(_, _, Goal) | Cases], Params, !Info,
+        !ModuleInfo, !IO) :-
+    term_traverse_goal(Goal, Params, !.Info, GoalInfo, !ModuleInfo, !IO),
+    term_traverse_switch(Cases, Params, !.Info, CasesInfo, !ModuleInfo, !IO),
     combine_paths(GoalInfo, CasesInfo, Params, !:Info).
 
 %-----------------------------------------------------------------------------%
 
-:- pred cannot_succeed(traversal_info::in, traversal_info::out) is det.
+:- pred cannot_succeed(term_traversal_info::in, term_traversal_info::out)
+    is det.
 
-cannot_succeed(error(Errors, CanLoop), error(Errors, CanLoop)).
-cannot_succeed(ok(_, CanLoop), ok(Empty, CanLoop)) :-
-    set.init(Empty).
+cannot_succeed(Info0, Info) :-
+    (
+        Info0 = term_traversal_error(_, _),
+        Info = Info0
+    ;
+        Info0 = term_traversal_ok(_, CanLoop),
+        Info = term_traversal_ok(set.init, CanLoop)
+    ).
 
-:- pred add_path(path_info::in, traversal_info::in, traversal_info::out) is det.
+:- pred add_path(term_path_info::in,
+    term_traversal_info::in, term_traversal_info::out) is det.
 
-add_path(_, error(Errors, CanLoop), error(Errors, CanLoop)).
-add_path(Path, ok(Paths0, CanLoop), ok(Paths, CanLoop)) :-
-    set.insert(Paths0, Path, Paths).
+add_path(Path, Info0, Info) :-
+    (
+        Info0 = term_traversal_error(_, _),
+        Info = Info0
+    ;
+        Info0 = term_traversal_ok(Paths0, CanLoop),
+        set.insert(Paths0, Path, Paths),
+        Info = term_traversal_ok(Paths, CanLoop)
+    ).
 
 :- pred add_error(prog_context::in, termination_error::in,
-    traversal_params::in, traversal_info::in, traversal_info::out) is det.
+    term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out) is det.
 
-add_error(Context, Error, Params, error(Errors0, CanLoop),
-        error(Errors, CanLoop)) :-
+add_error(Context, Error, Params, Info0, Info) :-
+    (
+        Info0 = term_traversal_error(Errors0, CanLoop),
     Errors1 = [termination_error_context(Error, Context) | Errors0],
     params_get_max_errors(Params, MaxErrors),
-    list.take_upto(MaxErrors, Errors1, Errors).
-add_error(Context, Error, _, ok(_, CanLoop),
-        error([termination_error_context(Error, Context)], CanLoop)).
+        list.take_upto(MaxErrors, Errors1, Errors),
+        Info = term_traversal_error(Errors, CanLoop)
+    ;
+        Info0 = term_traversal_ok(_, CanLoop),
+        ErrorContext = termination_error_context(Error, Context),
+        Info = term_traversal_error([ErrorContext], CanLoop)
+    ).
 
 :- pred called_can_loop(prog_context::in, termination_error::in,
-    traversal_params::in, traversal_info::in, traversal_info::out) is det.
+    term_traversal_params::in,
+    term_traversal_info::in, term_traversal_info::out) is det.
 
-called_can_loop(Context, Error, Params, error(Errors, CanLoop0),
-        error(Errors, CanLoop)) :-
+called_can_loop(Context, Error, Params, Info0, Info) :-
+    (
+        Info0 = term_traversal_error(Errors, CanLoop0),
     CanLoop1 = [termination_error_context(Error, Context) | CanLoop0],
     params_get_max_errors(Params, MaxErrors),
-    list.take_upto(MaxErrors, CanLoop1, CanLoop).
-called_can_loop(Context, Error, Params, ok(Paths, CanLoop0),
-        ok(Paths, CanLoop)) :-
+        list.take_upto(MaxErrors, CanLoop1, CanLoop),
+        Info = term_traversal_error(Errors, CanLoop)
+    ;
+        Info0 = term_traversal_ok(Paths, CanLoop0),
     CanLoop1 = [termination_error_context(Error, Context) | CanLoop0],
     params_get_max_errors(Params, MaxErrors),
-    list.take_upto(MaxErrors, CanLoop1, CanLoop).
+        list.take_upto(MaxErrors, CanLoop1, CanLoop),
+        Info = term_traversal_ok(Paths, CanLoop)
+    ).
 
-:- pred combine_paths(traversal_info::in, traversal_info::in,
-    traversal_params::in, traversal_info::out) is det.
+:- pred combine_paths(term_traversal_info::in, term_traversal_info::in,
+    term_traversal_params::in, term_traversal_info::out) is det.
 
-combine_paths(error(Errors1, CanLoop1), error(Errors2, CanLoop2), Params,
-        error(Errors, CanLoop)) :-
+combine_paths(InfoA, InfoB, Params, Info) :-
+    (
+        InfoA = term_traversal_error(ErrorsA, CanLoopA),
+        InfoB = term_traversal_error(ErrorsB, CanLoopB),
     params_get_max_errors(Params, MaxErrors),
-    list.append(Errors1, Errors2, Errors3),
-    list.take_upto(MaxErrors, Errors3, Errors),
-    list.append(CanLoop1, CanLoop2, CanLoop3),
-    list.take_upto(MaxErrors, CanLoop3, CanLoop).
-combine_paths(error(Errors1, CanLoop1), ok(_, CanLoop2), Params,
-        error(Errors1, CanLoop)) :-
+        list.take_upto(MaxErrors, ErrorsA ++ ErrorsB, Errors),
+        list.take_upto(MaxErrors, CanLoopA ++ CanLoopB, CanLoop),
+        Info = term_traversal_error(Errors, CanLoop)
+    ;
+        InfoA = term_traversal_error(ErrorsA, CanLoopA),
+        InfoB = term_traversal_ok(_, CanLoopB),
     params_get_max_errors(Params, MaxErrors),
-    list.append(CanLoop1, CanLoop2, CanLoop3),
-    list.take_upto(MaxErrors, CanLoop3, CanLoop).
-combine_paths(ok(_, CanLoop1), error(Errors2, CanLoop2), Params,
-        error(Errors2, CanLoop)) :-
+        list.take_upto(MaxErrors, CanLoopA ++ CanLoopB, CanLoop),
+        Info = term_traversal_error(ErrorsA, CanLoop)
+    ;
+        InfoA = term_traversal_ok(_, CanLoopA),
+        InfoB = term_traversal_error(ErrorsB, CanLoopB),
     params_get_max_errors(Params, MaxErrors),
-    list.append(CanLoop1, CanLoop2, CanLoop3),
-    list.take_upto(MaxErrors, CanLoop3, CanLoop).
-combine_paths(ok(Paths1, CanLoop1), ok(Paths2, CanLoop2), Params,
-        Info) :-
+        list.take_upto(MaxErrors, CanLoopA ++ CanLoopB, CanLoop),
+        Info = term_traversal_error(ErrorsB, CanLoop)
+    ;
+        InfoA = term_traversal_ok(PathsA, CanLoopA),
+        InfoB = term_traversal_ok(PathsB, CanLoopB),
     params_get_max_errors(Params, MaxErrors),
-    list.append(CanLoop1, CanLoop2, CanLoop3),
-    list.take_upto(MaxErrors, CanLoop3, CanLoop),
-    set.union(Paths2, Paths1, Paths),
+        list.take_upto(MaxErrors, CanLoopA ++ CanLoopB, CanLoop),
+        set.union(PathsB, PathsA, Paths),
     params_get_max_paths(Params, MaxPaths),
     (
         % Don't try to track the state of too many paths;
@@ -450,11 +475,12 @@
         set.count(Paths, Count),
         Count =< MaxPaths
     ->
-        Info = ok(Paths, CanLoop)
+            Info = term_traversal_ok(Paths, CanLoop)
     ;
         params_get_context(Params, Context),
-        Info = error([termination_error_context(too_many_paths, Context)],
-            CanLoop)
+            ErrorContext = termination_error_context(too_many_paths, Context),
+            Info = term_traversal_error([ErrorContext], CanLoop)
+        )
     ).
 
 %-----------------------------------------------------------------------------%
@@ -493,8 +519,8 @@
     % order unification.
     %
 :- pred unify_change(module_info::in, prog_var::in, cons_id::in,
-    list(prog_var)::in, list(uni_mode)::in, traversal_params::in, int::out,
-    bag(prog_var)::out, bag(prog_var)::out) is semidet.
+    list(prog_var)::in, list(uni_mode)::in, term_traversal_params::in,
+    int::out, bag(prog_var)::out, bag(prog_var)::out) is semidet.
 
 unify_change(ModuleInfo, OutVar, ConsId, Args0, Modes0, Params, Gamma,
         InVars, OutVars) :-
@@ -502,17 +528,15 @@
     params_get_var_types(Params, VarTypes),
     map.lookup(VarTypes, OutVar, Type),
     \+ type_is_higher_order(Type),
-    ( type_to_ctor_and_args(Type, TypeCtor, _) ->
+    type_to_ctor_and_args_det(Type, TypeCtor, _),
         filter_args_and_modes(VarTypes, Args0, Args1, Modes0, Modes1),
         functor_norm(FunctorInfo, TypeCtor, ConsId, ModuleInfo,
             Gamma, Args1, Args, Modes1, Modes),
-        split_unification_vars(Args, Modes, ModuleInfo, InVars, OutVars)
-    ;
-        unexpected(this_file, "unify_change/8: variable type.")
-    ).
+    split_unification_vars(Args, Modes, ModuleInfo, InVars, OutVars).
 
-:- pred filter_args_and_modes(vartypes::in, list(prog_var)::in,
-    list(prog_var)::out, list(uni_mode)::in, list(uni_mode)::out) is det.
+:- pred filter_args_and_modes(vartypes::in,
+    list(prog_var)::in, list(prog_var)::out,
+    list(uni_mode)::in, list(uni_mode)::out) is det.
 
 filter_args_and_modes(VarTypes, Args0, Args, Modes0, Modes) :-
     assoc_list.from_corresponding_lists(Args0, Modes0, ArgsAndModes0),
@@ -526,31 +550,37 @@
 %-----------------------------------------------------------------------------%
 
 :- pred record_change(bag(prog_var)::in, bag(prog_var)::in, int::in,
-    list(pred_proc_id)::in, traversal_info::in, traversal_info::out) is det.
+    list(pred_proc_id)::in, term_traversal_info::in, term_traversal_info::out)
+    is det.
 
-record_change(_, _, _, _, error(Errors, CanLoop), error(Errors, CanLoop)).
-record_change(InVars, OutVars, Gamma, CalledPPIds, ok(Paths0, CanLoop),
-        ok(NewPaths, CanLoop)) :-
+record_change(InVars, OutVars, Gamma, CalledPPIds, Info0, Info) :-
+    (
+        Info0 = term_traversal_error(_, _),
+        Info = Info0
+    ;
+        Info0 = term_traversal_ok(Paths0, CanLoop),
     set.to_sorted_list(Paths0, PathsList0),
     set.init(NewPaths0),
     record_change_2(PathsList0, InVars, OutVars, Gamma, CalledPPIds,
-        NewPaths0, NewPaths).
+            NewPaths0, NewPaths),
+        Info = term_traversal_ok(NewPaths, CanLoop)
+    ).
 
-:- pred record_change_2(list(path_info)::in, bag(prog_var)::in,
+:- pred record_change_2(list(term_path_info)::in, bag(prog_var)::in,
     bag(prog_var)::in, int::in, list(pred_proc_id)::in,
-    set(path_info)::in, set(path_info)::out) is det.
+    set(term_path_info)::in, set(term_path_info)::out) is det.
 
 record_change_2([], _, _, _, _, !PathSet).
 record_change_2([Path0 | Paths0], InVars, OutVars, CallGamma, CallPPIds,
         !PathSet) :-
-    Path0 = path_info(ProcData, Start, Gamma0, PPIds0, Vars0),
+    Path0 = term_path_info(ProcData, Start, Gamma0, PPIds0, Vars0),
     ( bag.intersect(OutVars, Vars0) ->
         % The change produces some active variables.
         Gamma = CallGamma + Gamma0,
         list.append(CallPPIds, PPIds0, PPIds),
         bag.subtract(Vars0, OutVars, Vars1),
         bag.union(InVars, Vars1, Vars),
-        Path = path_info(ProcData, Start, Gamma, PPIds, Vars)
+        Path = term_path_info(ProcData, Start, Gamma, PPIds, Vars)
     ;
         % The change produces no active variables.
         Path = Path0
@@ -561,25 +591,32 @@
 %-----------------------------------------------------------------------------%
 
 :- pred error_if_intersect(bag(prog_var)::in, prog_context::in,
-    termination_error::in, traversal_info::in, traversal_info::out) is det.
+    termination_error::in, term_traversal_info::in, term_traversal_info::out)
+    is det.
 
-error_if_intersect(_, _, _, error(Errors, CanLoop), error(Errors, CanLoop)).
-error_if_intersect(OutVars, Context, ErrorMsg, ok(Paths, CanLoop), Info) :-
+error_if_intersect(OutVars, Context, ErrorMsg, Info0, Info) :-
+    (
+        Info0 = term_traversal_error(_, _),
+        Info = Info0
+    ;
+        Info0 = term_traversal_ok(Paths, CanLoop),
     (
         set.to_sorted_list(Paths, PathList),
         some_active_vars_in_bag(PathList, OutVars)
     ->
-        Info = error([termination_error_context(ErrorMsg, Context)], CanLoop)
+            ErrorContext = termination_error_context(ErrorMsg, Context),
+            Info = term_traversal_error([ErrorContext], CanLoop)
     ;
-        Info = ok(Paths, CanLoop)
+            Info = term_traversal_ok(Paths, CanLoop)
+        )
     ).
 
-:- pred some_active_vars_in_bag(list(path_info)::in,
+:- pred some_active_vars_in_bag(list(term_path_info)::in,
     bag(prog_var)::in) is semidet.
 
 some_active_vars_in_bag([Path | Paths], OutVars) :-
     (
-        Path = path_info(_, _, _, _, Vars),
+        Path = term_path_info(_, _, _, _, Vars),
         bag.intersect(Vars, OutVars)
     ;
         some_active_vars_in_bag(Paths, OutVars)
@@ -591,13 +628,13 @@
     bag.init(ActiveVars).
 upper_bound_active_vars([Path | Paths], ActiveVars) :-
     upper_bound_active_vars(Paths, ActiveVars1),
-    Path = path_info(_, _, _, _, ActiveVars2),
+    Path = term_path_info(_, _, _, _, ActiveVars2),
     bag.least_upper_bound(ActiveVars1, ActiveVars2, ActiveVars).
 
 %-----------------------------------------------------------------------------%
 
-:- type traversal_params
-    --->    traversal_params(
+:- type term_traversal_params
+    --->    term_traversal_params(
                 term_trav_functor_info      :: functor_info,
                 
                 % The procedure we are tracing through.
@@ -623,27 +660,27 @@
                 term_trav_max_paths         :: int
         ).
 
-init_traversal_params(FunctorInfo, PredProcId, Context, VarTypes,
+init_term_traversal_params(FunctorInfo, PredProcId, Context, VarTypes,
         OutputSuppliers, RecInputSuppliers, MaxErrors, MaxPaths,
         Params) :-
-    Params = traversal_params(FunctorInfo, PredProcId, Context,
+    Params = term_traversal_params(FunctorInfo, PredProcId, Context,
         VarTypes, OutputSuppliers, RecInputSuppliers,
         MaxErrors, MaxPaths).
 
-:- pred params_get_functor_info(traversal_params::in, functor_info::out)
+:- pred params_get_functor_info(term_traversal_params::in, functor_info::out)
     is det.
-:- pred params_get_ppid(traversal_params::in, pred_proc_id::out)
+:- pred params_get_ppid(term_traversal_params::in, pred_proc_id::out)
     is det.
-:- pred params_get_context(traversal_params::in, prog_context::out)
+:- pred params_get_context(term_traversal_params::in, prog_context::out)
     is det.
-:- pred params_get_var_types(traversal_params::in, vartypes::out)
+:- pred params_get_var_types(term_traversal_params::in, vartypes::out)
     is det.
-:- pred params_get_output_suppliers(traversal_params::in,
+:- pred params_get_output_suppliers(term_traversal_params::in,
     map(pred_proc_id, list(bool))::out) is det.
-:- pred params_get_rec_input_suppliers(traversal_params::in,
+:- pred params_get_rec_input_suppliers(term_traversal_params::in,
     map(pred_proc_id, list(bool))::out) is det.
-:- pred params_get_max_errors(traversal_params::in, int::out) is det.
-:- pred params_get_max_paths(traversal_params::in, int::out) is det.
+:- pred params_get_max_errors(term_traversal_params::in, int::out) is det.
+:- pred params_get_max_paths(term_traversal_params::in, int::out) is det.
 
 params_get_functor_info(Params, Params ^ term_trav_functor_info).
 params_get_ppid(Params, Params ^ term_trav_ppid).
Index: compiler/termination.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/termination.m,v
retrieving revision 1.78
diff -u -b -r1.78 termination.m
--- compiler/termination.m	23 Nov 2007 07:35:28 -0000	1.78
+++ compiler/termination.m	12 Jan 2008 23:55:38 -0000
@@ -95,27 +95,23 @@
     globals.io_lookup_int_option(termination_error_limit, MaxErrors, !IO),
     globals.io_lookup_int_option(termination_path_limit, MaxPaths, !IO),
     PassInfo = pass_info(FunctorInfo, MaxErrors, MaxPaths),
-    %
+
     % Process builtin and compiler-generated predicates, and user-supplied
     % pragmas.
-    %
     module_info_predids(PredIds, !ModuleInfo),
     check_preds(PredIds, !ModuleInfo, !IO),
-    %
+
     % Process all the SCCs of the call graph in a bottom-up order.
-    %
     module_info_ensure_dependency_info(!ModuleInfo),
     module_info_dependency_info(!.ModuleInfo, DepInfo),
     hlds_dependency_info_get_dependency_ordering(DepInfo, SCCs),
-    %
+
     % Set the termination status of foreign_procs based on the foreign code
     % attributes.
-    %
     check_foreign_code_attributes(SCCs, !ModuleInfo, !IO),
-    %
+
     % Ensure that termination pragmas for a procedure do not conflict with
     % termination pragmas for other procedures in the SCC.
-    %
     check_pragmas_are_consistent(SCCs, !ModuleInfo, !IO),
 
     list.foldl2(analyse_termination_in_scc(PassInfo), SCCs, !ModuleInfo, !IO),
@@ -294,9 +290,8 @@
                 !ModuleInfo)
         ;
             % There is a conflict between the user-supplied termination
-            % information for two or more procedures in this SCC.  Emit a
-            % warning and then assume that they all loop.
-            %
+            % information for two or more procedures in this SCC.
+            % Emit a warning and then assume that they all loop.
             get_context_from_scc(SCCTerminationKnown, !.ModuleInfo,
                 Context),
             NewTermStatus = can_loop([termination_error_context(
@@ -369,12 +364,12 @@
         find_arg_sizes_in_scc(SCCArgSizeUnknown, PassInfo, ArgSizeResult,
             TermErrors, !ModuleInfo, !IO),
         (
-            ArgSizeResult = ok(Solutions, OutputSupplierMap),
+            ArgSizeResult = arg_size_ok(Solutions, OutputSupplierMap),
             set_finite_arg_size_infos(Solutions, OutputSupplierMap,
                 !ModuleInfo),
             ArgSizeErrors = []
         ;
-            ArgSizeResult = error(Errors),
+            ArgSizeResult = arg_size_error(Errors),
             set_infinite_arg_size_infos(SCCArgSizeUnknown,
                 infinite(Errors), !ModuleInfo),
             ArgSizeErrors = Errors
@@ -517,12 +512,11 @@
         list.filter(IsNonImported, SCC, NonImportedPPIds),
         NonImportedPPIds = [_|_],
 
-        % Don't emit non-termination warnings for the compiler
-        % generated wrapper predicates for solver type initialisation
-        % predicates.  If they don't terminate there's nothing the user
-        % can do about it anyway - the problem is with the
-        % initialisation predicate specified by the user, not the
-        % wrapper.
+        % Don't emit non-termination warnings for the compiler generated
+        % wrapper predicates for solver type initialisation predicates.
+        % If they don't terminate there's nothing the user can do about it
+        % anyway - the problem is with the initialisation predicate specified
+        % by the user, not the wrapper.
         list.all_false(is_solver_init_wrapper_pred(!.ModuleInfo), SCC),
 
         % Only output warnings of non-termination for direct errors.  If there
@@ -828,12 +822,12 @@
     ),
     change_procs_arg_size_info(ProcIds, Override, ArgSize, !ProcTable).
 
+    % change_procs_termination_info(ProcList, Override, TerminationInfo,
+    %     !ProcTable):
+    %
     % This predicate sets the termination_info property of the given list of
     % procedures.
     %
-    % change_procs_termination_info(ProcList, Override, TerminationInfo,
-    %       ProcTable, ProcTable)
-    %
     % If Override is yes, then this predicate overrides any existing
     % termination information. If Override is no, then it leaves the proc_info
     % of a procedure unchanged unless the proc_info had no termination
@@ -911,10 +905,9 @@
         ),
         \+ is_unify_or_compare_pred(PredInfo),
 
-        % XXX These should be allowed, but the predicate
-        % declaration for the specialized predicate is not produced
-        % before the termination pragmas are read in, resulting
-        % in an undefined predicate error.
+        % XXX These should be allowed, but the predicate declaration for
+        % the specialized predicate is not produced before the termination
+        % pragmas are read in, resulting in an undefined predicate error.
         \+ set.member(PredId, TypeSpecForcePreds)
     ->
         PredName = pred_info_name(PredInfo),
Index: compiler/tupling.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/tupling.m,v
retrieving revision 1.43
diff -u -b -r1.43 tupling.m
--- compiler/tupling.m	30 Dec 2007 08:24:00 -0000	1.43
+++ compiler/tupling.m	12 Jan 2008 20:48:23 -0000
@@ -1557,7 +1557,7 @@
 build_insert_map(CellVar, FieldVars, IntervalInfo, InsertMap) :-
     FieldVarsSet = set.from_list(FieldVars),
     map.foldl(build_insert_map_2(CellVar, FieldVars, FieldVarsSet),
-        IntervalInfo ^ anchor_follow_map, map.init, InsertMap).
+        IntervalInfo ^ ii_anchor_follow_map, map.init, InsertMap).
 
 :- pred build_insert_map_2(prog_var::in, list(prog_var)::in, set(prog_var)::in,
     anchor::in, anchor_follow_info::in, insert_map::in, insert_map::out)
Index: compiler/unify_proc.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/unify_proc.m,v
retrieving revision 1.198
diff -u -b -r1.198 unify_proc.m
--- compiler/unify_proc.m	22 Jan 2008 15:06:17 -0000	1.198
+++ compiler/unify_proc.m	24 Jan 2008 01:18:51 -0000
@@ -1406,7 +1406,7 @@
 :- func can_compare_constants_as_ints(unify_proc_info) = bool.
 
 can_compare_constants_as_ints(Info) = CanCompareAsInt :-
-    ModuleInfo = Info ^ module_info,
+    ModuleInfo = Info ^ upi_module_info,
     module_info_get_globals(ModuleInfo, Globals),
     lookup_bool_option(Globals, can_compare_constants_as_ints,
         CanCompareAsInt).
@@ -2112,7 +2112,7 @@
 :- func should_pretest_equality(unify_proc_info) = bool.
 
 should_pretest_equality(Info) = ShouldPretestEq :-
-    ModuleInfo = Info ^ module_info,
+    ModuleInfo = Info ^ upi_module_info,
     module_info_get_globals(ModuleInfo, Globals),
     lookup_bool_option(Globals, should_pretest_equality, ShouldPretestEq).
 
@@ -2172,10 +2172,10 @@
 
 :- type unify_proc_info
     --->    unify_proc_info(
-                varset          ::  prog_varset,
-                vartypes        ::  vartypes,
-                rtti_varmaps    ::  rtti_varmaps,
-                module_info     ::  module_info
+                upi_varset          ::  prog_varset,
+                upi_vartypes        ::  vartypes,
+                upi_rtti_varmaps    ::  rtti_varmaps,
+                upi_module_info     ::  module_info
             ).
 
 info_init(ModuleInfo, UPI) :-
@@ -2185,27 +2185,27 @@
     UPI = unify_proc_info(VarSet, Types, RttiVarMaps, ModuleInfo).
 
 info_new_var(Type, Var, !UPI) :-
-    varset.new_var(!.UPI ^ varset, Var, VarSet),
-    map.det_insert(!.UPI ^ vartypes, Var, Type, VarTypes),
-    !:UPI = !.UPI ^ varset := VarSet,
-    !:UPI = !.UPI ^ vartypes := VarTypes.
+    varset.new_var(!.UPI ^ upi_varset, Var, VarSet),
+    map.det_insert(!.UPI ^ upi_vartypes, Var, Type, VarTypes),
+    !:UPI = !.UPI ^ upi_varset := VarSet,
+    !:UPI = !.UPI ^ upi_vartypes := VarTypes.
 
 info_new_named_var(Type, Name, Var, !UPI) :-
-    varset.new_named_var(!.UPI ^ varset, Name, Var, VarSet),
-    map.det_insert(!.UPI ^ vartypes, Var, Type, VarTypes),
-    !:UPI = !.UPI ^ varset := VarSet,
-    !:UPI = !.UPI ^ vartypes := VarTypes.
-
-info_extract(UPI, UPI ^ varset, UPI ^ vartypes).
-
-info_get_varset(UPI, UPI ^ varset).
-info_get_types(UPI, UPI ^ vartypes).
-info_get_rtti_varmaps(UPI, UPI ^ rtti_varmaps).
-info_get_module_info(UPI, UPI ^ module_info).
-
-info_set_varset(VarSet, UPI, UPI ^ varset := VarSet).
-info_set_types(Types, UPI, UPI ^ vartypes := Types).
-info_set_rtti_varmaps(RttiVarMaps, UPI, UPI ^ rtti_varmaps := RttiVarMaps).
+    varset.new_named_var(!.UPI ^ upi_varset, Name, Var, VarSet),
+    map.det_insert(!.UPI ^ upi_vartypes, Var, Type, VarTypes),
+    !:UPI = !.UPI ^ upi_varset := VarSet,
+    !:UPI = !.UPI ^ upi_vartypes := VarTypes.
+
+info_extract(UPI, UPI ^ upi_varset, UPI ^ upi_vartypes).
+
+info_get_varset(UPI, UPI ^ upi_varset).
+info_get_types(UPI, UPI ^ upi_vartypes).
+info_get_rtti_varmaps(UPI, UPI ^ upi_rtti_varmaps).
+info_get_module_info(UPI, UPI ^ upi_module_info).
+
+info_set_varset(VarSet, UPI, UPI ^ upi_varset := VarSet).
+info_set_types(Types, UPI, UPI ^ upi_vartypes := Types).
+info_set_rtti_varmaps(RttiVarMaps, UPI, UPI ^ upi_rtti_varmaps := RttiVarMaps).
 
 %-----------------------------------------------------------------------------%
 
Index: compiler/unused_args.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/unused_args.m,v
retrieving revision 1.148
diff -u -b -r1.148 unused_args.m
--- compiler/unused_args.m	22 Jan 2008 15:06:18 -0000	1.148
+++ compiler/unused_args.m	24 Jan 2008 01:18:51 -0000
@@ -499,7 +499,7 @@
             ),
 
             proc_info_get_goal(ProcInfo, Goal),
-            Info = traverse_info(!.ModuleInfo, VarTypes),
+            Info = unused_args_info(!.ModuleInfo, VarTypes),
             traverse_goal(Info, Goal, !VarDep),
             svmap.set(proc(PredId, ProcId), !.VarDep, !VarUsage),
 
@@ -616,13 +616,13 @@
 % Traversal of goal structure, building up dependencies for all variables
 %
 
-:- type traverse_info
-    --->    traverse_info(
-                module_info :: module_info,
-                vartypes    :: vartypes
+:- type unused_args_info
+    --->    unused_args_info(
+                unarg_module_info   :: module_info,
+                unarg_vartypes      :: vartypes
             ).
 
-:- pred traverse_goal(traverse_info::in, hlds_goal::in,
+:- pred traverse_goal(unused_args_info::in, hlds_goal::in,
     var_dep::in, var_dep::out) is det.
 
 traverse_goal(Info, Goal, !VarDep) :-
@@ -640,7 +640,7 @@
         traverse_list_of_goals(Info, Goals, !VarDep)
     ;
         GoalExpr = plain_call(PredId, ProcId, Args, _, _, _),
-        module_info_pred_proc_info(Info ^ module_info, PredId, ProcId,
+        module_info_pred_proc_info(Info ^ unarg_module_info, PredId, ProcId,
             _Pred, Proc),
         proc_info_get_headvars(Proc, HeadVars),
         add_pred_call_arg_dep(proc(PredId, ProcId), Args, HeadVars, !VarDep)
@@ -775,7 +775,7 @@
     % Partition the arguments to a deconstruction into inputs
     % and outputs.
     %
-:- pred partition_deconstruct_args(traverse_info::in, list(prog_var)::in,
+:- pred partition_deconstruct_args(unused_args_info::in, list(prog_var)::in,
     list(uni_mode)::in, list(prog_var)::out, list(prog_var)::out) is det.
 
 partition_deconstruct_args(Info, ArgVars, ArgModes, InputVars, OutputVars) :-
@@ -786,13 +786,13 @@
         partition_deconstruct_args(Info, Vars, Modes, InputVars1, OutputVars1),
         Mode = ((InitialInst1 - InitialInst2) -> (FinalInst1 - FinalInst2)),
 
-        map.lookup(Info ^ vartypes, Var, Type),
+        map.lookup(Info ^ unarg_vartypes, Var, Type),
 
         % If the inst of the argument of the LHS is changed,
         % the argument is input.
         (
             inst_matches_binding(InitialInst1, FinalInst1,
-                Type, Info ^ module_info)
+                Type, Info ^ unarg_module_info)
         ->
             InputVars = InputVars1
         ;
@@ -803,7 +803,7 @@
         % the argument is output.
         (
             inst_matches_binding(InitialInst2, FinalInst2, Type,
-                Info ^ module_info)
+                Info ^ unarg_module_info)
         ->
             OutputVars = OutputVars1
         ;
@@ -842,7 +842,7 @@
 list_case_to_list_goal([case(_, _, Goal) | Cases], [Goal | Goals]) :-
     list_case_to_list_goal(Cases, Goals).
 
-:- pred traverse_list_of_goals(traverse_info::in, list(hlds_goal)::in,
+:- pred traverse_list_of_goals(unused_args_info::in, list(hlds_goal)::in,
     var_dep::in, var_dep::out) is det.
 
 traverse_list_of_goals(_, [], !VarDep).
Index: compiler/var_locn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/var_locn.m,v
retrieving revision 1.56
diff -u -b -r1.56 var_locn.m
--- compiler/var_locn.m	24 Jan 2008 01:08:14 -0000	1.56
+++ compiler/var_locn.m	24 Jan 2008 01:18:51 -0000
@@ -449,51 +449,41 @@
 
 :- type var_locn_info
     --->    var_locn_info(
-                varset          :: prog_varset,
-                                % The varset from the proc_info.
+                % The varset and vartypes from the proc_info.
+                vli_varset          :: prog_varset,
+                vli_vartypes        :: vartypes,
+
+                % Maps each var to its stack slot, if it has one.
+                vli_stack_slots     :: stack_slots,
+
+                % The values of the options that are relevant to decisions
+                % about which rvals are constants.
+                vli_exprn_opts      :: exprn_opts,
 
-                vartypes        :: vartypes,
-                                % The vartypes from the proc_info.
-
-                stack_slots     :: stack_slots,
-                                % Maps each var to its stack slot,
-                                % if it has one.
-
-                exprn_opts      :: exprn_opts,
-                                % The values of the options that are relevant
-                                % to decisions about which rvals are constants.
-
-                follow_vars_map :: abs_follow_vars_map,
                                 % Where vars are needed next.
+                vli_follow_vars_map :: abs_follow_vars_map,
 
-                next_non_res    :: int,
-                                % Next register that isn't reserved in
-                                % follow_vars_map.
+                % Next register that isn't reserved in follow_vars_map.
+                vli_next_non_res    :: int,
 
-                var_state_map   :: var_state_map,
                                 % Documented above.
+                vli_var_state_map   :: var_state_map,
+                vli_loc_var_map     :: loc_var_map,
 
-                loc_var_map     :: loc_var_map,
-                                % Documented above.
+                % Locations that are temporarily reserved for purposes such as
+                % holding the tags of variables during switches.
+                vli_acquired        :: set(lval),
+
+                % If this slot contains N, then registers r1 through rN
+                % can only be modified by a place_var operation, or by a
+                % free_up_lval operation that moves a variable to the
+                % (free or freeable) lval associated with it in the exceptions
+                % field. Used to implement calls, foreign_procs and the
+                % store_maps at the ends of branched control structures.
+                vli_locked          :: int,
 
-                acquired        :: set(lval),
-                                % Locations that are temporarily reserved
-                                % for purposes such as holding the tags of
-                                % variables during switches.
-
-                locked          :: int,
-                                % If this slot contains N, then registers
-                                % r1 through rN can only be modified by
-                                % a place_var operation, or by a free_up_lval
-                                % operation that moves a variable to the
-                                % (free or freeable) lval associated with it
-                                % in the exceptions field. Used to implement
-                                % calls, foreign_procs and the store_maps
-                                % at the ends of branched control structures.
-
-                exceptions      :: assoc_list(prog_var, lval)
-                                % See the documentation of the locked field
-                                % above.
+                % See the documentation of the locked field above.
+                vli_exceptions      :: assoc_list(prog_var, lval)
             ).
 
 %----------------------------------------------------------------------------%
@@ -2459,25 +2449,25 @@
 :- pred var_locn_set_exceptions(assoc_list(prog_var, lval)::in,
     var_locn_info::in, var_locn_info::out) is det.
 
-var_locn_get_varset(VI, VI ^ varset).
-var_locn_get_vartypes(VI, VI ^ vartypes).
-var_locn_get_stack_slots(VI, VI ^ stack_slots).
-var_locn_get_exprn_opts(VI, VI ^ exprn_opts).
-var_locn_get_follow_var_map(VI, VI ^ follow_vars_map).
-var_locn_get_next_non_reserved(VI, VI ^ next_non_res).
-var_locn_get_var_state_map(VI, VI ^ var_state_map).
-var_locn_get_loc_var_map(VI, VI ^ loc_var_map).
-var_locn_get_acquired(VI, VI ^ acquired).
-var_locn_get_locked(VI, VI ^ locked).
-var_locn_get_exceptions(VI, VI ^ exceptions).
-
-var_locn_set_follow_var_map(FVM, VI, VI ^ follow_vars_map := FVM).
-var_locn_set_next_non_reserved(NNR, VI, VI ^ next_non_res := NNR).
-var_locn_set_var_state_map(VSM, VI, VI ^ var_state_map := VSM).
-var_locn_set_loc_var_map(LVM, VI, VI ^ loc_var_map := LVM).
-var_locn_set_acquired(A, VI, VI ^ acquired := A).
-var_locn_set_locked(L, VI, VI ^ locked := L).
-var_locn_set_exceptions(E, VI, VI ^ exceptions := E).
+var_locn_get_varset(VI, VI ^ vli_varset).
+var_locn_get_vartypes(VI, VI ^ vli_vartypes).
+var_locn_get_stack_slots(VI, VI ^ vli_stack_slots).
+var_locn_get_exprn_opts(VI, VI ^ vli_exprn_opts).
+var_locn_get_follow_var_map(VI, VI ^ vli_follow_vars_map).
+var_locn_get_next_non_reserved(VI, VI ^ vli_next_non_res).
+var_locn_get_var_state_map(VI, VI ^ vli_var_state_map).
+var_locn_get_loc_var_map(VI, VI ^ vli_loc_var_map).
+var_locn_get_acquired(VI, VI ^ vli_acquired).
+var_locn_get_locked(VI, VI ^ vli_locked).
+var_locn_get_exceptions(VI, VI ^ vli_exceptions).
+
+var_locn_set_follow_var_map(FVM, VI, VI ^ vli_follow_vars_map := FVM).
+var_locn_set_next_non_reserved(NNR, VI, VI ^ vli_next_non_res := NNR).
+var_locn_set_var_state_map(VSM, VI, VI ^ vli_var_state_map := VSM).
+var_locn_set_loc_var_map(LVM, VI, VI ^ vli_loc_var_map := LVM).
+var_locn_set_acquired(A, VI, VI ^ vli_acquired := A).
+var_locn_set_locked(L, VI, VI ^ vli_locked := L).
+var_locn_set_exceptions(E, VI, VI ^ vli_exceptions := E).
 
 %----------------------------------------------------------------------------%
 
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
cvs diff: Diffing extras
cvs diff: Diffing extras/base64
cvs diff: Diffing extras/cgi
cvs diff: Diffing extras/complex_numbers
cvs diff: Diffing extras/complex_numbers/samples
cvs diff: Diffing extras/complex_numbers/tests
cvs diff: Diffing extras/concurrency
cvs diff: Diffing extras/curs
cvs diff: Diffing extras/curs/samples
cvs diff: Diffing extras/curses
cvs diff: Diffing extras/curses/sample
cvs diff: Diffing extras/dynamic_linking
cvs diff: Diffing extras/error
cvs diff: Diffing extras/fixed
cvs diff: Diffing extras/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_allegro
cvs diff: Diffing extras/graphics/mercury_allegro/examples
cvs diff: Diffing extras/graphics/mercury_allegro/samples
cvs diff: Diffing extras/graphics/mercury_allegro/samples/demo
cvs diff: Diffing extras/graphics/mercury_allegro/samples/mandel
cvs diff: Diffing extras/graphics/mercury_allegro/samples/pendulum2
cvs diff: Diffing extras/graphics/mercury_allegro/samples/speed
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/log4m
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
cvs diff: Diffing extras/mopenssl
cvs diff: Diffing extras/morphine
cvs diff: Diffing extras/morphine/non-regression-tests
cvs diff: Diffing extras/morphine/scripts
cvs diff: Diffing extras/morphine/source
cvs diff: Diffing extras/net
cvs diff: Diffing extras/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/posix/samples
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/standalone_c
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/solver_types
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing ssdb
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
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
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
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