Files
mercury/compiler/code_aux.m
Zoltan Somogyi c8e4004825 This diff makes code_info.m and many callers of its predicates easier to read
Estimated hours taken: 4
Branches: main

This diff makes code_info.m and many callers of its predicates easier to read
and to maintain, but contains no changes in algorithms whatsoever.

compiler/code_info.m:
	Bring this module into line with our current coding standards.
	Use predmode declarations, functions, and state variable syntax
	when appropriate.

	Reorder arguments of predicates where necessary for the use of state
	variable syntax, and where this improves readability.

	Where a predicate returned its input code_info unchanged, purely
	to allow the convenient use of DCG notation in the caller, delete the
	unnecessary output argument. This should make the caller somewhat more
	efficient, since it can avoid updating the stack slot holding the
	current code_info.

	Replace old-style lambdas with new-style lambdas or with partially
	applied named procedures.

compiler/*.m:
	Conform to the changes in code_info.m. This mostly means using the
	new argument orders of predicates exported by hlds_pred.m, and
	using state variable notation.
2003-10-27 05:42:37 +00:00

112 lines
3.9 KiB
Mathematica

%-----------------------------------------------------------------------------%
% Copyright (C) 1994-2003 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.
%---------------------------------------------------------------------------%
%
% Auxiliary code generator module. Unlike code_util, it imports code_info.
%
% Main authors: conway, zs.
%
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
:- module ll_backend__code_aux.
:- interface.
:- import_module hlds__hlds_goal.
:- import_module hlds__hlds_llds.
:- import_module ll_backend__code_info.
:- import_module parse_tree__prog_data.
:- import_module bool.
% code_aux__contains_simple_recursive_call(G, CI, Last) succeeds
% if G is a conjunction of goals, exactly one of which is a recursive
% call (CI says what the current procedure is), and there are no
% other goals that cause control to leave this procedure. Last is
% set dependening on whether the recursive call is last in the
% conjunction or not.
% XXX should avoid the dependency on code_info here
:- pred code_aux__contains_simple_recursive_call(hlds_goal, code_info, bool).
:- mode code_aux__contains_simple_recursive_call(in, in, out) is semidet.
:- pred code_aux__explain_stack_slots(stack_slots, prog_varset, string).
:- mode code_aux__explain_stack_slots(in, in, out) is det.
%---------------------------------------------------------------------------%
:- implementation.
:- import_module hlds__goal_form.
:- import_module ll_backend__llds.
:- import_module ll_backend__llds_out.
:- import_module string, list, assoc_list, map, std_util, varset.
%-----------------------------------------------------------------------------%
code_aux__contains_simple_recursive_call(Goal - _, CodeInfo, Last) :-
Goal = conj(Goals),
code_aux__contains_simple_recursive_call_expr(Goals, CodeInfo, Last).
:- pred code_aux__contains_simple_recursive_call_expr(list(hlds_goal)::in,
code_info::in, bool::out) is semidet.
code_aux__contains_simple_recursive_call_expr([Goal|Goals], CodeInfo, Last) :-
Goal = GoalExpr - _,
(
contains_only_builtins_expr(GoalExpr)
->
code_aux__contains_simple_recursive_call_expr(Goals, CodeInfo,
Last)
;
code_aux__is_recursive_call(GoalExpr, CodeInfo),
( Goals = [] ->
Last = yes
;
contains_only_builtins_list(Goals),
Last = no
)
).
:- pred code_aux__is_recursive_call(hlds_goal_expr, code_info).
:- mode code_aux__is_recursive_call(in, in) is semidet.
code_aux__is_recursive_call(Goal, CodeInfo) :-
Goal = call(CallPredId, CallProcId, _, BuiltinState, _, _),
BuiltinState = not_builtin,
code_info__get_pred_id(CodeInfo, PredId),
PredId = CallPredId,
code_info__get_proc_id(CodeInfo, ProcId),
ProcId = CallProcId.
%-----------------------------------------------------------------------------%
code_aux__explain_stack_slots(StackSlots, VarSet, Explanation) :-
map__to_assoc_list(StackSlots, StackSlotsList),
code_aux__explain_stack_slots_2(StackSlotsList, VarSet, "",
Explanation1),
string__append("\nStack slot assignments (if any):\n", Explanation1,
Explanation).
:- pred code_aux__explain_stack_slots_2(assoc_list(prog_var, lval), prog_varset,
string, string).
:- mode code_aux__explain_stack_slots_2(in, in, in, out) is det.
code_aux__explain_stack_slots_2([], _, String, String).
code_aux__explain_stack_slots_2([Var - Lval | Rest], VarSet, String0, String) :-
code_aux__explain_stack_slots_2(Rest, VarSet, String0, String1),
( llds_out__lval_to_string(Lval, LvalString0) ->
LvalString = LvalString0
;
LvalString = "some lval"
),
varset__lookup_name(VarSet, Var, VarName),
string__append_list([VarName, "\t ->\t", LvalString, "\n", String1],
String).
%---------------------------------------------------------------------------%