Files
mercury/compiler/string_switch.m
Zoltan Somogyi 00ea415659 Implement scalar and vector global data for the MLDS backend, modelled on
Estimated hours taken: 32
Branches: main

Implement scalar and vector global data for the MLDS backend, modelled on
the implementation of global data for the LLDS backend. Use scalar global
data to eliminate redundant copies of static memory cells. Use vector global
data to implement lookup switches, and to implement string switches more
efficiently.

The diff reduces the compiler executable's size by 3.3% by eliminating
duplicate copies of static cells. The diff can reduce the sizes of object files
not only through this reduction in the size of read-only data, but also through
reductions in the size of the needed relocation info: even in the absence of
duplicated cells, using one global variable that holds an array of all the
cells of the same type requires less relocation info than a whole bunch of
separate global variables each holding one cell. If C debugging is enabled,
we can also expect a significant reduction in the size of the debug information
stored in object files AND in executables, for the same reason. (This was the
original motivation for scalar static data on the LLDS backend; the large
amount of relocation information in object files, especially if Mercury
debugging was enabled, led to long link times.)

compiler/ml_global_data.m:
	Make the changes described above.

compiler/ml_lookup_switch.m:
	This new module implements lookup switches for the MLDS backend.
	For now, it implements only model_det and model_semi switches.

compiler/ml_switch_gen.m:
	Call the new module when appropriate.

	Do not require the switch generation methods that never generate
	definitions to return an empty list of definitions.

compiler/ml_backend.m:
	Add the new module.

compiler/notes/compiler_design.html:
	Mention the new module, and fix some documentation rot.

compiler/mlds.m:
	Extend the relevant types to allow the generated MLDS code to refer
	to both scalar and vector global data.

	Move a predicate that belongs here from ml_code_util.m.

	Rename a predicate to avoid ambiguity with its own return type.

	Give the functors of some types distinguishing prefixes.

compiler/ml_util.m:
	Replace some semidet predicates with functions returning bool,
	since the semidet predicates silently did the wrong thing on the new
	additions to the MLDS.

compiler/ml_code_gen.m:
	Ensure that we do not generate references to scalar and vector common
	cells on platforms which do not (yet) support them. At the moment,
	they are supported only when generating C.

	Put some code into a predicate of its own.

compiler/builtin_ops.m:
	Extend the type that represents array elements to allow them to be
	structures, which they are for vector globals.

compiler/ml_code_util.m:
	Add some new utility predicates and functions.

	Move some predicates that are now needed in more than one module here.

	Remove the predicates moved to mlds.m.

	Conform to the changes above.

compiler/ml_string_switch.m:
compiler/string_switch.m:
	Instead of two separate arrays, use one array of structures (a static
	vector), since they way, the string and the next slot indicator,
	which are accesses together, are next to each other and thus
	in the same cache block.

compiler/lookup_switch.m:
compiler/switch_util.m:
	Move several predicates from lookup_switch.m to switch_util.m,
	since now ml_lookup_switch.m needs them too. Parameterize the moved
	predicates as needed.

	Conform to the changes above.

compiler/llds.m:
	Add prefixes to some functor names to avoid ambiguities.

compiler/llds_out.m:
compiler/lookup_util.m:
compiler/mercury_compile.m:
	Minor style improvements.

compiler/global_data.m:
	Minor cleanups. Give names to some data types, and add prefixes to some
	field names.

	Conform to the changes above.

compiler/jumpopt.m:
	Minor style improvements.

	Conform to the changes above.

compiler/opt_debug.m:
	Fix some misleading variable names.

compiler/reassign.m:
	Factor out some duplicated code.

compiler/ll_pseudo_type_info.m:
compiler/ml_closure_gen.m:
compiler/ml_elim_nested.m:
compiler/ml_optimize.m:
compiler/ml_tag_switch.m:
compiler/ml_tailcall.m:
compiler/ml_unify_gen.m:
compiler/mlds_to_c.m:
compiler/mlds_to_gcc.m:
compiler/mlds_to_il.m:
compiler/mlds_to_java.m:
compiler/mlds_to_managed.m:
compiler/rtti_to_mlds.m:
compiler/stack_layout.m:
compiler/unify_gen.m:
	Conform to the changes above.

tests/hard_coded/lookup_switch_simple.{m,exp}:
tests/hard_coded/lookup_switch_simple_bitvec.{m,exp}:
tests/hard_coded/lookup_switch_simple_non.{m,exp}:
tests/hard_coded/lookup_switch_simple_opt.{m,exp}:
	New test cases to exercise the new functionality.

tests/hard_coded/Mmakefile:
tests/hard_coded/Mercury.options:
	Enable the new tests.
2009-09-21 04:09:06 +00:00

228 lines
9.0 KiB
Mathematica

%-----------------------------------------------------------------------------%
% vim: ft=mercury ts=4 sw=4 et
%-----------------------------------------------------------------------------%
% Copyright (C) 1994-2007, 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: string_switch.m.
% Author: fjh.
%
% For switches on strings, we generate a hash table using open addressing
% to resolve hash conflicts.
%
%-----------------------------------------------------------------------------%
:- module ll_backend.string_switch.
:- interface.
:- import_module hlds.code_model.
:- import_module hlds.hlds_goal.
:- import_module ll_backend.code_info.
:- import_module ll_backend.llds.
:- import_module parse_tree.prog_data.
:- import_module list.
:- pred generate_string_switch(list(tagged_case)::in, rval::in, string::in,
code_model::in, can_fail::in, hlds_goal_info::in, label::in,
branch_end::in, branch_end::out, llds_code::out,
code_info::in, code_info::out) is det.
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
:- implementation.
:- import_module backend_libs.builtin_ops.
:- import_module backend_libs.switch_util.
:- import_module hlds.hlds_data.
:- import_module hlds.hlds_goal.
:- import_module hlds.hlds_llds.
:- import_module libs.compiler_util.
:- import_module ll_backend.code_gen.
:- import_module ll_backend.switch_case.
:- import_module ll_backend.trace_gen.
:- import_module cord.
:- import_module int.
:- import_module map.
:- import_module maybe.
:- import_module pair.
:- import_module string.
%-----------------------------------------------------------------------------%
generate_string_switch(Cases, VarRval, VarName, CodeModel, _CanFail,
SwitchGoalInfo, EndLabel, !MaybeEnd, Code, !CI) :-
% We get the registers we use as working storage in the hash table lookup
% code now, before we generate the code of the switch arms, since the set
% of free registers will in general be different before and after that
% action. However, it is safe to release them immediately, even though
% we haven't yet generated all the code which uses them, because that
% code will *only* be executed before the code for the cases, and because
% that code is generated manually below. Releasing the registers early
% allows the code of the cases to make use of them.
acquire_reg(reg_r, SlotReg, !CI),
acquire_reg(reg_r, RowReg, !CI),
acquire_reg(reg_r, StringReg, !CI),
release_reg(SlotReg, !CI),
release_reg(RowReg, !CI),
release_reg(StringReg, !CI),
get_next_label(LoopLabel, !CI),
get_next_label(FailLabel, !CI),
get_next_label(JumpLabel, !CI),
% Determine how big to make the hash table. Currently we round the number
% of cases up to the nearest power of two, and then double it.
% This should hopefully ensure that we don't get too many hash collisions.
list.length(Cases, NumCases),
int.log2(NumCases, LogNumCases),
int.pow(2, LogNumCases, RoundedNumCases),
TableSize = 2 * RoundedNumCases,
HashMask = TableSize - 1,
remember_position(!.CI, BranchStart),
Params = represent_params(VarName, SwitchGoalInfo, CodeModel, BranchStart,
EndLabel),
% Compute the hash table.
map.init(CaseLabelMap0),
switch_util.string_hash_cases(Cases, HashMask,
represent_tagged_case_for_llds(Params),
CaseLabelMap0, CaseLabelMap, !MaybeEnd, !CI, HashValsMap),
map.to_assoc_list(HashValsMap, HashValsList),
switch_util.calc_string_hash_slots(HashValsList, HashValsMap,
HashSlotsMap),
% We must generate the failure code in the context in which none of the
% switch arms have been executed yet.
reset_to_position(BranchStart, !CI),
generate_failure(FailCode, !CI),
% Generate the data structures for the hash table.
gen_string_hash_slots(0, TableSize, HashSlotsMap, FailLabel,
TableRows, Targets),
% Generate the code for the cases.
map.foldl(add_remaining_case, CaseLabelMap, empty, CasesCode),
EndLabelCode = singleton(
llds_instr(label(EndLabel), "end of hashed string switch")
),
% Generate the code for the hash table lookup.
RowElemTypes = [lt_string, lt_integer],
add_vector_static_cell(RowElemTypes, TableRows, TableAddr, !CI),
ArrayElemTypes = [scalar_elem_string, scalar_elem_int],
ArrayElemType = array_elem_struct(ArrayElemTypes),
TableAddrRval = const(llconst_data_addr(TableAddr, no)),
HashLookupCode = from_list([
llds_instr(comment("hashed string switch"), ""),
llds_instr(assign(SlotReg,
binop(bitwise_and, unop(hash_string, VarRval),
const(llconst_int(HashMask)))),
"compute the hash value of the input string"),
llds_instr(label(LoopLabel), "begin hash chain loop"),
llds_instr(assign(RowReg,
binop(int_mul, lval(SlotReg), const(llconst_int(2)))),
"find the start of the row"),
llds_instr(assign(StringReg,
binop(array_index(ArrayElemType),
TableAddrRval, lval(RowReg))),
"lookup the string for this hash slot"),
llds_instr(if_val(binop(logical_and, lval(StringReg),
binop(str_eq, lval(StringReg), VarRval)),
code_label(JumpLabel)),
"did we find a match?"),
llds_instr(assign(SlotReg,
binop(array_index(ArrayElemType),
TableAddrRval,
binop(int_add, lval(RowReg), const(llconst_int(1))))),
"not yet, so get next slot in hash chain"),
llds_instr(
if_val(binop(int_ge, lval(SlotReg), const(llconst_int(0))),
code_label(LoopLabel)),
"keep searching until we reach the end of the chain"),
llds_instr(label(FailLabel), "no match, so fail")
]),
% XXX The generated code would be faster (due to better locality)
% if we included the target addresses in the main table. Unfortunately,
% that would require two extensions to the LLDS. The first and relatively
% easy change would be a new LLDS instruction that represents a goto
% to an arbitrary rval (in this case, the rval taken from the selected
% table row). The second and substantially harder change would be making
% the internal labels of the switch arms actually storable in static data.
% We do not currently have any way to refer to internal labels from data,
% and optimizations that manipulate labels (such as frameopt, which can
% duplicate them, and dupelim, which can replace them with other labels)
% would have to be taught to reflect any changes they make in the global
% data. It is the last step that is the killer in the terms of difficulty
% of implementation.
JumpCode = from_list([
llds_instr(label(JumpLabel), "we found a match"),
llds_instr(computed_goto(lval(SlotReg), Targets),
"jump to the corresponding code")
]),
Code = HashLookupCode ++ FailCode ++ JumpCode ++ CasesCode ++
EndLabelCode.
:- pred gen_string_hash_slots(int::in, int::in,
map(int, string_hash_slot(label))::in, label::in,
list(list(rval))::out, list(maybe(label))::out) is det.
gen_string_hash_slots(Slot, TableSize, HashSlotMap, FailLabel,
TableRows, MaybeTargets) :-
( Slot = TableSize ->
TableRows = [],
MaybeTargets = []
;
gen_string_hash_slot(Slot, HashSlotMap, FailLabel,
StringRval, NextSlotRval, Target),
gen_string_hash_slots(Slot + 1, TableSize, HashSlotMap, FailLabel,
TailTableRows, TailMaybeTargets),
HeadTableRow = [StringRval, NextSlotRval],
TableRows = [HeadTableRow | TailTableRows],
MaybeTargets = [yes(Target) | TailMaybeTargets]
).
:- pred gen_string_hash_slot(int::in, map(int, string_hash_slot(label))::in,
label::in, rval::out, rval::out, label::out) is det.
gen_string_hash_slot(Slot, HashSlotMap, FailLabel,
StringRval, NextSlotRval, Target) :-
( map.search(HashSlotMap, Slot, SlotInfo) ->
SlotInfo = string_hash_slot(Next, String, CaseLabel),
NextSlotRval = const(llconst_int(Next)),
StringRval = const(llconst_string(String)),
Target = CaseLabel
;
StringRval = const(llconst_int(0)),
NextSlotRval = const(llconst_int(-2)),
Target = FailLabel
).
:- pred this_is_last_case(int::in, int::in,
map(int, string_hash_slot(label))::in) is semidet.
this_is_last_case(Slot, TableSize, Table) :-
Slot1 = Slot + 1,
( Slot1 >= TableSize ->
true
;
\+ map.contains(Table, Slot1),
this_is_last_case(Slot1, TableSize, Table)
).
%-----------------------------------------------------------------------------%
:- func this_file = string.
this_file = "string_switch.m".
%-----------------------------------------------------------------------------%