mirror of
https://github.com/Mercury-Language/mercury.git
synced 2025-12-14 21:35:49 +00:00
Estimated hours taken: 100 Branches: main This patch changes the parallel execution mechanism in the low level backend. The main idea is that, even in programs with only moderate parallelism, we won't have enough processors to exploit it all. We should try to reduce the cost in the common case, i.e. when a parallel conjunction gets executed sequentially. This patch does two things along those lines: (1) Instead of unconditionally executing all parallel conjuncts (but the last) in separate Mercury contexts, we allow a context to continue execution of the next conjunct of a parallel conjunction if it has just finished executing the previous conjunct. This saves on allocating unnecessary contexts, which can be a big reduction in memory usage. We also try to execute conjuncts left-to-right so as to minimise the need to suspend contexts when there are dependencies between conjuncts. (2) Conjuncts that *are* executed in parallel still need separate contexts. We used to pass variable bindings to those conjuncts by flushing input variable values to stack slots and copying the procedure's stack frame to the new context. When the conjunct finished, we would copy new variable bindings back to stack slots in the original context. What happens now is that we don't do any copying back and forth. We introduce a new abstract machine register `parent_sp' which points to the location of the stack pointer at the time that a parallel conjunction began. In parallel conjuncts we refer to all stack slots via the `parent_sp' pointer, since we could be running on a different context altogether and `sp' would be pointing into a new detstack. Since parallel conjuncts now share the procedure's stack frame, we have to allocate stack slots such that all parallel conjuncts in a procedure that could be executing simultaneously have distinct sets of stack slots. We currently use the simplest possible strategy, i.e. don't allow variables in parallel conjuncts to reuse stack slots. Note: in effect parent_sp is a frame pointer which is only set for and used by the code of parallel conjuncts. We don't call it a frame pointer as it can be confused with "frame variables" which have to do with the nondet stack. compiler/code_info.m: Add functionality to keep track of how deep inside of nested parallel conjunctions the code generator is. Add functionality to acquire and release "persistent" temporary stack slots. Unlike normal temporary stack slots, these don't get implicitly released when the code generator's location-dependent state is reset. Conform to additions of `parent_sp' and parent stack variables. compiler/exprn_aux.m: Generalise the `substitute_lval_in_*' predicates by `transform_lval_in_*' predicates. Instead of performing a fixed substitution, these take a higher order predicate which performs some operation on each lval. Redefine the substitution predicates in terms of the transformation predicates. Conform to changes in `fork', `join_and_terminate' and `join_and_continue' instructions. Conform to additions of `parent_sp' and parent stack variables. Remove `substitute_rval_in_args' and `substitute_rval_in_arg' which were unused. compiler/live_vars.m: Introduce a new type `parallel_stackvars' which is threaded through `build_live_sets_in_goal'. We accumulate the sets of variables which are assigned stack slots in each parallel conjunct. At the end of processing a parallel conjunction, use this information to force variables which are assigned stack slots to have distinct slots. compiler/llds.m: Change the semantics of the `fork' instruction. It now takes a single argument: the label of the next conjunct after the current one. The instruction now "sparks" the next conjunct to be run, either in a different context (possibly in parallel, on another Mercury engine) or is queued to be executed in the current context after the current conjunct is finished. Change the semantics of the `join_and_continue' instruction. This instruction now serves to end all parallel conjuncts, not just the last one in a parallel conjunction. Remove the `join_and_terminate' instruction (no longer used). Add the new abstract machine register `parent_sp'. Introduce "parent stack slots", which are similar to normal stack slots but relative to the `parent_sp' register. compiler/par_conj_gen.m: Change the code generated for parallel conjunctions. That is: - use the new `fork' instruction at the beginning of a parallel conjunct; - use the `join_and_continue' instruction at the end of all parallel conjuncts; - keep track of how deep the code generator currently is in parallel conjunctions; - set and restore the `parent_sp' register when entering a non-nested parallel conjunction; - after generating the code of a parallel conjunct, replace all references to stack slots by parent stack slots; - remove code to copy back output variables when a parallel conjunct finishes. Update some comments. runtime/mercury_context.c: runtime/mercury_context.h: Add the type `MR_Spark'. Sparks are allocated on the heap and contain enough information to begin execution of a single parallel conjunct. Add globals `MR_spark_queue_head' and `MR_spark_queue_tail'. These are pointers to the start and end of a global queue of sparks. Idle engines can pick up work from this queue in the same way that they can pick up work from the global context queue (the "run queue"). Add new fields to the MR_Context structure. `MR_ctxt_parent_sp' is a saved copy of the `parent_sp' register for when the context is suspended. `MR_ctxt_spark_stack' is a stack of sparks that we decided not to put on the global spark queue. Update `MR_load_context' and `MR_save_context' to save and restore `MR_ctxt_parent_sp'. Add the counters `MR_num_idle_engines' and `MR_num_outstanding_contexts_and_sparks'. These are used to decide, when a `fork' instruction is reached, whether a spark should be put on the global spark queue (with potential for parallelism but also more overhead) or on the calling context's spark stack (no parallelism and less overhead). Rename `MR_init_context' to `MR_init_context_maybe_generator'. When initialising contexts, don't reset redzones of already allocated stacks. It seems to be unnecessary (and the reset implementation is buggy anyway, though it's fine on Linux). Rename `MR_schedule' to `MR_schedule_context'. Add new functions `MR_schedule_spark_globally' and `MR_schedule_spark_locally'. In `MR_do_runnext', add code for idle engines to get work from the global spark queue. Resuming contexts are prioritised over sparks. Rename `MR_fork_new_context' to `MR_fork_new_child'. Change the definitions of `MR_fork_new_child' and `MR_join_and_continue' as per the new behaviour of the `fork' and `join_and_continue' instructions. Delete `MR_join_and_terminate'. Add a new field `MR_st_orig_context' to the MR_SyncTerm structure to record which context originated the parallel conjunction instance represented by a MR_SyncTerm instance, and update `MR_init_sync_term'. This is needed by the new behaviour of `MR_join_and_continue'. Update some comments. runtime/mercury_engine.h: runtime/mercury_regs.c: runtime/mercury_regs.h: runtime/mercury_stacks.h: Add the abstract machine register `parent_sp' and code to copy it to and from the fake_reg array. Add a macro `MR_parent_sv' to access stack slots via `parent_sp'. Add `MR_eng_parent_sp' to the MercuryEngine structure. runtime/mercury_wrapper.c: runtime/mercury_wrapper.h: Add Mercury runtime option `--max-contexts-per-thread' which is saved in the global variable `MR_max_contexts_per_thread'. The number `MR_max_outstanding_contexts' is derived from this. It sets a soft limit on the number of sparks we put in the global spark queue, relative to the number of threads we are running. We don't want to put too many sparks on the global queue if there are plenty of ready contexts or sparks already on the global queues, as they are likely to result in new contexts being allocated. When initially creating worker engines, wait until all the worker engines have acknowledged that they are idle before continuing. This is mainly so programs (especially benchmarks and test cases) with only a few fork instructions near the beginning of the program don't execute the forks before any worker engines are ready, resulting in no parallelism. runtime/mercury_engine.c: runtime/mercury_thread.c: Don't allocate a context at the time a Mercury engine is created. An engine only needs a new context when it is about to pick up a spark. configure.in: compiler/options.m: scripts/Mercury.config.in: Update to reflect the extra field in MR_SyncTerm. Add the option `--sync-term-size' and actually make use the result of the sync term size calculated during configuration. compiler/code_util.m: compiler/continuation_info.m: compiler/dupelim.m: compiler/dupproc.m: compiler/global_data.m: compiler/hlds_llds.m: compiler/jumpopt.m: compiler/livemap.m: compiler/llds_out.m: compiler/middle_rec.m: compiler/opt_debug.m: compiler/opt_util.m: compiler/reassign.m: compiler/stack_layout.m: compiler/use_local_vars.m: compiler/var_locn.m: Conform to changes in `fork', `join_and_terminate' and `join_and_continue' instructions. Conform to additions of `parent_sp' and parent stack variables. XXX not sure about the changes in stack_layout.m library/par_builtin.m: Conform to changes in the runtime system.
454 lines
15 KiB
Mathematica
454 lines
15 KiB
Mathematica
%-----------------------------------------------------------------------------%
|
|
% vim: ft=mercury ts=4 sw=4 et
|
|
%-----------------------------------------------------------------------------%
|
|
% Copyright (C) 1994-2006 The University of Melbourne.
|
|
% This file may only be copied under the terms of the GNU General
|
|
% Public License - see the file COPYING in the Mercury distribution.
|
|
%-----------------------------------------------------------------------------%
|
|
%
|
|
% File: code_util.m.
|
|
%
|
|
% Various utilities routines for code generation and recognition of builtins.
|
|
%
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
:- module ll_backend.code_util.
|
|
:- interface.
|
|
|
|
:- import_module hlds.hlds_goal.
|
|
:- import_module hlds.hlds_llds.
|
|
:- import_module hlds.hlds_module.
|
|
:- import_module hlds.hlds_pred.
|
|
:- import_module hlds.hlds_rtti.
|
|
:- import_module ll_backend.llds.
|
|
:- import_module mdbcomp.prim_data.
|
|
:- import_module parse_tree.prog_data.
|
|
|
|
:- import_module assoc_list.
|
|
:- import_module list.
|
|
:- import_module maybe.
|
|
:- import_module pair.
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
% Create a code address which holds the address of the specified procedure.
|
|
% The `immed' argument should be `no' if the the caller wants the returned
|
|
% address to be valid from everywhere in the program. If being valid from
|
|
% within the current procedure is enough, this argument should be `yes'
|
|
% wrapped around the value of the --procs-per-c-function option and the
|
|
% current procedure id. Using an address that is only valid from within
|
|
% the current procedure may make jumps more efficient.
|
|
%
|
|
:- type immed == maybe(pair(int, pred_proc_id)).
|
|
:- pred make_entry_label(module_info::in, pred_id::in, proc_id::in, immed::in,
|
|
code_addr::out) is det.
|
|
|
|
:- pred make_entry_label_from_rtti(rtti_proc_label::in, immed::in,
|
|
code_addr::out) is det.
|
|
|
|
% Create a label which holds the address of the specified procedure,
|
|
% which must be defined in the current module (procedures that are
|
|
% imported from other modules have representations only as code_addrs,
|
|
% not as labels, since their address is not known at C compilation time).
|
|
% The fourth argument has the same meaning as for make_entry_label.
|
|
%
|
|
:- pred make_local_entry_label(module_info::in, pred_id::in, proc_id::in,
|
|
immed::in, label::out) is det.
|
|
|
|
% Create a label internal to a Mercury procedure.
|
|
%
|
|
:- pred make_internal_label(module_info::in, pred_id::in, proc_id::in, int::in,
|
|
label::out) is det.
|
|
|
|
:- pred extract_proc_label_from_code_addr(code_addr::in, proc_label::out)
|
|
is det.
|
|
|
|
:- pred arg_loc_to_register(arg_loc::in, lval::out) is det.
|
|
|
|
:- pred max_mentioned_reg(list(lval)::in, int::out) is det.
|
|
:- pred max_mentioned_abs_reg(list(abs_locn)::in, int::out) is det.
|
|
|
|
:- pred goal_may_alloc_temp_frame(hlds_goal::in) is semidet.
|
|
|
|
% Negate a condition.
|
|
% This is used mostly just to make the generated code more readable.
|
|
%
|
|
:- pred neg_rval(rval::in, rval::out) is det.
|
|
|
|
:- pred negate_the_test(list(instruction)::in, list(instruction)::out) is det.
|
|
|
|
% These predicates return the set of lvals referenced in an rval
|
|
% and an lval respectively. Lvals referenced indirectly through
|
|
% lvals of the form var(_) are not counted.
|
|
%
|
|
:- pred lvals_in_rval(rval::in, list(lval)::out) is det.
|
|
:- pred lvals_in_lval(lval::in, list(lval)::out) is det.
|
|
:- pred lvals_in_lvals(list(lval)::in, list(lval)::out) is det.
|
|
|
|
% Given a procedure that already has its arg_info field filled in,
|
|
% return a list giving its input variables and their initial locations.
|
|
%
|
|
:- pred build_input_arg_list(proc_info::in, assoc_list(prog_var, lval)::out)
|
|
is det.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- implementation.
|
|
|
|
:- import_module backend_libs.builtin_ops.
|
|
:- import_module backend_libs.proc_label.
|
|
:- import_module backend_libs.rtti.
|
|
:- import_module hlds.code_model.
|
|
:- import_module hlds.goal_form.
|
|
:- import_module hlds.special_pred.
|
|
:- import_module libs.compiler_util.
|
|
:- import_module libs.options.
|
|
:- import_module parse_tree.prog_util.
|
|
|
|
:- import_module bool.
|
|
:- import_module char.
|
|
:- import_module int.
|
|
:- import_module set.
|
|
:- import_module string.
|
|
:- import_module term.
|
|
:- import_module varset.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
make_entry_label(ModuleInfo, PredId, ProcId, Immed, ProcAddr) :-
|
|
RttiProcLabel = rtti.make_rtti_proc_label(ModuleInfo, PredId, ProcId),
|
|
make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr).
|
|
|
|
make_entry_label_from_rtti(RttiProcLabel, Immed, ProcAddr) :-
|
|
( RttiProcLabel ^ proc_is_imported = yes ->
|
|
ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
|
|
ProcAddr = imported(ProcLabel)
|
|
;
|
|
make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label),
|
|
ProcAddr = label(Label)
|
|
).
|
|
|
|
make_local_entry_label(ModuleInfo, PredId, ProcId, Immed, Label) :-
|
|
RttiProcLabel = rtti.make_rtti_proc_label(ModuleInfo, PredId, ProcId),
|
|
make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label).
|
|
|
|
:- pred make_local_entry_label_from_rtti(rtti_proc_label::in,
|
|
immed::in, label::out) is det.
|
|
|
|
make_local_entry_label_from_rtti(RttiProcLabel, Immed, Label) :-
|
|
ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
|
|
(
|
|
Immed = no,
|
|
% If we want to define the label or use it to put it into a data
|
|
% structure, a label that is usable only within the current C module
|
|
% won't do.
|
|
( RttiProcLabel ^ proc_is_exported = yes ->
|
|
EntryType = entry_label_exported
|
|
;
|
|
EntryType = entry_label_local
|
|
),
|
|
Label = entry(EntryType, ProcLabel)
|
|
;
|
|
Immed = yes(ProcsPerFunc - proc(CurPredId, CurProcId)),
|
|
choose_local_label_type(ProcsPerFunc, CurPredId, CurProcId,
|
|
RttiProcLabel^pred_id, RttiProcLabel^proc_id,
|
|
ProcLabel, Label)
|
|
).
|
|
|
|
:- pred choose_local_label_type(int::in, pred_id::in, proc_id::in,
|
|
pred_id::in, proc_id::in, proc_label::in, label::out) is det.
|
|
|
|
choose_local_label_type(ProcsPerFunc, CurPredId, CurProcId,
|
|
PredId, ProcId, ProcLabel, Label) :-
|
|
(
|
|
% If we want to branch to the label now, we prefer a form that is
|
|
% usable only within the current C module, since it is likely to be
|
|
% faster.
|
|
(
|
|
ProcsPerFunc = 0
|
|
;
|
|
PredId = CurPredId,
|
|
ProcId = CurProcId
|
|
)
|
|
->
|
|
EntryType = entry_label_c_local
|
|
;
|
|
EntryType = entry_label_local
|
|
),
|
|
Label = entry(EntryType, ProcLabel).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
make_internal_label(ModuleInfo, PredId, ProcId, LabelNum, Label) :-
|
|
ProcLabel = make_proc_label(ModuleInfo, PredId, ProcId),
|
|
Label = internal(LabelNum, ProcLabel).
|
|
|
|
extract_proc_label_from_code_addr(CodeAddr, ProcLabel) :-
|
|
( CodeAddr = label(Label) ->
|
|
ProcLabel = get_proc_label(Label)
|
|
; CodeAddr = imported(ProcLabelPrime) ->
|
|
ProcLabel = ProcLabelPrime
|
|
;
|
|
unexpected(this_file, "extract_label_from_code_addr failed")
|
|
).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
arg_loc_to_register(ArgLoc, reg(reg_r, ArgLoc)).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
max_mentioned_reg(Lvals, MaxRegNum) :-
|
|
max_mentioned_reg_2(Lvals, 0, MaxRegNum).
|
|
|
|
:- pred max_mentioned_reg_2(list(lval)::in, int::in, int::out) is det.
|
|
|
|
max_mentioned_reg_2([], !MaxRegNum).
|
|
max_mentioned_reg_2([Lval | Lvals], !MaxRegNum) :-
|
|
( Lval = reg(reg_r, N) ->
|
|
int.max(N, !MaxRegNum)
|
|
;
|
|
true
|
|
),
|
|
max_mentioned_reg_2(Lvals, !MaxRegNum).
|
|
|
|
max_mentioned_abs_reg(Lvals, MaxRegNum) :-
|
|
max_mentioned_abs_reg_2(Lvals, 0, MaxRegNum).
|
|
|
|
:- pred max_mentioned_abs_reg_2(list(abs_locn)::in, int::in, int::out) is det.
|
|
|
|
max_mentioned_abs_reg_2([], !MaxRegNum).
|
|
max_mentioned_abs_reg_2([Lval | Lvals], !MaxRegNum) :-
|
|
( Lval = abs_reg(N) ->
|
|
int.max(N, !MaxRegNum)
|
|
;
|
|
true
|
|
),
|
|
max_mentioned_abs_reg_2(Lvals, !MaxRegNum).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
goal_may_alloc_temp_frame(Goal) :-
|
|
goal_may_alloc_temp_frame(Goal, yes).
|
|
|
|
:- pred goal_may_alloc_temp_frame(hlds_goal::in, bool::out) is det.
|
|
|
|
goal_may_alloc_temp_frame(Goal - _GoalInfo, May) :-
|
|
goal_may_alloc_temp_frame_2(Goal, May).
|
|
|
|
:- pred goal_may_alloc_temp_frame_2(hlds_goal_expr::in, bool::out)
|
|
is det.
|
|
|
|
goal_may_alloc_temp_frame_2(generic_call(_, _, _, _), no).
|
|
goal_may_alloc_temp_frame_2(plain_call(_, _, _, _, _, _), no).
|
|
goal_may_alloc_temp_frame_2(unify(_, _, _, _, _), no).
|
|
% We cannot safely say that a foreign code fragment does not allocate
|
|
% temporary nondet frames without knowing all the #defined macros
|
|
% that expand to mktempframe and variants thereof. The performance
|
|
% impact of being too conservative is probably not too bad.
|
|
goal_may_alloc_temp_frame_2(call_foreign_proc(_, _, _, _, _, _, _), yes).
|
|
goal_may_alloc_temp_frame_2(scope(_, Goal), May) :-
|
|
Goal = _ - GoalInfo,
|
|
goal_info_get_code_model(GoalInfo, CodeModel),
|
|
( CodeModel = model_non ->
|
|
May = yes
|
|
;
|
|
goal_may_alloc_temp_frame(Goal, May)
|
|
).
|
|
goal_may_alloc_temp_frame_2(negation(Goal), May) :-
|
|
goal_may_alloc_temp_frame(Goal, May).
|
|
goal_may_alloc_temp_frame_2(conj(_ConjType, Goals), May) :-
|
|
goal_list_may_alloc_temp_frame(Goals, May).
|
|
goal_may_alloc_temp_frame_2(disj(Goals), May) :-
|
|
goal_list_may_alloc_temp_frame(Goals, May).
|
|
goal_may_alloc_temp_frame_2(switch(_Var, _Det, Cases), May) :-
|
|
cases_may_alloc_temp_frame(Cases, May).
|
|
goal_may_alloc_temp_frame_2(if_then_else(_Vars, C, T, E), May) :-
|
|
( goal_may_alloc_temp_frame(C, yes) ->
|
|
May = yes
|
|
; goal_may_alloc_temp_frame(T, yes) ->
|
|
May = yes
|
|
;
|
|
goal_may_alloc_temp_frame(E, May)
|
|
).
|
|
goal_may_alloc_temp_frame_2(shorthand(ShorthandGoal), May) :-
|
|
goal_may_alloc_temp_frame_2_shorthand(ShorthandGoal,May).
|
|
|
|
:- pred goal_may_alloc_temp_frame_2_shorthand(shorthand_goal_expr::in,
|
|
bool::out) is det.
|
|
|
|
goal_may_alloc_temp_frame_2_shorthand(bi_implication(G1, G2), May) :-
|
|
( goal_may_alloc_temp_frame(G1, yes) ->
|
|
May = yes
|
|
;
|
|
goal_may_alloc_temp_frame(G2, May)
|
|
).
|
|
|
|
:- pred goal_list_may_alloc_temp_frame(list(hlds_goal)::in, bool::out) is det.
|
|
|
|
goal_list_may_alloc_temp_frame([], no).
|
|
goal_list_may_alloc_temp_frame([Goal | Goals], May) :-
|
|
( goal_may_alloc_temp_frame(Goal, yes) ->
|
|
May = yes
|
|
;
|
|
goal_list_may_alloc_temp_frame(Goals, May)
|
|
).
|
|
|
|
:- pred cases_may_alloc_temp_frame(list(case)::in, bool::out) is det.
|
|
|
|
cases_may_alloc_temp_frame([], no).
|
|
cases_may_alloc_temp_frame([case(_, Goal) | Cases], May) :-
|
|
( goal_may_alloc_temp_frame(Goal, yes) ->
|
|
May = yes
|
|
;
|
|
cases_may_alloc_temp_frame(Cases, May)
|
|
).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
neg_rval(Rval, NegRval) :-
|
|
( neg_rval_2(Rval, NegRval0) ->
|
|
NegRval = NegRval0
|
|
;
|
|
NegRval = unop(logical_not, Rval)
|
|
).
|
|
|
|
:- pred neg_rval_2(rval::in, rval::out) is semidet.
|
|
|
|
neg_rval_2(const(Const), const(NegConst)) :-
|
|
(
|
|
Const = llconst_true,
|
|
NegConst = llconst_false
|
|
;
|
|
Const = llconst_false,
|
|
NegConst = llconst_true
|
|
).
|
|
neg_rval_2(unop(logical_not, Rval), Rval).
|
|
neg_rval_2(binop(Op, X, Y), binop(NegOp, X, Y)) :-
|
|
neg_op(Op, NegOp).
|
|
|
|
:- pred neg_op(binary_op::in, binary_op::out) is semidet.
|
|
|
|
neg_op(eq, ne).
|
|
neg_op(ne, eq).
|
|
neg_op(int_lt, int_ge).
|
|
neg_op(int_le, int_gt).
|
|
neg_op(int_gt, int_le).
|
|
neg_op(int_ge, int_lt).
|
|
neg_op(str_eq, str_ne).
|
|
neg_op(str_ne, str_eq).
|
|
neg_op(str_lt, str_ge).
|
|
neg_op(str_le, str_gt).
|
|
neg_op(str_gt, str_le).
|
|
neg_op(str_ge, str_lt).
|
|
neg_op(float_eq, float_ne).
|
|
neg_op(float_ne, float_eq).
|
|
neg_op(float_lt, float_ge).
|
|
neg_op(float_le, float_gt).
|
|
neg_op(float_gt, float_le).
|
|
neg_op(float_ge, float_lt).
|
|
|
|
negate_the_test([], _) :-
|
|
unexpected(this_file, "negate_the_test on empty list").
|
|
negate_the_test([Instr0 | Instrs0], Instrs) :-
|
|
( Instr0 = if_val(Test, Target) - Comment ->
|
|
neg_rval(Test, NewTest),
|
|
Instrs = [if_val(NewTest, Target) - Comment]
|
|
;
|
|
negate_the_test(Instrs0, Instrs1),
|
|
Instrs = [Instr0 | Instrs1]
|
|
).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
lvals_in_lvals([], []).
|
|
lvals_in_lvals([First | Rest], FirstLvals ++ RestLvals) :-
|
|
lvals_in_lval(First, FirstLvals),
|
|
lvals_in_lvals(Rest, RestLvals).
|
|
|
|
lvals_in_rval(lval(Lval), [Lval | Lvals]) :-
|
|
lvals_in_lval(Lval, Lvals).
|
|
lvals_in_rval(var(_), []).
|
|
lvals_in_rval(mkword(_, Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_rval(const(_), []).
|
|
lvals_in_rval(unop(_, Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_rval(binop(_, Rval1, Rval2), Lvals1 ++ Lvals2) :-
|
|
lvals_in_rval(Rval1, Lvals1),
|
|
lvals_in_rval(Rval2, Lvals2).
|
|
lvals_in_rval(mem_addr(MemRef), Lvals) :-
|
|
lvals_in_mem_ref(MemRef, Lvals).
|
|
|
|
lvals_in_lval(reg(_, _), []).
|
|
lvals_in_lval(stackvar(_), []).
|
|
lvals_in_lval(parent_stackvar(_), []).
|
|
lvals_in_lval(framevar(_), []).
|
|
lvals_in_lval(succip, []).
|
|
lvals_in_lval(maxfr, []).
|
|
lvals_in_lval(curfr, []).
|
|
lvals_in_lval(succip_slot(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(redofr_slot(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(redoip_slot(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(succfr_slot(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(prevfr_slot(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(hp, []).
|
|
lvals_in_lval(sp, []).
|
|
lvals_in_lval(parent_sp, []).
|
|
lvals_in_lval(field(_, Rval1, Rval2), Lvals1 ++ Lvals2) :-
|
|
lvals_in_rval(Rval1, Lvals1),
|
|
lvals_in_rval(Rval2, Lvals2).
|
|
lvals_in_lval(lvar(_), []).
|
|
lvals_in_lval(temp(_, _), []).
|
|
lvals_in_lval(mem_ref(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_lval(global_var_ref(_), []).
|
|
|
|
:- pred lvals_in_mem_ref(mem_ref::in, list(lval)::out) is det.
|
|
|
|
lvals_in_mem_ref(stackvar_ref(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_mem_ref(framevar_ref(Rval), Lvals) :-
|
|
lvals_in_rval(Rval, Lvals).
|
|
lvals_in_mem_ref(heap_ref(Rval1, _, Rval2), Lvals1 ++ Lvals2) :-
|
|
lvals_in_rval(Rval1, Lvals1),
|
|
lvals_in_rval(Rval2, Lvals2).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
build_input_arg_list(ProcInfo, VarLvals) :-
|
|
proc_info_get_headvars(ProcInfo, HeadVars),
|
|
proc_info_arg_info(ProcInfo, ArgInfos),
|
|
assoc_list.from_corresponding_lists(HeadVars, ArgInfos, VarArgInfos),
|
|
build_input_arg_list_2(VarArgInfos, VarLvals).
|
|
|
|
:- pred build_input_arg_list_2(assoc_list(prog_var, arg_info)::in,
|
|
assoc_list(prog_var, lval)::out) is det.
|
|
|
|
build_input_arg_list_2([], []).
|
|
build_input_arg_list_2([V - Arg | Rest0], VarArgs) :-
|
|
Arg = arg_info(Loc, Mode),
|
|
( Mode = top_in ->
|
|
arg_loc_to_register(Loc, Reg),
|
|
VarArgs = [V - Reg | VarArgs0]
|
|
;
|
|
VarArgs = VarArgs0
|
|
),
|
|
build_input_arg_list_2(Rest0, VarArgs0).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- func this_file = string.
|
|
|
|
this_file = "code_util.m".
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
:- end_module code_util.
|
|
%-----------------------------------------------------------------------------%
|