Files
mercury/compiler/code_util.m
Zoltan Somogyi d4bbcda309 Move all the frequently occurring layout structures and components of layout
Estimated hours taken: 40
Branches: main

Move all the frequently occurring layout structures and components of layout
structures into arrays where possible. By replacing N global variables holding
individual layout structures or layout structure components with one global
variable holding an array of them, we reduce the sizes of the symbol tables
stored in object files, which should speed up both the C compiler and the
linker.

Measured on the modules of the library, mdbcomp and compiler directories
compiled in grade asm_fast.gc.debug, this diff reduces the size of the
generated C source files by 7.8%, the size of the generated object files
by 10.4%, and the number of symbols in the symbol tables of those object files
by a whopping 42.8%. (These improvements include, and are not on top of,
the improvements in my previous similar diff.)

runtime/mercury_stack_layout.h:
	Each label layout structure has information about the type and
	location of every variable that is live at that label. We store
	this information in three arrays: an array of pseudo-typeinfos giving
	the types of all these variables, and two arrays MR_ShortLvals and
	MR_LongLvals respectively giving their locations. (Most of the time,
	the location's encoded form fits into one byte (the MR_ShortLval)
	but sometimes it needs more bits (this is when we use MR_LongLval)).

	We used to store these three arrays, whose elements are different
	types, in a single occurrence-specific common structure,
	one after the other, with a cumbersome mechanism being required
	to access them. We now store them as segments of three separate arrays,
	of pseudo-typeinfos, MR_ShortLvals and MR_LongLvals respectively.
	This makes access simpler and faster (which will matter more to any
	accurate garbage collector than it does to the debugger). It also
	allows more scope for compression, since reusing an existing segment of
	one of the three arrays is easier than reusing an entire common
	structure, which would require the equivalent of exact matches
	on all three arrays.

	Since most label layout structures that have information about
	variables can encode the variables' locations using only MR_ShortLvals,
	create a version of the label layout structure type that omits the
	field used to record the whereabouts of the long location descriptors.

	Add macros now generated by the compiler to initialize layout
	structures.

	Simplify a one-field struct.

runtime/mercury_grade.h:
	Increment the binary compatibility version number for debuggable
	executables, since .c and .o files from before and after the change
	to label layout structures are NOT compatible.

runtime/mercury_type_info.h:
	Fix some binary-compatibility-related bit rot.

runtime/mercury_misc.h:
	Move here the existing macros used by the compiler when generating
	references to layout arrays, and add new ones.

runtime/mercury_goto.h:
	Delete the macros moved to mercury_misc.h.
	Conform to the changes in mercury_stack_layout.h.

runtime/Mmakefile:
	Prevent the unnecessary rebuilding of mercury_conf.h.

runtime/mercury_accurate_gc.c:
runtime/mercury_agc_debug.c:
runtime/mercury_layout_util.c:
runtime/mercury_stack_trace.c:
runtime/mercury_types.h:
trace/mercury_trace.c:
trace/mercury_trace_vars.c:
	Conform to the changes in mercury_stack_layout.h.

runtime/mercury_wrapper.c:
	Improve the debug support a bit.

runtime/mercury_engine.h:
	Fix style.

compiler/layout.m:
	Make the change described at the top. Almost all layout structures
	are now in arrays. The only exceptions are those that occur rarely,
	and proc layouts, whose names need to be derivable from the name
	of the procedure itself.

	Instead of having a single type "layout_data" that can represent
	different kinds of single global variables (not array slots), have
	different kinds for different purposes. This makes the code clearer
	and allows traversals that do not have to skip over inapplicable kinds
	of layout structures.

compiler/layout_out.m:
	Output the new arrays.

compiler/stack_layout.m:
	Generate the new arrays. Previously, an individual term generated by
	stack_layout.m could represent several components of a layout
	structure, with the components separated by layout_out.m. We now
	do the separation in stack_layout.m itself, adding each component
	to the array to which it belongs.

	Instead of passing around a single stack_layout_info structure,
	pass around several smaller one. This is preferable, since I found out
	the hard way that including everything in one structure would give the
	structure 51 fields. Most parts of the module work with only one
	or two of these structures, which makes their role clearer.

	Cluster related predicates together.

compiler/options.m:
doc/user_guide.texi:
	Add an option that control whether stack_layout.m will attempt to
	compress the layout arrays that can meaningfully be comressed.

compiler/llds.m:
	Remove the old distinction between a data_addr and a data_name,
	replacing both types with a single new one: data_id. Since different
	kinds of data_names were treated differently in many places,
	the distinction in types (which was intended to allow us to process
	data_addrs that wrapped data_names differently from other kinds of
	data_addrs) wasn't buying us anything anymore.

	The new data_id type allows for the possibility that the code generator
	wants to generate a reference to an address it does not know yet,
	because it is a slot in a layout array, and the slot has not been
	allocated yet.

	Add the information from which the new layout array structures
	will be generated to the LLDS.

compiler/llds_out.m:
	Call layout_out.m to output the new layout arrays.

	Adapt the decl_id type to the replacement of data_addrs by data_ids.
	Don't both keeping track of the have-vs-have-not-declared status
	of structures that are always declared at the start.

	When writing out a data_addr, for some kinds of data_addr, llds_out.m
	would write out the name of the relevant variable, while for some other
	kinds, it would write out its address. This diff separates out those
	those things into separate predicates, each of which behaves
	consistently.

compiler/mercury_compile_llds_back_end.m:
	Convey the intended contents of the new layout arrays from
	stack_layout.m to llds_out.m.

compiler/continuation_info.m:
	Add a type required by the way we now generate proc_static structures
	for deep profiling.

compiler/hlds_rtti.m:
	Add distinguishing prefixes to the field names of the rtti_proc_label
	type.

compiler/code_info.m:
compiler/code_util.m:
compiler/erl_rtti.m:
compiler/exprn_aux.m:
compiler/global_data.m:
compiler/ll_pseudo_type_info.m:
compiler/ml_code_util.m:
compiler/opt_debug.m:
compiler/proc_gen.m:
compiler/prog_rep.m:
compiler/rtti_out.m:
compiler/unify_gen.m:
	Conform to the changes above.

tests/debugger/declarative/track_through_catch.exp:
	Expect procedures to be listed in the proper order.

tests/EXPECT_FAIL_TESTS.asm_fast.gc.debug:
tests/EXPECT_FAIL_TESTS.asm_fast.gc.profdeep:
	Add these files to ignore expected failues in these grades.
2009-10-30 03:33:34 +00:00

425 lines
15 KiB
Mathematica

%-----------------------------------------------------------------------------%
% vim: ft=mercury ts=4 sw=4 et
%-----------------------------------------------------------------------------%
% Copyright (C) 1994-2009 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 bool.
:- 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)).
:- func make_entry_label(module_info, pred_id, proc_id, immed) = code_addr.
:- func make_entry_label_from_rtti(rtti_proc_label, immed) = code_addr.
% 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.
%
:- func make_local_entry_label(module_info, pred_id, proc_id, immed) = label.
% Create a label internal to a Mercury procedure.
%
:- func make_internal_label(module_info, pred_id, proc_id, int) = label.
:- func extract_proc_label_from_code_addr(code_addr) = proc_label.
:- 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, bool::out) is det.
% 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.
%
:- func lvals_in_rval(rval) = list(lval).
:- func lvals_in_lval(lval) = list(lval).
:- func lvals_in_lvals(list(lval)) = list(lval).
% 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 libs.compiler_util.
:- import_module int.
:- import_module term.
%---------------------------------------------------------------------------%
make_entry_label(ModuleInfo, PredId, ProcId, Immed) = ProcAddr :-
RttiProcLabel = make_rtti_proc_label(ModuleInfo, PredId, ProcId),
ProcAddr = make_entry_label_from_rtti(RttiProcLabel, Immed).
make_entry_label_from_rtti(RttiProcLabel, Immed) = ProcAddr :-
ProcIsImported = RttiProcLabel ^ rpl_proc_is_imported,
(
ProcIsImported = yes,
ProcLabel = make_proc_label_from_rtti(RttiProcLabel),
ProcAddr = code_imported_proc(ProcLabel)
;
ProcIsImported = no,
Label = make_local_entry_label_from_rtti(RttiProcLabel, Immed),
ProcAddr = code_label(Label)
).
make_local_entry_label(ModuleInfo, PredId, ProcId, Immed) = Label :-
RttiProcLabel = make_rtti_proc_label(ModuleInfo, PredId, ProcId),
Label = make_local_entry_label_from_rtti(RttiProcLabel, Immed).
:- func make_local_entry_label_from_rtti(rtti_proc_label, immed) = label.
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.
ProcIsExported = RttiProcLabel ^ rpl_proc_is_exported,
(
ProcIsExported = yes,
EntryType = entry_label_exported
;
ProcIsExported = no,
EntryType = entry_label_local
),
Label = entry_label(EntryType, ProcLabel)
;
Immed = yes(ProcsPerFunc - proc(CurPredId, CurProcId)),
Label = choose_local_label_type(ProcsPerFunc, CurPredId, CurProcId,
RttiProcLabel ^ rpl_pred_id, RttiProcLabel ^ rpl_proc_id,
ProcLabel)
).
:- func choose_local_label_type(int, pred_id, proc_id, pred_id, proc_id,
proc_label) = label.
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_label(EntryType, ProcLabel).
%-----------------------------------------------------------------------------%
make_internal_label(ModuleInfo, PredId, ProcId, LabelNum) = Label :-
ProcLabel = make_proc_label(ModuleInfo, PredId, ProcId),
Label = internal_label(LabelNum, ProcLabel).
extract_proc_label_from_code_addr(CodeAddr) = ProcLabel :-
( CodeAddr = code_label(Label) ->
ProcLabel = get_proc_label(Label)
; CodeAddr = code_imported_proc(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(hlds_goal(GoalExpr, _GoalInfo), May) :-
goal_may_alloc_temp_frame_2(GoalExpr, 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 = hlds_goal(_, GoalInfo),
CodeModel = goal_info_get_code_model(GoalInfo),
(
CodeModel = model_non,
May = yes
;
( CodeModel = model_det
; CodeModel = model_semi
),
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(_), _) :-
% These should have been expanded out by now.
unexpected(this_file, "goal_may_alloc_temp_frame_2: shorthand").
:- 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 = llds_instr(if_val(Test, Target), Comment) ->
neg_rval(Test, NewTest),
Instrs = [llds_instr(if_val(NewTest, Target), Comment)]
;
negate_the_test(Instrs0, Instrs1),
Instrs = [Instr0 | Instrs1]
).
%-----------------------------------------------------------------------------%
lvals_in_lvals([]) = [].
lvals_in_lvals([First | Rest]) = FirstLvals ++ RestLvals :-
FirstLvals = lvals_in_lval(First),
RestLvals = lvals_in_lvals(Rest).
lvals_in_rval(lval(Lval)) = [Lval | lvals_in_lval(Lval)].
lvals_in_rval(var(_)) = [].
lvals_in_rval(mkword(_, Rval)) = lvals_in_rval(Rval).
lvals_in_rval(const(_)) = [].
lvals_in_rval(unop(_, Rval)) = lvals_in_rval(Rval).
lvals_in_rval(binop(_, Rval1, Rval2)) =
lvals_in_rval(Rval1) ++ lvals_in_rval(Rval2).
lvals_in_rval(mem_addr(MemRef)) = lvals_in_mem_ref(MemRef).
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_in_rval(Rval).
lvals_in_lval(redofr_slot(Rval)) = lvals_in_rval(Rval).
lvals_in_lval(redoip_slot(Rval)) = lvals_in_rval(Rval).
lvals_in_lval(succfr_slot(Rval)) = lvals_in_rval(Rval).
lvals_in_lval(prevfr_slot(Rval)) = lvals_in_rval(Rval).
lvals_in_lval(hp) = [].
lvals_in_lval(sp) = [].
lvals_in_lval(parent_sp) = [].
lvals_in_lval(field(_, Rval1, Rval2)) =
lvals_in_rval(Rval1) ++ lvals_in_rval(Rval2).
lvals_in_lval(lvar(_)) = [].
lvals_in_lval(temp(_, _)) = [].
lvals_in_lval(mem_ref(Rval)) = lvals_in_rval(Rval).
lvals_in_lval(global_var_ref(_)) = [].
:- func lvals_in_mem_ref(mem_ref) = list(lval).
lvals_in_mem_ref(stackvar_ref(Rval)) = lvals_in_rval(Rval).
lvals_in_mem_ref(framevar_ref(Rval)) = lvals_in_rval(Rval).
lvals_in_mem_ref(heap_ref(Rval1, _, Rval2)) =
lvals_in_rval(Rval1) ++ lvals_in_rval(Rval2).
%-----------------------------------------------------------------------------%
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]
;
( Mode = top_out
; Mode = top_unused
),
VarArgs = VarArgs0
),
build_input_arg_list_2(Rest0, VarArgs0).
%---------------------------------------------------------------------------%
:- func this_file = string.
this_file = "code_util.m".
%-----------------------------------------------------------------------------%
:- end_module code_util.
%-----------------------------------------------------------------------------%