[m-rev.] for review: fix some test case failures in deep profiling grades

Zoltan Somogyi zs at cs.mu.OZ.AU
Tue May 2 17:25:28 AEST 2006


compiler/lookup_switch.m:
	Fix two bugs that caused test case failures in deep profiling grades.

	One bug was that an acquired register wasn't being released before
	the creation of a resume point, which rebuilds the code generator state
	(and thus forgets about acquired registers).

	The other bug was that is_lookup_switch wasn't performing the actions
	generate_goal would have when processing goals. In particular, it
	wasn't invoking pre_goal_update and post_goal_update on disjunctions
	inside the switch.

compiler/lookup_util.m:
	Do not standardize goals by removing scopes from around other goals,
	because this could also remove the effects of the code generator
	annotations (e.g. liveness changes such as pre-births) on the scope
	goal.

compiler/simplify.m:
	Eliminate those redundant scopes if asked to do so. Since this is done
	before the code generator annotations are put on goals, this is safe.

compiler/code_gen.m:
compiler/proc_gen.m:
	Divide the old code_gen.m into two modules: the new code_gen.m
	concerned with generating code for goals, and the new module proc_gen.m
	concerned with generating code for procedures. Without this, the code
	for handling goals is lost inside the old code_gen.m module.

compiler/ll_backend.m:
	Include the new module.

compiler/mercury_compile.m:
	Import proc_gen instead of code_gen, and ask simplify to eliminate
	unnecessary scopes before code generation.

compiler/middle_rec.m:
	Update a reference to a predicate now in proc_gen.m.

compiler/notes/compiler_design.html:
	Document the new module.

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/tests
cvs diff: Diffing browser
cvs diff: Diffing bytecode
cvs diff: Diffing compiler
Index: compiler/code_gen.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_gen.m,v
retrieving revision 1.159
diff -u -b -r1.159 code_gen.m
--- compiler/code_gen.m	26 Apr 2006 03:05:31 -0000	1.159
+++ compiler/code_gen.m	29 Apr 2006 09:51:52 -0000
@@ -5,27 +5,20 @@
 % This file may only be copied under the terms of the GNU General
 % Public License - see the file COPYING in the Mercury distribution.
 %---------------------------------------------------------------------------%
-
+%
 % File: code_gen.m.
 % Main authors: conway, zs.
-
-% Code generation - convert from HLDS to LLDS.
-%
-% The two main tasks of this module are
-%
-% 1 to look after the aspects of generating code for a procedure
-%   that do not involve generating code for a specific goal, and
 %
-% 2 to provide a generic predicate that can be called from anywhere in
-%   the code generator to generate code for a goal.
-%
-% Code_gen forwards most of the actual construction of code for particular
-% goals to other modules. The generation of code for unifications is done
+% The task of this module is to provide a generic predicate that can be called
+% from anywhere in the code generator to generate code for a goal. We forward
+% most of the actual construction of code for particular types of goals
+% to other modules. The generation of code for unifications is done
 % by unify_gen, for calls, higher-order calls and method calls by call_gen,
 % for commits by commit_gen, for if-then-elses and negations by ite_gen,
 % for switches by switch_gen and its subsidiary modules, for disjunctions
-% by disj_gen, and for pragma_c_codes by pragma_c_gen. The only kind of goal
-% handled directly by code_gen is the conjunction.
+% by disj_gen, for parallel conjunctions by par_conj_gen, and for foreign_procs
+% by pragma_c_gen. The only goals handled directly by code_gen are sequential
+% conjunctions.
 
 %---------------------------------------------------------------------------%
 
@@ -34,1024 +27,44 @@
 
 :- import_module hlds.code_model.
 :- import_module hlds.hlds_goal.
-:- import_module hlds.hlds_module.
-:- import_module hlds.hlds_pred.
 :- import_module ll_backend.code_info.
-:- import_module ll_backend.global_data.
 :- import_module ll_backend.llds.
 
-:- import_module io.
-:- import_module list.
-
 %---------------------------------------------------------------------------%
 
-    % Translate a HLDS module to LLDS.
-    %
-:- pred generate_code(module_info::in, global_data::in, global_data::out,
-    list(c_procedure)::out, io::di, io::uo) is det.
-
-    % Translate a HLDS procedure to LLDS, threading through the data structure
-    % that records information about layout structures.
-    %
-:- pred generate_proc_code(pred_info::in, proc_info::in,
-    proc_id::in, pred_id::in, module_info::in,
-    global_data::in, global_data::out, c_procedure::out) is det.
-
     % Translate a HLDS goal to LLDS.
     %
 :- pred generate_goal(code_model::in, hlds_goal::in, code_tree::out,
     code_info::in, code_info::out) is det.
 
-    % Return the message that identifies the procedure to pass to
-    % the incr_sp_push_msg macro in the generated C code.
-    %
-:- func push_msg(module_info, pred_id, proc_id) = string.
-
 %---------------------------------------------------------------------------%
 %---------------------------------------------------------------------------%
 
 :- implementation.
 
-:- import_module backend_libs.builtin_ops.
-:- import_module backend_libs.proc_label.
-:- import_module backend_libs.rtti.
-:- import_module check_hlds.mode_util.
-:- import_module check_hlds.type_util.
-:- import_module hlds.goal_util.
-:- import_module hlds.hlds_clauses.
-:- import_module hlds.hlds_llds.
-:- import_module hlds.hlds_out.
+:- import_module hlds.hlds_pred.
 :- import_module hlds.instmap.
-:- import_module hlds.passes_aux.
-:- import_module hlds.special_pred.
 :- import_module libs.compiler_util.
 :- import_module libs.globals.
-:- import_module libs.options.
-:- import_module libs.trace_params.
 :- import_module libs.tree.
 :- import_module ll_backend.call_gen.
 :- import_module ll_backend.code_util.
 :- import_module ll_backend.commit_gen.
-:- import_module ll_backend.continuation_info.
 :- import_module ll_backend.disj_gen.
 :- import_module ll_backend.ite_gen.
-:- import_module ll_backend.layout.
-:- import_module ll_backend.llds_out.
 :- import_module ll_backend.middle_rec.
 :- import_module ll_backend.par_conj_gen.
 :- import_module ll_backend.pragma_c_gen.
 :- import_module ll_backend.switch_gen.
-:- import_module ll_backend.trace.
 :- import_module ll_backend.unify_gen.
-:- import_module mdbcomp.prim_data.
-:- import_module mdbcomp.program_representation.
 :- import_module parse_tree.prog_data.
-:- import_module parse_tree.prog_out.
-:- import_module parse_tree.prog_util.
 
-:- import_module assoc_list.
 :- import_module bool.
-:- import_module char.
-:- import_module counter.
-:- import_module int.
+:- import_module list.
 :- import_module map.
 :- import_module maybe.
 :- import_module pair.
 :- import_module set.
-:- import_module solutions.
-:- import_module string.
-:- import_module term.
-:- import_module varset.
-
-%---------------------------------------------------------------------------%
-
-generate_code(ModuleInfo0, !GlobalData, Procedures, !IO) :-
-    % Get a list of all the predicate ids for which we will generate code.
-    module_info_predids(ModuleInfo0, PredIds),
-    % Now generate the code for each predicate.
-    generate_pred_list_code(ModuleInfo0, !GlobalData, PredIds,
-        Procedures, !IO).
-
-    % Translate a list of HLDS predicates to LLDS.
-    %
-:- pred generate_pred_list_code(module_info::in,
-    global_data::in, global_data::out,
-    list(pred_id)::in, list(c_procedure)::out, io::di, io::uo) is det.
-
-generate_pred_list_code(_ModuleInfo, !GlobalData, [], [], !IO).
-generate_pred_list_code(ModuleInfo, !GlobalData, [PredId | PredIds],
-        Predicates, !IO) :-
-    generate_maybe_pred_code(ModuleInfo, !GlobalData, PredId,
-        Predicates0, !IO),
-    generate_pred_list_code(ModuleInfo, !GlobalData, PredIds,
-        Predicates1, !IO),
-    list.append(Predicates0, Predicates1, Predicates).
-
-:- pred generate_maybe_pred_code(module_info::in,
-    global_data::in, global_data::out, pred_id::in,
-    list(c_procedure)::out, io::di, io::uo) is det.
-
-    % Note that some of the logic of generate_maybe_pred_code is duplicated
-    % by mercury_compile.backend_pass_by_preds, so modifications here may
-    % also need to be repeated there.
-    %
-generate_maybe_pred_code(ModuleInfo, !GlobalData, PredId, Predicates, !IO) :-
-    module_info_preds(ModuleInfo, PredInfos),
-    map.lookup(PredInfos, PredId, PredInfo),
-    ProcIds = pred_info_non_imported_procids(PredInfo),
-    (
-        ProcIds = [],
-        Predicates = []
-    ;
-        ProcIds = [_ | _],
-        module_info_get_globals(ModuleInfo, Globals),
-        globals.lookup_bool_option(Globals, very_verbose, VeryVerbose),
-        (
-            VeryVerbose = yes,
-            io.write_string("% Generating code for ", !IO),
-            hlds_out.write_pred_id(ModuleInfo, PredId, !IO),
-            io.write_string("\n", !IO),
-            globals.lookup_bool_option(Globals, detailed_statistics,
-                Statistics),
-            maybe_report_stats(Statistics, !IO)
-        ;
-            VeryVerbose = no
-        ),
-        generate_pred_code(ModuleInfo, !GlobalData,
-            PredId, PredInfo, ProcIds, Predicates)
-    ).
-
-    % Translate a HLDS predicate to LLDS.
-    %
-:- pred generate_pred_code(module_info::in, global_data::in, global_data::out,
-    pred_id::in, pred_info::in, list(proc_id)::in, list(c_procedure)::out)
-    is det.
-
-generate_pred_code(ModuleInfo, !GlobalData, PredId, PredInfo, ProcIds, Code) :-
-    generate_proc_list_code(ProcIds, PredId, PredInfo, ModuleInfo,
-        !GlobalData, [], Code).
-
-    % Translate all the procedures of a HLDS predicate to LLDS.
-    %
-:- pred generate_proc_list_code(list(proc_id)::in, pred_id::in, pred_info::in,
-    module_info::in, global_data::in, global_data::out,
-    list(c_procedure)::in, list(c_procedure)::out) is det.
-
-generate_proc_list_code([], _PredId, _PredInfo, _ModuleInfo,
-        !GlobalData, !Procs).
-generate_proc_list_code([ProcId | ProcIds], PredId, PredInfo, ModuleInfo0,
-        !GlobalData, !Procs) :-
-    pred_info_get_procedures(PredInfo, ProcInfos),
-    map.lookup(ProcInfos, ProcId, ProcInfo),
-    generate_proc_code(PredInfo, ProcInfo, ProcId, PredId, ModuleInfo0,
-        !GlobalData, Proc),
-    !:Procs = [Proc | !.Procs],
-    generate_proc_list_code(ProcIds, PredId, PredInfo, ModuleInfo0,
-        !GlobalData, !Procs).
-
-%---------------------------------------------------------------------------%
-
-    % Values of this type hold information about stack frames that is
-    % generated when generating prologs and is used in generating epilogs
-    % and when massaging the code generated for the procedure.
-
-:- type frame_info
-    --->    frame(
-                int,        % Number of slots in frame.
-
-                maybe(int), % Slot number of succip if succip is
-                            % present in a general slot.
-
-                bool        % Is this the frame of a model_non
-                            % proc defined via pragma C code?
-            ).
-
-%---------------------------------------------------------------------------%
-
-generate_proc_code(PredInfo, ProcInfo0, ProcId, PredId, ModuleInfo0,
-        !GlobalData, Proc) :-
-    % The modified module_info and proc_info are both discarded
-    % on return from generate_proc_code.
-    maybe_set_trace_level(PredInfo, ModuleInfo0, ModuleInfo),
-    ensure_all_headvars_are_named(ProcInfo0, ProcInfo),
-
-    proc_info_interface_determinism(ProcInfo, Detism),
-    proc_info_interface_code_model(ProcInfo, CodeModel),
-    proc_info_get_goal(ProcInfo, Goal),
-    Goal = _ - GoalInfo,
-    goal_info_get_follow_vars(GoalInfo, MaybeFollowVars),
-    (
-        MaybeFollowVars = yes(FollowVars)
-    ;
-        MaybeFollowVars = no,
-        map.init(FollowVarsMap),
-        FollowVars = abs_follow_vars(FollowVarsMap, 1)
-    ),
-    module_info_get_globals(ModuleInfo, Globals),
-    continuation_info.basic_stack_layout_for_proc(PredInfo, Globals,
-        BasicStackLayout, ForceProcId),
-    SaveSuccip = BasicStackLayout,
-
-    % Initialise the code_info structure. Generate_category_code below will use
-    % the returned OutsideResumePoint as the entry to the code that handles
-    % the failure of the procedure, if such code is needed. It is never needed
-    % for model_det procedures, always needed for model_semi procedures, and
-    % needed for model_non procedures only if we are doing execution tracing.
-    global_data_get_static_cell_info(!.GlobalData, StaticCellInfo0),
-    code_info_init(SaveSuccip, Globals, PredId, ProcId, PredInfo,
-        ProcInfo, FollowVars, ModuleInfo, StaticCellInfo0,
-        OutsideResumePoint, TraceSlotInfo, CodeInfo0),
-
-    % Find out the approriate context for the predicate's interface events.
-    pred_info_clauses_info(PredInfo, ClausesInfo),
-    get_clause_list(ClausesInfo ^ clauses_rep, Clauses),
-    (
-        Clauses = [],
-        % This predicate must have been created by the compiler. In that case,
-        % the context of the body goal is the best we can do.
-        goal_info_get_context(GoalInfo, ProcContext)
-    ;
-        Clauses = [FirstClause | _],
-        ProcContext = FirstClause ^ clause_context
-    ),
-
-    % Generate code for the procedure.
-    generate_category_code(CodeModel, ProcContext, Goal, OutsideResumePoint,
-        TraceSlotInfo, CodeTree, MaybeTraceCallLabel, FrameInfo,
-        CodeInfo0, CodeInfo),
-    code_info.get_max_reg_in_use_at_trace(CodeInfo, MaxTraceReg),
-    code_info.get_static_cell_info(CodeInfo, StaticCellInfo),
-    global_data_set_static_cell_info(StaticCellInfo, !GlobalData),
-
-    globals.get_trace_level(Globals, TraceLevel),
-    code_info.get_created_temp_frame(CodeInfo, CreatedTempFrame),
-
-    EffTraceIsNone = eff_trace_level_is_none(PredInfo, ProcInfo, TraceLevel),
-    (
-        EffTraceIsNone = no,
-        CreatedTempFrame = yes,
-        CodeModel \= model_non
-    ->
-        % If tracing is enabled, the procedure lives on the det stack and the
-        % code created any temporary nondet stack frames, then we must have
-        % reserved a stack slot for storing the value of maxfr; if we didn't,
-        % a retry command in the debugger from a point in the middle of this
-        % procedure will do the wrong thing.
-        proc_info_get_need_maxfr_slot(ProcInfo, HaveMaxfrSlot),
-        expect(unify(HaveMaxfrSlot, yes), this_file,
-            "should have reserved a slot for maxfr, but didn't")
-    ;
-        true
-    ),
-
-    % Turn the code tree into a list.
-    tree.flatten(CodeTree, FragmentList),
-    % Now the code is a list of code fragments (== list(instr)),
-    % so we need to do a level of unwinding to get a flat list.
-    list.condense(FragmentList, Instructions0),
-    FrameInfo = frame(TotalSlots, MaybeSuccipSlot, _),
-    (
-        MaybeSuccipSlot = yes(SuccipSlot),
-        % The set of recorded live values at calls (for value numbering)
-        % and returns (for accurate gc and execution tracing) do not yet record
-        % the stack slot holding the succip, so add it to those sets.
-        add_saved_succip(Instructions0,
-            SuccipSlot, Instructions)
-    ;
-        MaybeSuccipSlot = no,
-        Instructions = Instructions0
-    ),
-
-    proc_info_get_maybe_proc_table_info(ProcInfo, MaybeTableInfo),
-    (
-        ( BasicStackLayout = yes
-        ; MaybeTableInfo = yes(table_io_decl_info(_TableIoDeclInfo))
-        )
-    ->
-        % Create the procedure layout structure.
-        RttiProcLabel = rtti.make_rtti_proc_label(ModuleInfo,
-            PredId, ProcId),
-        code_info.get_layout_info(CodeInfo, InternalMap),
-        code_util.make_local_entry_label(ModuleInfo, PredId, ProcId,
-            no, EntryLabel),
-        proc_info_get_eval_method(ProcInfo, EvalMethod),
-        proc_info_get_initial_instmap(ProcInfo, ModuleInfo, InstMap0),
-        proc_info_get_headvars(ProcInfo, HeadVars),
-        proc_info_get_varset(ProcInfo, VarSet),
-        proc_info_get_argmodes(ProcInfo, ArgModes),
-        proc_info_get_vartypes(ProcInfo, VarTypes),
-        globals.get_trace_suppress(Globals, TraceSuppress),
-        (
-            eff_trace_needs_proc_body_reps(PredInfo, ProcInfo,
-                TraceLevel, TraceSuppress) = yes
-        ->
-            NeedGoalRep = yes
-        ;
-            NeedGoalRep = no
-        ),
-        NeedsAllNames = eff_trace_needs_all_var_names(PredInfo,
-            ProcInfo, TraceLevel, TraceSuppress),
-        proc_info_get_maybe_deep_profile_info(ProcInfo,
-            MaybeHLDSDeepInfo),
-        (
-            MaybeHLDSDeepInfo = yes(HLDSDeepInfo),
-            DeepProfInfo = generate_deep_prof_info(ProcInfo,
-                HLDSDeepInfo),
-            MaybeDeepProfInfo = yes(DeepProfInfo)
-        ;
-            MaybeHLDSDeepInfo = no,
-            MaybeDeepProfInfo = no
-        ),
-        EffTraceLevel = eff_trace_level(PredInfo, ProcInfo, TraceLevel),
-        ProcLayout = proc_layout_info(RttiProcLabel, EntryLabel,
-            Detism, TotalSlots, MaybeSuccipSlot, EvalMethod,
-            EffTraceLevel, MaybeTraceCallLabel, MaxTraceReg,
-            HeadVars, ArgModes, Goal, NeedGoalRep, InstMap0,
-            TraceSlotInfo, ForceProcId, VarSet, VarTypes,
-            InternalMap, MaybeTableInfo, NeedsAllNames,
-            MaybeDeepProfInfo),
-        global_data_add_new_proc_layout(proc(PredId, ProcId), ProcLayout,
-            !GlobalData)
-    ;
-        true
-    ),
-
-    code_info.get_closure_layouts(CodeInfo, ClosureLayouts),
-    global_data_add_new_closure_layouts(ClosureLayouts, !GlobalData),
-    ProcLabel = make_proc_label(ModuleInfo, PredId, ProcId),
-    maybe_add_tabling_pointer_var(ModuleInfo, PredId, ProcId, ProcInfo,
-        ProcLabel, !GlobalData),
-
-    Name = pred_info_name(PredInfo),
-    Arity = pred_info_orig_arity(PredInfo),
-
-    code_info.get_label_counter(CodeInfo, LabelCounter),
-    (
-        EffTraceIsNone = yes,
-        MayAlterRtti = may_alter_rtti
-    ;
-        EffTraceIsNone = no,
-        MayAlterRtti = must_not_alter_rtti
-    ),
-
-    globals.lookup_bool_option(Globals, generate_bytecode, GenBytecode),
-    (
-        % XXX: There is a mass of calls above that the bytecode doesn't need;
-        % work out which is and isn't needed and put inside the else case
-        % below.
-        GenBytecode = yes,
-        % We don't generate bytecode for unify and compare preds.
-        % The automatically generated unify and compare predicates
-        % are correct by construction; for user-defined unify and
-        % compare predicates, we *assume* their correctness for now
-        % (perhaps not wisely).
-        \+ is_unify_or_compare_pred(PredInfo),
-        % Don't generate bytecode for procs with foreign code.
-        goal_has_foreign(Goal) = no
-    ->
-        bytecode_stub(ModuleInfo, PredId, ProcId, ProcInstructions),
-        ProcLabelCounter = counter.init(0)
-    ;
-        ProcInstructions = Instructions,
-        ProcLabelCounter = LabelCounter
-    ),
-    Proc = c_procedure(Name, Arity, proc(PredId, ProcId), CodeModel,
-        ProcInstructions, ProcLabel, ProcLabelCounter, MayAlterRtti).
-
-:- pred maybe_set_trace_level(pred_info::in,
-    module_info::in, module_info::out) is det.
-
-maybe_set_trace_level(PredInfo, !ModuleInfo) :-
-    module_info_get_globals(!.ModuleInfo, Globals0),
-    (
-        PredModule = pred_info_module(PredInfo),
-        PredName = pred_info_name(PredInfo),
-        PredArity = pred_info_orig_arity(PredInfo),
-        no_type_info_builtin(PredModule, PredName, PredArity)
-    ->
-        % These predicates should never be traced, since they do not obey
-        % typeinfo_liveness. Since they may be opt_imported into other
-        % modules, we must switch off the tracing of such preds on a
-        % pred-by-pred basis.
-        globals.set_trace_level_none(Globals0, Globals1),
-        module_info_set_globals(Globals1, !ModuleInfo)
-    ;
-        pred_info_get_origin(PredInfo, special_pred(_)),
-        globals.get_trace_level(Globals0, TraceLevel),
-        UC_TraceLevel = trace_level_for_unify_compare(TraceLevel)
-    ->
-        globals.set_trace_level(UC_TraceLevel, Globals0, Globals1),
-        module_info_set_globals(Globals1, !ModuleInfo)
-    ;
-        true
-    ).
-
-:- func generate_deep_prof_info(proc_info, deep_profile_proc_info)
-    = proc_layout_proc_static.
-
-generate_deep_prof_info(ProcInfo, HLDSDeepInfo) = DeepProfInfo :-
-    HLDSDeepInfo ^ deep_layout = MaybeHLDSDeepLayout,
-    (
-        MaybeHLDSDeepLayout = yes(HLDSDeepLayout)
-    ;
-        MaybeHLDSDeepLayout = no,
-        unexpected(this_file,
-            "generate_deep_prof_info: no HLDS deep profiling layout info")
-    ),
-    HLDSDeepLayout = hlds_deep_layout(HLDSProcStatic, HLDSExcpVars),
-    HLDSExcpVars = hlds_deep_excp_vars(TopCSDVar, MiddleCSDVar,
-        MaybeOldOutermostVar),
-    proc_info_get_stack_slots(ProcInfo, StackSlots),
-    ( map.search(StackSlots, TopCSDVar, TopCSDSlot) ->
-        TopCSDSlotNum = stack_slot_num(TopCSDSlot),
-        map.lookup(StackSlots, MiddleCSDVar, MiddleCSDSlot),
-        MiddleCSDSlotNum = stack_slot_num(MiddleCSDSlot),
-        (
-            MaybeOldOutermostVar = yes(OldOutermostVar),
-            map.lookup(StackSlots, OldOutermostVar, OldOutermostSlot),
-            OldOutermostSlotNum = stack_slot_num(OldOutermostSlot)
-        ;
-            MaybeOldOutermostVar = no,
-            OldOutermostSlotNum = -1
-        )
-    ;
-        TopCSDSlotNum = -1,
-        MiddleCSDSlotNum = -1,
-        OldOutermostSlotNum = -1
-    ),
-    DeepExcpSlots = deep_excp_slots(TopCSDSlotNum, MiddleCSDSlotNum,
-        OldOutermostSlotNum),
-    DeepProfInfo = proc_layout_proc_static(HLDSProcStatic, DeepExcpSlots).
-
-:- pred maybe_add_tabling_pointer_var(module_info::in,
-    pred_id::in, proc_id::in, proc_info::in, proc_label::in,
-    global_data::in, global_data::out) is det.
-
-maybe_add_tabling_pointer_var(ModuleInfo, PredId, ProcId, ProcInfo, ProcLabel,
-        !GlobalData) :-
-    proc_info_get_eval_method(ProcInfo, EvalMethod),
-    HasTablingPointer = eval_method_has_per_proc_tabling_pointer(EvalMethod),
-    (
-        HasTablingPointer = yes,
-        module_info_get_name(ModuleInfo, ModuleName),
-        Var = tabling_pointer_var(ModuleName, ProcLabel),
-        global_data_add_new_proc_var(proc(PredId, ProcId), Var, !GlobalData)
-    ;
-        HasTablingPointer = no
-    ).
-
-%---------------------------------------------------------------------------%
-%---------------------------------------------------------------------------%
-
-    % Generate_category_code generates code for an entire procedure.
-    % Its algorithm has three or four main stages:
-    %
-    %   - generate code for the body goal
-    %   - generate code for the procedure entry
-    %   - generate code for the procedure exit
-    %   - generate code for the procedure fail (if needed)
-    %
-    % The first three tasks are forwarded to other procedures.
-    % The fourth task, if needed, is done by generate_category_code.
-    %
-    % The only caller of generate_category_code, generate_proc_code,
-    % has set up the code generator state to reflect what the machine
-    % state will be on entry to the procedure. Ensuring that the
-    % machine state at exit will conform to the expectation
-    % of the caller is the job of generate_exit.
-    %
-    % The reason why we generate the entry code after the body is that
-    % information such as the total number of stack slots needed,
-    % which is needed in the procedure entry prologue, cannot be
-    % conveniently obtained before generating the body, since the
-    % code generator may allocate temporary variables to hold values
-    % such as saved heap and trail pointers.
-    %
-    % Code_gen.generate_entry cannot depend on the code generator
-    % state, since when it is invoked this state is not appropriate
-    % for the procedure entry. Nor can it change the code generator state,
-    % since that would confuse generate_exit.
-    %
-    % Generating CALL trace events is done by generate_category_code,
-    % since only on entry to generate_category_code is the code generator
-    % state set up right. Generating EXIT trace events is done by
-    % generate_exit. Generating FAIL trace events is done
-    % by generate_category_code, since this requires modifying how
-    % we generate code for the body of the procedure (failures must
-    % now branch to a different place). Since FAIL trace events are
-    % part of the failure continuation, generate_category_code takes
-    % care of the failure continuation as well. (Model_det procedures
-    % of course have no failure continuation. Model_non procedures have
-    % a failure continuation, but in the absence of tracing this
-    % continuation needs no code. Only model_semi procedures need code
-    % for the failure continuation at all times.)
-    %
-:- pred generate_category_code(code_model::in, prog_context::in, hlds_goal::in,
-    resume_point_info::in, trace_slot_info::in, code_tree::out,
-    maybe(label)::out, frame_info::out, code_info::in, code_info::out) is det.
-
-generate_category_code(model_det, ProcContext, Goal, ResumePoint,
-        TraceSlotInfo, Code, MaybeTraceCallLabel, FrameInfo, !CI) :-
-    % Generate the code for the body of the procedure.
-    (
-        code_info.get_globals(!.CI, Globals),
-        globals.lookup_bool_option(Globals, middle_rec, yes),
-        middle_rec.match_and_generate(Goal, MiddleRecCode, !CI)
-    ->
-        Code = MiddleRecCode,
-        MaybeTraceCallLabel = no,
-        FrameInfo = frame(0, no, no)
-    ;
-        code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
-        (
-            MaybeTraceInfo = yes(TraceInfo),
-            trace.generate_external_event_code(call, TraceInfo,
-                ProcContext, MaybeCallExternalInfo, !CI),
-            (
-                MaybeCallExternalInfo = yes(CallExternalInfo),
-                CallExternalInfo = external_event_info(TraceCallLabel, _,
-                    TraceCallCode)
-            ;
-                MaybeCallExternalInfo = no,
-                unexpected(this_file,
-                    "generate_category_code: call events suppressed")
-            ),
-            MaybeTraceCallLabel = yes(TraceCallLabel)
-        ;
-            MaybeTraceInfo = no,
-            TraceCallCode = empty,
-            MaybeTraceCallLabel = no
-        ),
-        generate_goal(model_det, Goal, BodyCode, !CI),
-        generate_entry(!.CI, model_det, Goal, ResumePoint,
-            FrameInfo, EntryCode),
-        generate_exit(model_det, FrameInfo, TraceSlotInfo,
-            ProcContext, _, ExitCode, !CI),
-        Code = tree_list([EntryCode, TraceCallCode, BodyCode, ExitCode])
-    ).
-
-generate_category_code(model_semi, ProcContext, Goal, ResumePoint,
-        TraceSlotInfo, Code, MaybeTraceCallLabel, FrameInfo, !CI) :-
-    set.singleton_set(FailureLiveRegs, reg(r, 1)),
-    FailCode = node([
-        assign(reg(r, 1), const(false)) - "Fail",
-        livevals(FailureLiveRegs) - "",
-        goto(succip) - "Return from procedure call"
-    ]),
-    code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
-    (
-        MaybeTraceInfo = yes(TraceInfo),
-        trace.generate_external_event_code(call, TraceInfo, ProcContext,
-            MaybeCallExternalInfo, !CI),
-        (
-            MaybeCallExternalInfo = yes(CallExternalInfo),
-            CallExternalInfo = external_event_info(TraceCallLabel, _,
-                TraceCallCode)
-        ;
-            MaybeCallExternalInfo = no,
-            unexpected(this_file,
-                "generate_category_code: call events suppressed")
-        ),
-        MaybeTraceCallLabel = yes(TraceCallLabel),
-        generate_goal(model_semi, Goal, BodyCode, !CI),
-        generate_entry(!.CI, model_semi, Goal, ResumePoint,
-            FrameInfo, EntryCode),
-        generate_exit(model_semi, FrameInfo, TraceSlotInfo,
-            ProcContext, RestoreDeallocCode, ExitCode, !CI),
-
-        code_info.generate_resume_point(ResumePoint, ResumeCode, !CI),
-        code_info.resume_point_vars(ResumePoint, ResumeVarList),
-        set.list_to_set(ResumeVarList, ResumeVars),
-        code_info.set_forward_live_vars(ResumeVars, !CI),
-        % XXX A context that gives the end of the procedure definition
-        % would be better than ProcContext.
-        trace.generate_external_event_code(fail, TraceInfo, ProcContext,
-            MaybeFailExternalInfo, !CI),
-        (
-            MaybeFailExternalInfo = yes(FailExternalInfo),
-            FailExternalInfo = external_event_info(_, _, TraceFailCode)
-        ;
-            MaybeFailExternalInfo = no,
-            TraceFailCode = empty
-        ),
-        Code = tree_list([EntryCode, TraceCallCode, BodyCode, ExitCode,
-            ResumeCode, TraceFailCode, RestoreDeallocCode, FailCode])
-    ;
-        MaybeTraceInfo = no,
-        MaybeTraceCallLabel = no,
-        generate_goal(model_semi, Goal, BodyCode, !CI),
-        generate_entry(!.CI, model_semi, Goal, ResumePoint,
-            FrameInfo, EntryCode),
-        generate_exit(model_semi, FrameInfo, TraceSlotInfo,
-            ProcContext, RestoreDeallocCode, ExitCode, !CI),
-        code_info.generate_resume_point(ResumePoint, ResumeCode, !CI),
-        Code = tree_list([EntryCode, BodyCode, ExitCode,
-            ResumeCode, RestoreDeallocCode, FailCode])
-    ).
-
-generate_category_code(model_non, ProcContext, Goal, ResumePoint,
-        TraceSlotInfo, Code, MaybeTraceCallLabel, FrameInfo, !CI) :-
-    code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
-    (
-        MaybeTraceInfo = yes(TraceInfo),
-        trace.generate_external_event_code(call, TraceInfo, ProcContext,
-            MaybeCallExternalInfo, !CI),
-        (
-            MaybeCallExternalInfo = yes(CallExternalInfo),
-            CallExternalInfo = external_event_info(TraceCallLabel, _,
-                TraceCallCode)
-        ;
-            MaybeCallExternalInfo = no,
-            unexpected(this_file,
-                "generate_category_code: call events suppressed")
-        ),
-        MaybeTraceCallLabel = yes(TraceCallLabel),
-        generate_goal(model_non, Goal, BodyCode, !CI),
-        generate_entry(!.CI, model_non, Goal, ResumePoint,
-            FrameInfo, EntryCode),
-        generate_exit(model_non, FrameInfo, TraceSlotInfo,
-            ProcContext, _, ExitCode, !CI),
-
-        code_info.generate_resume_point(ResumePoint, ResumeCode, !CI),
-        code_info.resume_point_vars(ResumePoint, ResumeVarList),
-        set.list_to_set(ResumeVarList, ResumeVars),
-        code_info.set_forward_live_vars(ResumeVars, !CI),
-        % XXX A context that gives the end of the procedure definition
-        % would be better than ProcContext.
-        trace.generate_external_event_code(fail, TraceInfo, ProcContext,
-            MaybeFailExternalInfo, !CI),
-        (
-            MaybeFailExternalInfo = yes(FailExternalInfo),
-            FailExternalInfo = external_event_info(_, _, TraceFailCode)
-        ;
-            MaybeFailExternalInfo = no,
-            TraceFailCode = empty
-        ),
-        ( TraceSlotInfo ^ slot_trail = yes(_) ->
-            MaybeFromFull = TraceSlotInfo ^ slot_from_full,
-            (
-                MaybeFromFull = yes(FromFullSlot),
-                % Generate code which discards the ticket only if it was
-                % allocated, i.e. only if MR_trace_from_full was true on entry.
-                FromFullSlotLval =
-                    llds.stack_slot_num_to_lval(model_non, FromFullSlot),
-                code_info.get_next_label(SkipLabel, !CI),
-                DiscardTraceTicketCode = node([
-                    if_val(unop(logical_not, lval(FromFullSlotLval)),
-                        label(SkipLabel)) - "",
-                    discard_ticket - "discard retry ticket",
-                    label(SkipLabel) - ""
-                ])
-            ;
-                MaybeFromFull = no,
-                DiscardTraceTicketCode = node([
-                    discard_ticket - "discard retry ticket"
-                ])
-            )
-        ;
-            DiscardTraceTicketCode = empty
-        ),
-        FailCode = node([
-            goto(do_fail) - "fail after fail trace port"
-        ]),
-        Code = tree_list([EntryCode, TraceCallCode, BodyCode, ExitCode,
-            ResumeCode, TraceFailCode, DiscardTraceTicketCode, FailCode])
-    ;
-        MaybeTraceInfo = no,
-        MaybeTraceCallLabel = no,
-        generate_goal(model_non, Goal, BodyCode, !CI),
-        generate_entry(!.CI, model_non, Goal, ResumePoint,
-            FrameInfo, EntryCode),
-        generate_exit(model_non, FrameInfo, TraceSlotInfo,
-            ProcContext, _, ExitCode, !CI),
-        Code = tree_list([EntryCode, BodyCode, ExitCode])
-    ).
-
-%---------------------------------------------------------------------------%
-
-    % Generate the prologue for a procedure.
-    %
-    % The prologue will contain
-    %
-    %   a comment to mark prologue start
-    %   a comment explaining the stack layout
-    %   the procedure entry label
-    %   code to allocate a stack frame
-    %   code to fill in some special slots in the stack frame
-    %   a comment to mark prologue end
-    %
-    % At the moment the only special slots are the succip slot, and
-    % the slots holding the call number and call depth for tracing.
-    %
-    % Not all frames will have all these components. For example, the code
-    % to allocate a stack frame will be missing if the procedure doesn't
-    % need a stack frame, and if the procedure is nondet, then the code
-    % to fill in the succip slot is subsumed by the mkframe.
-
-:- pred generate_entry(code_info::in, code_model::in, hlds_goal::in,
-    resume_point_info::in, frame_info::out, code_tree::out) is det.
-
-generate_entry(CI, CodeModel, Goal, OutsideResumePoint, FrameInfo,
-        EntryCode) :-
-    code_info.get_stack_slots(CI, StackSlots),
-    code_info.get_varset(CI, VarSet),
-    SlotsComment = explain_stack_slots(StackSlots, VarSet),
-    StartComment = node([
-        comment("Start of procedure prologue") - "",
-        comment(SlotsComment) - ""
-    ]),
-    code_info.get_total_stackslot_count(CI, MainSlots),
-    code_info.get_pred_id(CI, PredId),
-    code_info.get_proc_id(CI, ProcId),
-    code_info.get_module_info(CI, ModuleInfo),
-    code_util.make_local_entry_label(ModuleInfo, PredId, ProcId, no, Entry),
-    LabelCode = node([
-        label(Entry) - "Procedure entry point"
-    ]),
-    code_info.get_succip_used(CI, Used),
-    (
-        % Do we need to save the succip across calls?
-        Used = yes,
-        % Do we need to use a general slot for storing succip?
-        CodeModel \= model_non
-    ->
-        SuccipSlot = MainSlots + 1,
-        SaveSuccipCode = node([
-            assign(stackvar(SuccipSlot), lval(succip)) - "Save the success ip"
-        ]),
-        TotalSlots = SuccipSlot,
-        MaybeSuccipSlot = yes(SuccipSlot)
-    ;
-        SaveSuccipCode = empty,
-        TotalSlots = MainSlots,
-        MaybeSuccipSlot = no
-    ),
-    code_info.get_maybe_trace_info(CI, MaybeTraceInfo),
-    (
-        MaybeTraceInfo = yes(TraceInfo),
-        trace.generate_slot_fill_code(CI, TraceInfo, TraceFillCode)
-    ;
-        MaybeTraceInfo = no,
-        TraceFillCode = empty
-    ),
-    module_info_pred_info(ModuleInfo, PredId, PredInfo),
-    ModuleName = pred_info_module(PredInfo),
-    PredName = pred_info_name(PredInfo),
-    Arity = pred_info_orig_arity(PredInfo),
-
-    PushMsg = push_msg(ModuleInfo, PredId, ProcId),
-    ( CodeModel = model_non ->
-        code_info.resume_point_stack_addr(OutsideResumePoint,
-            OutsideResumeAddress),
-        (
-            Goal = foreign_proc(_, _, _, _, _, PragmaCode) - _,
-            PragmaCode = nondet(Fields, FieldsContext,
-                _, _, _, _, _, _, _)
-        ->
-            StructName = pragma_c_gen.struct_name(ModuleName, PredName, Arity,
-                ProcId),
-            Struct = pragma_c_struct(StructName, Fields, FieldsContext),
-            string.format("#define\tMR_ORDINARY_SLOTS\t%d\n",
-                [i(TotalSlots)], DefineStr),
-            DefineComponents = [pragma_c_raw_code(DefineStr,
-                cannot_branch_away, live_lvals_info(set.init))],
-            NondetFrameInfo = ordinary_frame(PushMsg, TotalSlots, yes(Struct)),
-            AllocCode = node([
-                mkframe(NondetFrameInfo, yes(OutsideResumeAddress))
-                    - "Allocate stack frame",
-                pragma_c([], DefineComponents, will_not_call_mercury,
-                    no, no, no, no, no, no) - ""
-            ]),
-            NondetPragma = yes
-        ;
-            NondetFrameInfo = ordinary_frame(PushMsg, TotalSlots, no),
-            AllocCode = node([
-                mkframe(NondetFrameInfo, yes(OutsideResumeAddress))
-                    - "Allocate stack frame"
-            ]),
-            NondetPragma = no
-        )
-    ; TotalSlots > 0 ->
-        AllocCode = node([
-            incr_sp(TotalSlots, PushMsg) - "Allocate stack frame"
-        ]),
-        NondetPragma = no
-    ;
-        AllocCode = empty,
-        NondetPragma = no
-    ),
-    FrameInfo = frame(TotalSlots, MaybeSuccipSlot, NondetPragma),
-    EndComment = node([
-        comment("End of procedure prologue") - ""
-    ]),
-    EntryCode = tree_list([StartComment, LabelCode, AllocCode,
-        SaveSuccipCode, TraceFillCode, EndComment]).
-
-%---------------------------------------------------------------------------%
-
-    % Generate the success epilogue for a procedure.
-    %
-    % The success epilogue will contain
-    %
-    %   a comment to mark epilogue start
-    %   code to place the output arguments where their caller expects
-    %   code to restore registers from some special slots
-    %   code to deallocate the stack frame
-    %   code to set r1 to MR_TRUE (for semidet procedures only)
-    %   a jump back to the caller, including livevals information
-    %   a comment to mark epilogue end
-    %
-    % The parts of this that restore registers and deallocate the stack
-    % frame are also part of the failure epilog, which is handled by
-    % our caller; this is why we return RestoreDeallocCode.
-    %
-    % At the moment the only special slots are the succip slot, and
-    % the tracing slots (holding the call sequence number, call event
-    % number, call depth, from-full indication, and trail state).
-    %
-    % Not all frames will have all these components. For example, for
-    % nondet procedures we don't deallocate the stack frame before
-    % success.
-    %
-    % Epilogues for procedures defined by nondet pragma C codes do not
-    % follow the rules above. For such procedures, the normal functions
-    % of the epilogue are handled when traversing the pragma C code goal;
-    % we need only #undef a macro defined by the procedure prologue.
-
-:- pred generate_exit(code_model::in, frame_info::in,
-    trace_slot_info::in, prog_context::in, code_tree::out, code_tree::out,
-    code_info::in, code_info::out) is det.
-
-generate_exit(CodeModel, FrameInfo, TraceSlotInfo, ProcContext,
-        RestoreDeallocCode, ExitCode, !CI) :-
-    StartComment = node([
-        comment("Start of procedure epilogue") - ""
-    ]),
-    EndComment = node([
-        comment("End of procedure epilogue") - ""
-    ]),
-    FrameInfo = frame(TotalSlots, MaybeSuccipSlot, NondetPragma),
-    ( NondetPragma = yes ->
-        UndefStr = "#undef\tMR_ORDINARY_SLOTS\n",
-        UndefComponents = [pragma_c_raw_code(UndefStr, cannot_branch_away,
-            live_lvals_info(set.init))],
-        UndefCode = node([
-            pragma_c([], UndefComponents, will_not_call_mercury,
-                no, no, no, no, no, no) - ""
-        ]),
-        RestoreDeallocCode = empty, % always empty for nondet code
-        ExitCode = tree_list([StartComment, UndefCode, EndComment])
-    ;
-        code_info.get_instmap(!.CI, Instmap),
-        ArgModes = code_info.get_arginfo(!.CI),
-        HeadVars = code_info.get_headvars(!.CI),
-        assoc_list.from_corresponding_lists(HeadVars, ArgModes, Args),
-        ( instmap.is_unreachable(Instmap) ->
-            OutLvals = set.init,
-            FlushCode = empty
-        ;
-            code_info.setup_return(Args, OutLvals, FlushCode, !CI)
-        ),
-        (
-            MaybeSuccipSlot = yes(SuccipSlot),
-            RestoreSuccipCode = node([
-                assign(succip, lval(stackvar(SuccipSlot))) -
-                    "restore the success ip"
-            ])
-        ;
-            MaybeSuccipSlot = no,
-            RestoreSuccipCode = empty
-        ),
-        (
-            ( TotalSlots = 0
-            ; CodeModel = model_non
-            )
-        ->
-            DeallocCode = empty
-        ;
-            DeallocCode = node([
-                decr_sp(TotalSlots) - "Deallocate stack frame"
-            ])
-        ),
-        (
-            TraceSlotInfo ^ slot_trail = yes(_),
-            CodeModel \= model_non
-        ->
-            MaybeFromFull = TraceSlotInfo ^ slot_from_full,
-            (
-                MaybeFromFull = yes(FromFullSlot),
-                % Generate code which prunes the ticket only if it was
-                % allocated, i.e. only if MR_trace_from_full was true on entry.
-                %
-                % Note that to avoid duplicating label names, we need to
-                % generate two different copies of this with different labels;
-                % this is needed for semidet code, which will get one copy
-                % in the success epilogue and one copy in the failure epilogue.
-                %
-                FromFullSlotLval =
-                    llds.stack_slot_num_to_lval(CodeModel, FromFullSlot),
-                code_info.get_next_label(SkipLabel, !CI),
-                code_info.get_next_label(SkipLabelCopy, !CI),
-                PruneTraceTicketCode = node([
-                    if_val(unop(logical_not, lval(FromFullSlotLval)),
-                        label(SkipLabel)) - "",
-                    prune_ticket - "prune retry ticket",
-                    label(SkipLabel) - ""
-                ]),
-                PruneTraceTicketCodeCopy = node([
-                    if_val(unop(logical_not, lval(FromFullSlotLval)),
-                        label(SkipLabelCopy)) - "",
-                    prune_ticket - "prune retry ticket",
-                    label(SkipLabelCopy) - ""
-                ])
-            ;
-                MaybeFromFull = no,
-                PruneTraceTicketCode = node([
-                    prune_ticket - "prune retry ticket"
-                ]),
-                PruneTraceTicketCodeCopy = PruneTraceTicketCode
-            )
-        ;
-            PruneTraceTicketCode = empty,
-            PruneTraceTicketCodeCopy = empty
-        ),
-
-        RestoreDeallocCode = tree_list([RestoreSuccipCode,
-            PruneTraceTicketCode, DeallocCode]),
-        RestoreDeallocCodeCopy = tree_list([RestoreSuccipCode,
-            PruneTraceTicketCodeCopy, DeallocCode]),
-
-        code_info.get_maybe_trace_info(!.CI, MaybeTraceInfo),
-        (
-            MaybeTraceInfo = yes(TraceInfo),
-            % XXX A context that gives the end of the procedure definition
-            % would be better than CallContext.
-            trace.generate_external_event_code(exit, TraceInfo, ProcContext,
-                MaybeExitExternalInfo, !CI),
-            (
-                MaybeExitExternalInfo = yes(ExitExternalInfo),
-                ExitExternalInfo = external_event_info(_, TypeInfoDatas,
-                    TraceExitCode)
-            ;
-                MaybeExitExternalInfo = no,
-                TypeInfoDatas = map.init,
-                TraceExitCode = empty
-            ),
-            map.values(TypeInfoDatas, TypeInfoLocnSets),
-            FindBaseLvals = (pred(Lval::out) is nondet :-
-                list.member(LocnSet, TypeInfoLocnSets),
-                set.member(Locn, LocnSet),
-                (
-                    Locn = direct(Lval)
-                ;
-                    Locn = indirect(Lval, _)
-                )
-            ),
-            solutions.solutions(FindBaseLvals, TypeInfoLvals),
-            set.insert_list(OutLvals, TypeInfoLvals, LiveLvals)
-        ;
-            MaybeTraceInfo = no,
-            TraceExitCode = empty,
-            LiveLvals = OutLvals
-        ),
-
-        (
-            CodeModel = model_det,
-            SuccessCode = node([
-                livevals(LiveLvals) - "",
-                goto(succip) - "Return from procedure call"
-            ]),
-            AllSuccessCode = tree_list([TraceExitCode, RestoreDeallocCodeCopy,
-                SuccessCode])
-        ;
-            CodeModel = model_semi,
-            set.insert(LiveLvals, reg(r, 1), SuccessLiveRegs),
-            SuccessCode = node([
-                assign(reg(r, 1), const(true)) - "Succeed",
-                livevals(SuccessLiveRegs) - "",
-                goto(succip) - "Return from procedure call"
-            ]),
-            AllSuccessCode = tree_list([TraceExitCode, RestoreDeallocCodeCopy,
-                SuccessCode])
-        ;
-            CodeModel = model_non,
-            (
-                MaybeTraceInfo = yes(TraceInfo2),
-                trace.maybe_setup_redo_event(TraceInfo2, SetupRedoCode)
-            ;
-                MaybeTraceInfo = no,
-                SetupRedoCode = empty
-            ),
-            SuccessCode = node([
-                livevals(LiveLvals) - "",
-                goto(do_succeed(no)) - "Return from procedure call"
-            ]),
-            AllSuccessCode = tree_list([SetupRedoCode,
-                TraceExitCode, SuccessCode])
-        ),
-        ExitCode = tree_list([StartComment, FlushCode, AllSuccessCode,
-            EndComment])
-    ).
 
 %---------------------------------------------------------------------------%
 
@@ -1067,8 +80,8 @@
         IsAtomic = no
     ),
     code_info.pre_goal_update(GoalInfo, IsAtomic, !CI),
-    code_info.get_instmap(!.CI, Instmap),
-    ( instmap.is_reachable(Instmap) ->
+    code_info.get_instmap(!.CI, InstMap),
+    ( instmap.is_reachable(InstMap) ->
         goal_info_get_code_model(GoalInfo, CodeModel),
         % Sanity check: code of some code models should occur
         % only in limited contexts.
@@ -1131,9 +144,7 @@
         % slots, but they won't *need* stack slots either, since there is no
         % way for such a leaf procedure to throw an exception. (Throwing
         % requires calling exception.throw, directly or indirectly.)
-        (
-            set.member(save_deep_excp_vars, Features)
-        ->
+        ( set.member(save_deep_excp_vars, Features) ->
             DeepSaveVars = compute_deep_save_excp_vars(ProcInfo),
             save_variables_on_stack(DeepSaveVars, DeepSaveCode, !CI),
             Code = tree(CodeUptoTip, DeepSaveCode)
@@ -1143,7 +154,7 @@
 
         % Make live any variables which subsequent goals will expect to be
         % live, but were not generated.
-        code_info.set_instmap(Instmap, !CI),
+        code_info.set_instmap(InstMap, !CI),
         code_info.post_goal_update(GoalInfo, !CI)
     ;
         Code = empty
@@ -1185,62 +196,72 @@
 :- pred generate_goal_2(hlds_goal_expr::in, hlds_goal_info::in,
     code_model::in, code_tree::out, code_info::in, code_info::out) is det.
 
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = unify(_, _, _, Uni, _),
-    unify_gen.generate_unification(CodeModel, Uni, GoalInfo, Code, !CI).
-generate_goal_2(conj(ConjType, Goals), GoalInfo, CodeModel, Code, !CI) :-
+generate_goal_2(GoalExpr, GoalInfo, CodeModel, Code, !CI) :-
+    (
+        GoalExpr = unify(_, _, _, Uni, _),
+        unify_gen.generate_unification(CodeModel, Uni, GoalInfo, Code, !CI)
+    ;
+        GoalExpr = conj(ConjType, Goals),
     (
         ConjType = plain_conj,
         generate_goals(Goals, CodeModel, Code, !CI)
     ;
         ConjType = parallel_conj,
-        par_conj_gen.generate_par_conj(Goals, GoalInfo, CodeModel, Code, !CI)
-    ).
-generate_goal_2(disj(Goals), GoalInfo, CodeModel, Code, !CI) :-
+            par_conj_gen.generate_par_conj(Goals, GoalInfo, CodeModel, Code,
+                !CI)
+        )
+    ;
+        GoalExpr = disj(Goals),
     AddTrailOps = should_add_trail_ops(!.CI, GoalInfo),
-    disj_gen.generate_disj(AddTrailOps, CodeModel, Goals, GoalInfo, Code, !CI).
-generate_goal_2(not(Goal), GoalInfo, CodeModel, Code, !CI) :-
+        disj_gen.generate_disj(AddTrailOps, CodeModel, Goals, GoalInfo, Code,
+            !CI)
+    ;
+        GoalExpr = not(Goal),
     AddTrailOps = should_add_trail_ops(!.CI, GoalInfo),
     ite_gen.generate_negation(AddTrailOps, CodeModel, Goal, GoalInfo,
-        Code, !CI).
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = if_then_else(_Vars, Cond, Then, Else),
+            Code, !CI)
+    ;
+        GoalExpr = if_then_else(_Vars, Cond, Then, Else),
     AddTrailOps = should_add_trail_ops(!.CI, GoalInfo),
-    ite_gen.generate_ite(AddTrailOps, CodeModel, Cond, Then, Else, GoalInfo,
-        Code, !CI).
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = switch(Var, CanFail, CaseList),
+        ite_gen.generate_ite(AddTrailOps, CodeModel, Cond, Then, Else,
+            GoalInfo, Code, !CI)
+    ;
+        GoalExpr = switch(Var, CanFail, CaseList),
     switch_gen.generate_switch(CodeModel, Var, CanFail, CaseList, GoalInfo,
-        Code, !CI).
-generate_goal_2(scope(_, Goal), GoalInfo, CodeModel, Code, !CI) :-
+            Code, !CI)
+    ;
+        GoalExpr = scope(_, Goal),
     AddTrailOps = should_add_trail_ops(!.CI, GoalInfo),
-    commit_gen.generate_commit(AddTrailOps, CodeModel, Goal, Code, !CI).
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = generic_call(GenericCall, Args, Modes, Det),
+        commit_gen.generate_commit(AddTrailOps, CodeModel, Goal, Code, !CI)
+    ;
+        GoalExpr = generic_call(GenericCall, Args, Modes, Det),
     call_gen.generate_generic_call(CodeModel, GenericCall, Args,
-        Modes, Det, GoalInfo, Code, !CI).
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = call(PredId, ProcId, Args, BuiltinState, _, _),
+            Modes, Det, GoalInfo, Code, !CI)
+    ;
+        GoalExpr = call(PredId, ProcId, Args, BuiltinState, _, _),
     ( BuiltinState = not_builtin ->
         call_gen.generate_call(CodeModel, PredId, ProcId, Args,
             GoalInfo, Code, !CI)
     ;
         call_gen.generate_builtin(CodeModel, PredId, ProcId, Args,
             Code, !CI)
-    ).
-generate_goal_2(Goal, GoalInfo, CodeModel, Code, !CI) :-
-    Goal = foreign_proc(Attributes, PredId, ProcId, Args, ExtraArgs,
+        )
+    ;
+        GoalExpr = foreign_proc(Attributes, PredId, ProcId, Args, ExtraArgs,
         PragmaCode),
     ( c = foreign_language(Attributes) ->
         pragma_c_gen.generate_pragma_c_code(CodeModel, Attributes,
-            PredId, ProcId, Args, ExtraArgs, GoalInfo, PragmaCode, Code, !CI)
+                PredId, ProcId, Args, ExtraArgs, GoalInfo, PragmaCode, Code,
+                    !CI)
     ;
         unexpected(this_file,
             "generate_goal_2: foreign code other than C unexpected")
-    ).
-generate_goal_2(shorthand(_), _, _, _, !CI) :-
+        )
+    ;
+        GoalExpr = shorthand(_),
     % These should have been expanded out by now.
-    unexpected(this_file, "generate_goal_2: unexpected shorthand").
+        unexpected(this_file, "generate_goal_2: unexpected shorthand")
+    ).
 
 %---------------------------------------------------------------------------%
 
@@ -1261,133 +282,6 @@
         generate_goals(Goals, CodeModel, Code2, !CI),
         Code = tree(Code1, Code2)
     ).
-
-%---------------------------------------------------------------------------%
-
-    % Add the succip to the livevals before and after calls. Traverses the list
-    % of instructions looking for livevals and calls, adding succip in the
-    % stackvar number given as an argument.
-    %
-:- pred add_saved_succip(list(instruction)::in, int::in,
-    list(instruction)::out) is det.
-
-add_saved_succip([], _StackLoc, []).
-add_saved_succip([Instrn0 - Comment | Instrns0 ], StackLoc,
-        [Instrn - Comment | Instrns]) :-
-    (
-        Instrn0 = livevals(LiveVals0),
-        Instrns0 \= [goto(succip) - _ | _]
-        % XXX We should also test for tailcalls
-        % once we start generating them directly.
-    ->
-        set.insert(LiveVals0, stackvar(StackLoc), LiveVals1),
-        Instrn = livevals(LiveVals1)
-    ;
-        Instrn0 = call(Target, ReturnLabel, LiveVals0, Context, GP, CM)
-    ->
-        map.init(Empty),
-        LiveVals = [live_lvalue(direct(stackvar(StackLoc)), succip, Empty)
-            | LiveVals0],
-        Instrn = call(Target, ReturnLabel, LiveVals, Context, GP, CM)
-    ;
-        Instrn = Instrn0
-    ),
-    add_saved_succip(Instrns0, StackLoc, Instrns).
-
-%---------------------------------------------------------------------------%
-
-:- pred bytecode_stub(module_info::in, pred_id::in, proc_id::in,
-    list(instruction)::out) is det.
-
-bytecode_stub(ModuleInfo, PredId, ProcId, BytecodeInstructions) :-
-
-    module_info_pred_info(ModuleInfo, PredId, PredInfo),
-    ModuleSymName = pred_info_module(PredInfo),
-
-    sym_name_to_string(ModuleSymName, "__", ModuleName),
-
-    code_util.make_local_entry_label(ModuleInfo, PredId, ProcId, no, Entry),
-
-    PredName = pred_info_name(PredInfo),
-    proc_id_to_int(ProcId, ProcNum),
-    string.int_to_string(ProcNum, ProcStr),
-    Arity = pred_info_orig_arity(PredInfo),
-    int_to_string(Arity, ArityStr),
-    PredOrFunc = pred_info_is_pred_or_func(PredInfo),
-
-    CallStructName = "bytecode_call_info",
-
-    append_list([
-        "\t\tstatic MB_Call ", CallStructName, " = {\n",
-        "\t\t\t(MB_Word)NULL,\n",
-        "\t\t\t""", ModuleName, """,\n",
-        "\t\t\t""", PredName, """,\n",
-        "\t\t\t", ProcStr, ",\n",
-        "\t\t\t", ArityStr, ",\n",
-        "\t\t\t", (PredOrFunc = function -> "MR_TRUE" ; "MR_FALSE"), "\n",
-        "\t\t};\n"
-        ], CallStruct),
-
-    append_list([
-        "\t\tMB_Native_Addr return_addr;\n",
-        "\t\tMR_save_registers();\n",
-        "\t\treturn_addr = MB_bytecode_call_entry(", "&",CallStructName,");\n",
-        "\t\tMR_restore_registers();\n",
-        "\t\tMR_GOTO(return_addr);\n"
-        ], BytecodeCall),
-
-    BytecodeInstructionsComponents = [
-        pragma_c_raw_code("\t{\n", cannot_branch_away,
-            live_lvals_info(set.init)),
-        pragma_c_raw_code(CallStruct, cannot_branch_away,
-            live_lvals_info(set.init)),
-        pragma_c_raw_code(BytecodeCall, cannot_branch_away,
-            no_live_lvals_info),
-        pragma_c_raw_code("\t}\n", cannot_branch_away,
-            live_lvals_info(set.init))
-    ],
-
-    BytecodeInstructions = [
-        label(Entry) - "Procedure entry point",
-        pragma_c([], BytecodeInstructionsComponents, may_call_mercury,
-            no, no, no, no, no, no) - "Entry stub"
-    ].
-
-%---------------------------------------------------------------------------%
-
-:- type type_giving_arg
-    --->    last_arg
-    ;       last_but_one_arg.
-
-push_msg(ModuleInfo, PredId, ProcId) = PushMsg :-
-    module_info_pred_info(ModuleInfo, PredId, PredInfo),
-    PredOrFunc = pred_info_is_pred_or_func(PredInfo),
-    ModuleName = pred_info_module(PredInfo),
-    PredName = pred_info_name(PredInfo),
-    Arity = pred_info_orig_arity(PredInfo),
-    pred_info_get_origin(PredInfo, Origin),
-    ( Origin = special_pred(SpecialId - TypeCtor) ->
-        find_arg_type_ctor_name(TypeCtor, TypeName),
-        SpecialPredName = get_special_pred_id_generic_name(SpecialId),
-        FullPredName = SpecialPredName ++ "_for_" ++ TypeName
-    ;
-        FullPredName = PredName
-    ),
-    % XXX if ModuleNameString ends with [0-9] and/or FullPredName starts with
-    % [0-9] then ideally we should use "'.'" rather than just ".".
-    %
-    PushMsg = pred_or_func_to_str(PredOrFunc) ++ " " ++
-        sym_name_to_string(ModuleName) ++ "." ++
-        FullPredName ++ "/" ++ int_to_string(Arity) ++ "-" ++
-        int_to_string(proc_id_to_int(ProcId)).
-
-:- pred find_arg_type_ctor_name((type_ctor)::in, string::out) is det.
-
-find_arg_type_ctor_name(TypeCtor, TypeName) :-
-    TypeCtor = type_ctor(TypeCtorSymName, TypeCtorArity),
-    mdbcomp.prim_data.sym_name_to_string(TypeCtorSymName, TypeCtorName),
-    string.int_to_string(TypeCtorArity, ArityStr),
-    string.append_list([TypeCtorName, "_", ArityStr], TypeName).
 
 %---------------------------------------------------------------------------%
 
Index: compiler/code_info.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/code_info.m,v
retrieving revision 1.320
diff -u -b -r1.320 code_info.m
--- compiler/code_info.m	26 Apr 2006 03:05:31 -0000	1.320
+++ compiler/code_info.m	1 May 2006 03:14:38 -0000
@@ -3427,8 +3427,7 @@
         RealStackVarLocs = [],
         DummyStackVarLocs = []
     ;
-        compute_forward_live_var_saves(!.CI, OutVarSet,
-            ForwardVarLocs),
+        compute_forward_live_var_saves(!.CI, OutVarSet, ForwardVarLocs),
         goal_info_get_code_model(GoalInfo, CodeModel),
         ( CodeModel = model_non ->
             % Save variables protected by the nearest resumption point on the
Index: compiler/ll_backend.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/ll_backend.m,v
retrieving revision 1.15
diff -u -b -r1.15 ll_backend.m
--- compiler/ll_backend.m	26 Apr 2006 03:05:35 -0000	1.15
+++ compiler/ll_backend.m	29 Apr 2006 09:18:02 -0000
@@ -34,7 +34,8 @@
 :- include_module code_util.
 
 % The HLDS->LLDS code generator.
-:- include_module code_gen.
+:- include_module proc_gen.
+   :- include_module code_gen.
    :- include_module ite_gen.
    :- include_module call_gen.
    :- include_module disj_gen.
Index: compiler/lookup_switch.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lookup_switch.m,v
retrieving revision 1.66
diff -u -b -r1.66 lookup_switch.m
--- compiler/lookup_switch.m	26 Apr 2006 03:05:36 -0000	1.66
+++ compiler/lookup_switch.m	1 May 2006 05:49:04 -0000
@@ -242,8 +242,10 @@
         LastVal = LastCaseVal
     ),
     figure_out_output_vars(!.CI, GoalInfo, OutVars),
+    code_info.remember_position(!.CI, CurPos),
     generate_constants(TaggedCases, OutVars, StoreMap, !MaybeEnd,
         CaseSolns, MaybeLiveness, set.init, ResumeVars, no, GoalTrailOps, !CI),
+    code_info.reset_to_position(CurPos, !CI),
     (
         MaybeLiveness = yes(Liveness)
     ;
@@ -323,6 +325,12 @@
         MaybeLiveness, !ResumeVars, !GoalTrailOps, !CI) :-
     Case = case(_, int_constant(CaseTag), _, Goal),
     Goal = GoalExpr - GoalInfo,
+
+    % Goals with these features need special treatment in generate_goal.
+    goal_info_get_features(GoalInfo, Features),
+    not set.member(call_table_gen, Features),
+    not set.member(save_deep_excp_vars, Features),
+
     ( GoalExpr = disj(Disjuncts) ->
         bool.or(goal_may_modify_trail(GoalInfo), !GoalTrailOps),
         (
@@ -341,13 +349,25 @@
                 ThisResumePoint = no_resume_point
             )
         ),
-        all_disjuncts_are_conj_of_unify(Disjuncts, StdDisjuncts),
-        generate_constants_for_disjuncts(StdDisjuncts, Vars, StoreMap,
-            !MaybeEnd, Solns, MaybeLiveness, !CI),
+        all_disjuncts_are_conj_of_unify(Disjuncts),
+
+        % We execute the pre- and post-goal update for the disjunction.
+        % The pre- and post-goal updates for the disjuncts themselves are
+        % done as part of the call to generate_goal in
+        % generate_constants_for_disjuncts in lookup_util.m.
+        code_info.pre_goal_update(GoalInfo, no, !CI),
+        code_info.get_instmap(!.CI, InstMap),
+        generate_constants_for_disjuncts(Disjuncts, Vars, StoreMap, !MaybeEnd,
+            Solns, MaybeLiveness, !CI),
+        code_info.set_instmap(InstMap, !CI),
+        code_info.post_goal_update(GoalInfo, !CI),
         CaseVal = CaseTag - several_solns(Solns)
     ;
-        goal_is_conj_of_unify(Goal, StdGoal),
-        generate_constants_for_arm(StdGoal, Vars, StoreMap, !MaybeEnd, Soln,
+        goal_is_conj_of_unify(Goal),
+        % The pre- and post-goal updates for the goals themselves are
+        % done as part of the call to generate_goal in
+        % generate_constants_for_disjuncts in lookup_util.m.
+        generate_constants_for_arm(Goal, Vars, StoreMap, !MaybeEnd, Soln,
             Liveness, !CI),
         MaybeLiveness = yes(Liveness),
         CaseVal = CaseTag - one_soln(Soln)
@@ -546,8 +566,8 @@
     list.reverse(RevLaterSolnArray, LaterSolnArray),
     MainRowTypes = [integer, integer | LLDSTypes],
     list.length(MainRowTypes, MainRowWidth),
-    code_info.add_vector_static_cell(MainRowTypes, MainRows,
-        MainVectorAddr, !CI),
+    code_info.add_vector_static_cell(MainRowTypes, MainRows, MainVectorAddr,
+        !CI),
     MainVectorAddrRval = const(data_addr_const(MainVectorAddr, no)),
     code_info.add_vector_static_cell(LLDSTypes, LaterSolnArray,
         LaterVectorAddr, !CI),
@@ -556,6 +576,14 @@
     % Since we release BaseReg only after the calls to generate_branch_end,
     % we must make sure that generate_branch_end won't want to overwrite
     % BaseReg.
+    %
+    % We release BaseReg in each arm of generate_code_for_each_kind below.
+    % We cannot release it at the bottom of this predicate, because in the
+    % kind_several_solns arm of generate_code_for_each_kind the generation
+    % of the resume point will clobber the set of acquired registers.
+    %
+    % We cannot release the stack slots anywhere, since they will be needed
+    % after backtracking.
     code_info.acquire_reg_not_in_storemap(StoreMap, BaseReg, !CI),
     code_info.acquire_temp_slot(lookup_switch_cur, CurSlot, !CI),
     code_info.acquire_temp_slot(lookup_switch_max, MaxSlot, !CI),
@@ -578,9 +606,6 @@
         ResumeVars, AddTrailOps, OutVars, StoreMap, MaybeEnd0, Liveness,
         KindsCode, !CI),
 
-    code_info.release_reg(BaseReg, !CI),
-    % We cannot release the stack slots, since they will be needed after
-    % backtracking.
     code_info.set_resume_point_to_unknown(!CI),
     EndLabelCode = node([
         label(EndLabel) - "end of several_soln lookup switch"
@@ -613,6 +638,7 @@
         Kind = kind_zero_solns,
         TestOp = int_ge,
         code_info.reset_to_position(BranchStart, !CI),
+        code_info.release_reg(BaseReg, !CI),
         code_info.generate_failure(KindCode, !CI)
     ;
         Kind = kind_one_soln,
@@ -621,6 +647,7 @@
         generate_offset_assigns(OutVars, 2, BaseReg, !CI),
         set_liveness_and_end_branch(StoreMap, MaybeEnd0, Liveness,
             BranchEndCode, !CI),
+        code_info.release_reg(BaseReg, !CI),
         GotoEndCode = node([
             goto(label(EndLabel)) - "goto end of switch from one_soln"
         ]),
@@ -672,6 +699,7 @@
 
         set_liveness_and_end_branch(StoreMap, MaybeEnd0, Liveness,
             FirstBranchEndCode, !CI),
+        code_info.release_reg(BaseReg, !CI),
 
         GotoEndCode = node([
             goto(label(EndLabel)) - "goto end of switch from several_soln"
Index: compiler/lookup_util.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/lookup_util.m,v
retrieving revision 1.1
diff -u -b -r1.1 lookup_util.m
--- compiler/lookup_util.m	26 Apr 2006 04:36:46 -0000	1.1
+++ compiler/lookup_util.m	1 May 2006 04:08:21 -0000
@@ -36,15 +36,13 @@
 :- pred figure_out_output_vars(code_info::in, hlds_goal_info::in,
     list(prog_var)::out) is det.
 
-    % Is the input goal a conjunction of unifications, or a scope goal wrapped
-    % around one? If yes, return the bare-bones version.
+    % Is the input goal a conjunction of unifications?
     %
-:- pred goal_is_conj_of_unify(hlds_goal::in, hlds_goal::out) is semidet.
+:- pred goal_is_conj_of_unify(hlds_goal::in) is semidet.
 
     % Run goal_is_conj_of_unify on each goal in the list.
     %
-:- pred all_disjuncts_are_conj_of_unify(list(hlds_goal)::in,
-    list(hlds_goal)::out) is semidet.
+:- pred all_disjuncts_are_conj_of_unify(list(hlds_goal)::in) is semidet.
 
     % To figure out if the outputs are constants, we
     %
@@ -105,29 +103,17 @@
         solutions.solutions(Lambda, OutVars)
     ).
 
-goal_is_conj_of_unify(Goal0, Goal) :-
-    Goal0 = GoalExpr - GoalInfo,
+goal_is_conj_of_unify(Goal) :-
+    Goal = _GoalExpr - GoalInfo,
     goal_info_get_code_model(GoalInfo, CodeModel),
     CodeModel = model_det,
-    (
-        GoalExpr = scope(Reason, SubGoal),
-        ( Reason = exist_quant(_)
-        ; Reason = barrier(removable)
-        ; Reason = from_ground_term(_)
-        )
-    ->
-        Goal = SubGoal
-    ;
-        Goal = Goal0
-    ),
     goal_to_conj_list(Goal, Conj),
     only_constant_goals(Conj).
 
-all_disjuncts_are_conj_of_unify([], []).
-all_disjuncts_are_conj_of_unify([Disjunct0 | Disjuncts0],
-        [Disjunct | Disjuncts]) :-
-    goal_is_conj_of_unify(Disjunct0, Disjunct),
-    all_disjuncts_are_conj_of_unify(Disjuncts0, Disjuncts).
+all_disjuncts_are_conj_of_unify([]).
+all_disjuncts_are_conj_of_unify([Disjunct | Disjuncts]) :-
+    goal_is_conj_of_unify(Disjunct),
+    all_disjuncts_are_conj_of_unify(Disjuncts).
 
 :- pred only_constant_goals(list(hlds_goal)::in) is semidet.
 
Index: compiler/mercury_compile.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/mercury_compile.m,v
retrieving revision 1.385
diff -u -b -r1.385 mercury_compile.m
--- compiler/mercury_compile.m	26 Apr 2006 03:05:36 -0000	1.385
+++ compiler/mercury_compile.m	1 May 2006 05:38:17 -0000
@@ -94,21 +94,21 @@
 :- import_module ll_backend.deep_profiling.
 
     % the LLDS back-end
-:- import_module ll_backend.saved_vars.
-:- import_module ll_backend.stack_opt.
-:- import_module ll_backend.stack_alloc.
+:- import_module ll_backend.continuation_info.
+:- import_module ll_backend.dupproc.
 :- import_module ll_backend.follow_code.
+:- import_module ll_backend.global_data.
 :- import_module ll_backend.liveness.
 :- import_module ll_backend.live_vars.
-:- import_module ll_backend.store_alloc.
-:- import_module ll_backend.code_gen.
-:- import_module ll_backend.optimize.
-:- import_module ll_backend.transform_llds.
 :- import_module ll_backend.llds_out.
-:- import_module ll_backend.continuation_info.
+:- import_module ll_backend.optimize.
+:- import_module ll_backend.proc_gen.
+:- import_module ll_backend.saved_vars.
+:- import_module ll_backend.stack_alloc.
 :- import_module ll_backend.stack_layout.
-:- import_module ll_backend.global_data.
-:- import_module ll_backend.dupproc.
+:- import_module ll_backend.stack_opt.
+:- import_module ll_backend.store_alloc.
+:- import_module ll_backend.transform_llds.
 
     % the bytecode back-end
 :- import_module bytecode_backend.bytecode_gen.
@@ -2474,8 +2474,8 @@
     maybe_followcode(Verbose, Stats, !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 320, "followcode", !DumpInfo, !IO),
 
-    simplify(no, ll_backend, Verbose, Stats,
-        process_all_nonimported_procs, !HLDS, !IO),
+    simplify(no, ll_backend, Verbose, Stats, process_all_nonimported_procs,
+        !HLDS, !IO),
     maybe_dump_hlds(!.HLDS, 325, "ll_backend_simplify", !DumpInfo, !IO),
 
     compute_liveness(Verbose, Stats, !HLDS, !IO),
@@ -2660,7 +2660,7 @@
         SimpList1 = SimpList0
     ),
       
-    SimpList = [do_once | SimpList1],
+    SimpList = [do_once, elim_removable_scopes | SimpList1],
     Simplifications = list_to_simplifications(SimpList),
     simplify_proc(Simplifications, PredId, ProcId, !HLDS, !ProcInfo, !IO),
     write_proc_progress_message("% Computing liveness in ", PredId, ProcId,
@@ -3072,13 +3072,12 @@
                 SimplifyPass = ll_backend,
                 (
                     IsProfPass = yes,
-                    % XXX Why does find_simplifications return a list of
-                    % them rather than a set?
                     list.delete_all(!.SimpList, constant_prop, !:SimpList)
                 ;
                     IsProfPass = no
                 ),
-                list.cons(do_once, !SimpList)
+                list.cons(do_once, !SimpList),
+                list.cons(elim_removable_scopes, !SimpList)
             ),
             Simplifications = list_to_simplifications(!.SimpList)
         ),
Index: compiler/middle_rec.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/middle_rec.m,v
retrieving revision 1.117
diff -u -b -r1.117 middle_rec.m
--- compiler/middle_rec.m	26 Apr 2006 03:05:37 -0000	1.117
+++ compiler/middle_rec.m	29 Apr 2006 09:38:49 -0000
@@ -42,6 +42,7 @@
 :- import_module ll_backend.code_util.
 :- import_module ll_backend.llds_out.
 :- import_module ll_backend.opt_util.
+:- import_module ll_backend.proc_gen.
 :- import_module ll_backend.unify_gen.
 :- import_module parse_tree.prog_data.
 :- import_module parse_tree.prog_out.
@@ -305,7 +306,7 @@
                 label(Loop2Label))
                 - "test on upward loop"]
     ;
-        PushMsg = code_gen.push_msg(ModuleInfo, PredId, ProcId),
+        PushMsg = proc_gen.push_msg(ModuleInfo, PredId, ProcId),
         MaybeIncrSp = [incr_sp(FrameSize, PushMsg) - ""],
         MaybeDecrSp = [decr_sp(FrameSize) - ""],
         InitAuxReg =  [assign(AuxReg, lval(sp))
Index: compiler/simplify.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/simplify.m,v
retrieving revision 1.175
diff -u -b -r1.175 simplify.m
--- compiler/simplify.m	29 Mar 2006 08:07:21 -0000	1.175
+++ compiler/simplify.m	1 May 2006 07:12:21 -0000
@@ -78,6 +78,8 @@
     ;       warn_obsolete           % --warn-obsolete
     ;       do_once                 % run things that should be done once
     ;       excess_assigns          % remove excess assignment unifications
+    ;       elim_removable_scopes   % remove scopes that do not need processing
+                                    % during llds code generation
     ;       opt_duplicate_calls     % optimize duplicate calls
     ;       constant_prop           % partially evaluate calls
     ;       common_struct           % common structure elimination
@@ -100,6 +102,7 @@
 :- pred simplify_do_warn_obsolete(simplify_info::in) is semidet.
 :- pred simplify_do_once(simplify_info::in) is semidet.
 :- pred simplify_do_excess_assign(simplify_info::in) is semidet.
+:- pred simplify_do_elim_removable_scopes(simplify_info::in) is semidet.
 :- pred simplify_do_opt_duplicate_calls(simplify_info::in) is semidet.
 :- pred simplify_do_const_prop(simplify_info::in) is semidet.
 :- pred simplify_do_common_struct(simplify_info::in) is semidet.
@@ -160,6 +163,7 @@
                 do_warn_obsolete            :: bool,
                 do_do_once                  :: bool,
                 do_excess_assign            :: bool,
+                do_elim_removable_scopes    :: bool,
                 do_opt_duplicate_calls      :: bool,
                 do_constant_prop            :: bool,
                 do_common_struct            :: bool,
@@ -169,7 +173,7 @@
 simplifications_to_list(Simplifications) = List :-
     Simplifications = simplifications(WarnSimpleCode, WarnDupCalls,
         WarnKnownBadFormat, WarnUnknownFormat, WarnObsolete, DoOnce,
-        ExcessAssign, OptDuplicateCalls, ConstantProp,
+        ExcessAssign, ElimRemovableScopes, OptDuplicateCalls, ConstantProp,
         CommonStruct, ExtraCommonStruct),
     List = 
         ( WarnSimpleCode = yes -> [warn_simple_code] ; [] ) ++
@@ -179,6 +183,7 @@
         ( WarnObsolete = yes -> [warn_obsolete] ; [] ) ++
         ( DoOnce = yes -> [do_once] ; [] ) ++
         ( ExcessAssign = yes -> [excess_assigns] ; [] ) ++
+        ( ElimRemovableScopes = yes -> [elim_removable_scopes] ; [] ) ++
         ( OptDuplicateCalls = yes -> [opt_duplicate_calls] ; [] ) ++
         ( ConstantProp = yes -> [constant_prop] ; [] ) ++
         ( CommonStruct = yes -> [common_struct] ; [] ) ++
@@ -193,6 +198,7 @@
         ( list.member(warn_obsolete, List) -> yes ; no ),
         ( list.member(do_once, List) -> yes ; no ),
         ( list.member(excess_assigns, List) -> yes ; no ),
+        ( list.member(elim_removable_scopes, List) -> yes ; no ),
         ( list.member(opt_duplicate_calls, List) -> yes ; no ),
         ( list.member(constant_prop, List) -> yes ; no ),
         ( list.member(common_struct, List) -> yes ; no ),
@@ -213,6 +219,7 @@
         OptDuplicateCalls),
     globals.lookup_bool_option(Globals, constant_propagation, ConstantProp),
     DoOnce = no,
+    ElimRemovableScopes = no,
     ExtraCommonStruct = no,
 
     Simplifications = simplifications(
@@ -223,6 +230,7 @@
         ( WarnObsolete = yes, WarnThisPass = yes -> yes ; no),
         DoOnce,
         ExcessAssign,
+        ElimRemovableScopes,
         OptDuplicateCalls,
         ConstantProp,
         CommonStruct,
@@ -250,6 +258,9 @@
 simplify_do_excess_assign(Info) :-
     simplify_info_get_simplifications(Info, Simplifications),
     Simplifications ^ do_excess_assign = yes.
+simplify_do_elim_removable_scopes(Info) :-
+    simplify_info_get_simplifications(Info, Simplifications),
+    Simplifications ^ do_elim_removable_scopes = yes.
 simplify_do_opt_duplicate_calls(Info) :-
     simplify_info_get_simplifications(Info, Simplifications),
     Simplifications ^ do_opt_duplicate_calls = yes.
@@ -502,7 +513,7 @@
 :- pred simplify_goal(hlds_goal::in, hlds_goal::out,
     simplify_info::in, simplify_info::out, io::di, io::uo) is det.
 
-simplify_goal(Goal0, Goal - GoalInfo, !Info, !IO) :-
+simplify_goal(Goal0, GoalExpr - GoalInfo, !Info, !IO) :-
     Goal0 = _ - GoalInfo0,
     goal_info_get_determinism(GoalInfo0, Detism),
     simplify_info_get_det_info(!.Info, DetInfo),
@@ -628,16 +639,27 @@
     % Remove unnecessary explicit quantifications before working
     % out whether the goal can cause a stack flush.
     %
-    ( Goal1 = scope(Reason, SomeGoal1) - GoalInfo1 ->
-        nested_scopes(Reason, SomeGoal1, GoalInfo1, Goal2)
+    ( Goal1 = scope(Reason1, SomeGoal1) - GoalInfo1 ->
+        nested_scopes(Reason1, SomeGoal1, GoalInfo1, Goal2)
     ;
         Goal2 = Goal1
     ),
-    simplify_info_maybe_clear_structs(before, Goal2, !Info),
-    Goal2 = GoalExpr2 - GoalInfo2,
-    simplify_goal_2(GoalExpr2, Goal, GoalInfo2, GoalInfo3, !Info, !IO),
-    simplify_info_maybe_clear_structs(after, Goal - GoalInfo3, !Info),
-    enforce_invariant(GoalInfo3, GoalInfo, !Info).
+    (
+        simplify_do_elim_removable_scopes(!.Info),
+        Goal2 = scope(Reason2, SomeGoal2) - _GoalInfo2,
+        ( Reason2 = barrier(removable)
+        ; Reason2 = from_ground_term(_)
+        )
+    ->
+        Goal3 = SomeGoal2
+    ;
+        Goal3 = Goal2
+    ),
+    simplify_info_maybe_clear_structs(before, Goal3, !Info),
+    Goal3 = GoalExpr3 - GoalInfo3,
+    simplify_goal_2(GoalExpr3, GoalExpr, GoalInfo3, GoalInfo4, !Info, !IO),
+    simplify_info_maybe_clear_structs(after, GoalExpr - GoalInfo4, !Info),
+    enforce_invariant(GoalInfo4, GoalInfo, !Info).
 
     % Ensure that the mode information and the determinism
     % information say consistent things about unreachability.
@@ -1804,8 +1826,7 @@
             Reason0 = exist_quant(Vars0),
             Reason1 = exist_quant(Vars1)
         ->
-            list.append(Vars0, Vars1, Vars2),
-            Reason2 = exist_quant(Vars2)
+            Reason2 = exist_quant(Vars0 ++ Vars1)
         ;
             Reason0 = from_ground_term(_)
         ->
Index: compiler/var_locn.m
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/var_locn.m,v
retrieving revision 1.38
diff -u -b -r1.38 var_locn.m
--- compiler/var_locn.m	26 Apr 2006 03:05:40 -0000	1.38
+++ compiler/var_locn.m	28 Apr 2006 07:18:46 -0000
@@ -400,24 +400,25 @@
     %   variable cached. The locs field will be nonempty, and both
     %   const_rval and expr_rval will be no.
 
-:- type var_state   --->
-    state(
+:- type var_state
+    --->    state(
         locs            :: set(lval),
-                        % must not contain var(_)
+                                % Must not contain var(_).
 
         const_rval      :: maybe(rval),
-                        % must not contain var(_), must be constant
+                                % Must not contain var(_), must be constant.
 
         expr_rval       :: maybe(rval),
-                        % will contain var(_), must not contain lvals
+                                % Will contain var(_), must not contain lvals.
 
         using_vars      :: set(prog_var),
                         % The set of vars whose expr_rval field refers
                         % to this var.
 
         dead_or_alive   :: dead_or_alive
-                        % A dead variable should be removed from var_state_map
-                        % when its using_vars field becomes empty.
+                                % A dead variable should be removed from
+                                % var_state_map when its using_vars field
+                                % becomes empty.
     ).
 
 :- type var_state_map   ==  map(prog_var, var_state).
@@ -437,8 +438,8 @@
 
 :- type loc_var_map ==  map(lval, set(prog_var)).
 
-:- type var_locn_info   --->
-    var_locn_info(
+:- type var_locn_info
+    --->    var_locn_info(
         varset          :: prog_varset,
                         % The varset from the proc_info.
 
@@ -446,17 +447,19 @@
                         % The vartypes from the proc_info.
 
         stack_slots     :: stack_slots,
-                        % Maps each var to its stack slot, if it has one.
+                                % 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.
+                                % 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.
 
         next_non_res    :: int,
-                        % Next register that isn't reserved in follow_vars_map.
+                                % Next register that isn't reserved in
+                                % follow_vars_map.
 
         var_state_map   :: var_state_map,
                         % Documented above.
@@ -465,21 +468,23 @@
                         % Documented above.
 
         acquired        :: set(lval),
-                        % Locations that are temporarily reserved for purposes
-                        % such as holding the tags of variables during
-                        % switches.
+                                % 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.
+                                % 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.
     ).
 
 %----------------------------------------------------------------------------%
cvs diff: Diffing compiler/notes
Index: compiler/notes/compiler_design.html
===================================================================
RCS file: /home/mercury/mercury1/repository/mercury/compiler/notes/compiler_design.html,v
retrieving revision 1.117
diff -u -b -r1.117 compiler_design.html
--- compiler/notes/compiler_design.html	26 Apr 2006 03:06:23 -0000	1.117
+++ compiler/notes/compiler_design.html	29 Apr 2006 10:28:16 -0000
@@ -1133,16 +1133,19 @@
 	For the LLDS back-end, this is also the point at which we
 	insert code to handle debugging and trailing, and to do
 	heap reclamation on failure.
-	The main code generation module is code_gen.m. 
-	It handles conjunctions and negations, but calls sub-modules
-	to do most of the other work:
+	The top level code generation module is proc_gen.m,
+	which looks after the generation of code for procedures
+	(including prologues and epilogues).
+	The predicate for generating code for arbitrary goals is in code_gen.m,
+	but that module handles only sequential conjunctions; it calls
+	other modules to handle other kinds of goals:
 
 		<ul>
 		<li> ite_gen.m (if-then-elses)
 		<li> call_gen.m (predicate calls and also calls to
 			out-of-line unification procedures)
 		<li> disj_gen.m (disjunctions)
-		<li> par_conj.m (parallel conjunctions)
+		<li> par_conj_gen.m (parallel conjunctions)
 		<li> unify_gen.m (unifications)
 		<li> switch_gen.m (switches), which has sub-modules
 			<ul>
@@ -1159,8 +1162,8 @@
 
 	<p>
 
-	code_gen.m also calls middle_rec.m to do middle recursion optimization,
-	which is implemented during code generation.
+	The code generator also calls middle_rec.m to do middle recursion
+	optimization, which is implemented during code generation.
 
 	<p>
 
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/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/gator
cvs diff: Diffing extras/gator/generations
cvs diff: Diffing extras/gator/generations/1
cvs diff: Diffing extras/graphics
cvs diff: Diffing extras/graphics/easyx
cvs diff: Diffing extras/graphics/easyx/samples
cvs diff: Diffing extras/graphics/mercury_glut
cvs diff: Diffing extras/graphics/mercury_opengl
cvs diff: Diffing extras/graphics/mercury_tcltk
cvs diff: Diffing extras/graphics/samples
cvs diff: Diffing extras/graphics/samples/calc
cvs diff: Diffing extras/graphics/samples/gears
cvs diff: Diffing extras/graphics/samples/maze
cvs diff: Diffing extras/graphics/samples/pent
cvs diff: Diffing extras/lazy_evaluation
cvs diff: Diffing extras/lex
cvs diff: Diffing extras/lex/samples
cvs diff: Diffing extras/lex/tests
cvs diff: Diffing extras/logged_output
cvs diff: Diffing extras/moose
cvs diff: Diffing extras/moose/samples
cvs diff: Diffing extras/moose/tests
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/odbc
cvs diff: Diffing extras/posix
cvs diff: Diffing extras/quickcheck
cvs diff: Diffing extras/quickcheck/tutes
cvs diff: Diffing extras/references
cvs diff: Diffing extras/references/samples
cvs diff: Diffing extras/references/tests
cvs diff: Diffing extras/solver_types
cvs diff: Diffing extras/solver_types/library
cvs diff: Diffing extras/stream
cvs diff: Diffing extras/trailed_update
cvs diff: Diffing extras/trailed_update/samples
cvs diff: Diffing extras/trailed_update/tests
cvs diff: Diffing extras/windows_installer_generator
cvs diff: Diffing extras/windows_installer_generator/sample
cvs diff: Diffing extras/windows_installer_generator/sample/images
cvs diff: Diffing extras/xml
cvs diff: Diffing extras/xml/samples
cvs diff: Diffing extras/xml_stylesheets
cvs diff: Diffing java
cvs diff: Diffing java/runtime
cvs diff: Diffing library
cvs diff: Diffing mdbcomp
cvs diff: Diffing profiler
cvs diff: Diffing robdd
cvs diff: Diffing runtime
cvs diff: Diffing runtime/GETOPT
cvs diff: Diffing runtime/machdeps
cvs diff: Diffing samples
cvs diff: Diffing samples/c_interface
cvs diff: Diffing samples/c_interface/c_calls_mercury
cvs diff: Diffing samples/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/c_interface/mercury_calls_c
cvs diff: Diffing samples/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/diff
cvs diff: Diffing samples/muz
cvs diff: Diffing samples/rot13
cvs diff: Diffing samples/solutions
cvs diff: Diffing samples/tests
cvs diff: Diffing samples/tests/c_interface
cvs diff: Diffing samples/tests/c_interface/c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/cplusplus_calls_mercury
cvs diff: Diffing samples/tests/c_interface/mercury_calls_c
cvs diff: Diffing samples/tests/c_interface/mercury_calls_cplusplus
cvs diff: Diffing samples/tests/c_interface/mercury_calls_fortran
cvs diff: Diffing samples/tests/c_interface/simpler_c_calls_mercury
cvs diff: Diffing samples/tests/c_interface/simpler_cplusplus_calls_mercury
cvs diff: Diffing samples/tests/diff
cvs diff: Diffing samples/tests/muz
cvs diff: Diffing samples/tests/rot13
cvs diff: Diffing samples/tests/solutions
cvs diff: Diffing samples/tests/toplevel
cvs diff: Diffing scripts
cvs diff: Diffing slice
cvs diff: Diffing tests
cvs diff: Diffing tests/benchmarks
cvs diff: Diffing tests/debugger
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/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:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list