Files
mercury/compiler/switch_gen.m
Zoltan Somogyi df0d9036cf Optimize calls that would be tail calls in Prolog but are followed by
Estimated hours taken: 40
Branches: main

Optimize calls that would be tail calls in Prolog but are followed by
construction unifications in Mercury: last call modulo construction.
For now, the optimization is available only for the LLDS backend.

compiler/lco.m:
	Turn this module from a placeholder to a real implementation
	of the optimization.

compiler/hlds_goal.m:
	Allow lco.m to attach to construction unifications a note that says
	that certain arguments, instead of being filled in by the unification,
	should have their addresses taken and stored in the corresponding
	variables.

	Group this note together with the note that asks for term size
	profiling to avoid an increase in the sizes of goals in the compiler
	in most cases.

compiler/hlds_pred.m:
	Provide a predicate for setting the name of a predicate after its
	creation. This functionality is used by lco.m.

	Extend the pred_transformation part of the pred_origin type to allow
	it to express that a procedure was created by lco.m.

	List the new primitive store_at_ref as a no-typeinfo builtin.

	Fix some problems with indentation.

compiler/layout_out.m:
	Handle the new pred_transformation.

compiler/unify_gen.m:
	When processing construction unifications that have the new feaure
	turned on, perform the requested action.

	Fix some departures from coding style. Shorten lines by deleting
	unnecessary module qualifications. Add some auxiliary predicates
	to make the code easier to read.

compiler/var_locn.m:
	Fix an earlier oversight: when materializing variables inside rvals
	and lvals, look inside memory references too. Previously, the omission
	didn't matter, since we didn't generate such references, but now we do.

	Fix some departures from coding style.

compiler/llds_out.m:
	Fix some old XXXs in code handling memory references. We didn't use to
	generate such references, but now we do.

	Move some functionality here from code_aux.m.

compiler/code_info.m:
	Provide some primitive operations needed by the new code in var_locn.m.

	Delete an unneeded predicate.

compiler/options.m:
	Rename the existing option optimize_constructor_last_call as
	optimize_constructor_last_call_accumulator, since that optimization
	is done by accumulator.m.

	Make optimize_constructor_last_call be the option that calls for the
	new optimization.

compiler/handle_options.m:
	Handle the implications of the new option.

compiler/mercury_compile.m:
	Invoke the lco module by its new interface.

librrary/private_builtin.m:
	Add a new primitive operation, store_at_ref, for use by the new
	optimization.

	Switch the module to four-space indentation.

compiler/add_clause.m:
	Comment out the warning for clauses for builtin, since this is needed
	to bootstrap the addition of the new builtin.

compiler/term_constr_initial.m:
	Handle the new builtin.

compiler/accumulator.m:
	Conform to the change in options.

compiler/builtin_ops.m:
	Provide a third template for builtins, for use by store_at_ref.

	Convert the file to four-space indentation.

compiler/call_gen.m:
	Generate code following the new builtin template.

compiler/rl_exprn.m:
	Minor changes to conform to the changes in builtin templates.

compiler/quantification.m:
	Minor changes to conform to the changes in construct unifications.

	Don't make the "get" predicates operating on quantification_infos
	to return the "new" quantification_info: it is always the same
	as the old one.

compiler/aditi_builtin_ops.m:
compiler/common.m:
compiler/deep_profiling.m:
compiler/higher_order.m:
compiler/hlds_out.m:
compiler/lambda.m:
compiler/magic_util.m:
compiler/ml_unify_gen.m:
compiler/modecheck_unify.m:
compiler/polymorphism.m:
compiler/size_prof.m:
	Minor changes to conform to the changes in construct unifications.

compiler/dependency_graph.m:
	Add a new predicate to recompute the dependency information,
	even if a previous (and possibly now inaccurate) version is present.

	Change the interface to make it clearer, by changing bools into types
	specific to the situation.

	Convert the file to four-space indentation.

compiler/mode_constraints.m:
	Minor changes to conform to the changes in dependency_graph.m.

compiler/code_aux.m:
	Delete this module. Half its functionality has been moved into
	llds_out.m, half to middle_rec.m (its only user).

compiler/goal_form.m:
	Move the predicates in this module that are used only by middle_rec.m
	to middle_rec.m.

	Convert the file to four-space indentation.

compiler/goal_util.m:
compiler/det_util.m:
	Move update_instmap from det_util to goal_util, since it is usefulness
	extends beyond determinism analysis.

	Convert det_util.m to four-space indentation.

compiler/middle_rec.m:
	Move here the code required only here from code_aux and goal_form.
	Update the moved code for the changes in construct unifications.
	The updates are specific to middle_rec.m: they wouldn't be of use
	to other modules. They basically say that any code that takes the
	addresses of fields cannot be handled by middle_rec.m.

compiler/code_gen.m:
compiler/det_analysis.m:
compiler/live_vars.m:
compiler/ll_backend.m:
compiler/loop_inv.m:
compiler/switch_detection.m:
compiler/switch_gen.m:
compiler/notes/compiler_design.html:
	Minor changes to conform to the deletion of code_aux.m and/or the
	movement of code from det_util to goal_util.m.

compiler/opt_debug.m:
	Print info for vars in rvals.

compiler/hlds_module.m:
	Convert a lambda to an explicit predicate to make some code easier to
	read.

	Switch the module to four-space indentation.
2005-09-13 04:56:20 +00:00

345 lines
12 KiB
Mathematica

%-----------------------------------------------------------------------------%
% Copyright (C) 1994-2005 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: switch_gen.m
% Authors: conway, fjh, zs
%
% This module handles the generation of code for switches, which are
% disjunctions that do not require backtracking. Switches are detected
% in switch_detection.m. This is the module that determines what
% sort of indexing to use for each switch and then actually generates the
% code.
%
% Currently the following forms of indexing are used:
%
% For switches on atomic data types (int, char, enums),
% if the cases are not sparse, we use the value of the switch variable
% to index into a jump table.
%
% If all the alternative goals for a switch on an atomic data type
% contain only construction unifications of constants, then we generate
% a dense lookup table (an array) for each output variable of the switch,
% rather than a dense jump table, so that executing the switch becomes
% a matter of doing an array index for each output variable - avoiding
% the branch overhead of the jump-table.
%
% For switches on discriminated union types, we generate code that does
% indexing first on the primary tag, and then on the secondary tag (if
% the primary tag is shared between several function symbols). The
% indexing code for switches on both primary and secondary tags can be
% in the form of a try-me-else chain, a try chain, a dense jump table
% or a binary search.
%
% For switches on strings, we lookup the address to jump to in a
% hash table, using open addressing to resolve hash collisions.
%
% For all other cases (or if the --smart-indexing option was
% disabled), we just generate a chain of if-then-elses.
%
%---------------------------------------------------------------------------%
:- module ll_backend__switch_gen.
:- interface.
:- import_module hlds__code_model.
:- import_module hlds__hlds_data.
:- 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 switch_gen__generate_switch(code_model::in, prog_var::in, can_fail::in,
list(case)::in, hlds_goal_info::in, code_tree::out,
code_info::in, code_info::out) is det.
%---------------------------------------------------------------------------%
:- implementation.
:- import_module backend_libs__switch_util.
:- import_module check_hlds__type_util.
:- import_module hlds__goal_form.
:- import_module hlds__hlds_llds.
:- import_module libs__globals.
:- import_module libs__options.
:- import_module libs__tree.
:- import_module ll_backend__code_gen.
:- import_module ll_backend__dense_switch.
:- import_module ll_backend__lookup_switch.
:- import_module ll_backend__string_switch.
:- import_module ll_backend__tag_switch.
:- import_module ll_backend__trace.
:- import_module ll_backend__unify_gen.
:- import_module bool.
:- import_module int.
:- import_module map.
:- import_module require.
:- import_module std_util.
:- import_module string.
%---------------------------------------------------------------------------%
% Choose which method to use to generate the switch.
% CanFail says whether the switch covers all cases.
switch_gen__generate_switch(CodeModel, CaseVar, CanFail, Cases, GoalInfo,
Code, !CI) :-
goal_info_get_store_map(GoalInfo, StoreMap),
SwitchCategory = switch_gen__determine_category(!.CI, CaseVar),
code_info__get_next_label(EndLabel, !CI),
switch_gen__lookup_tags(!.CI, Cases, CaseVar, TaggedCases0),
list__sort_and_remove_dups(TaggedCases0, TaggedCases),
code_info__get_globals(!.CI, Globals),
globals__lookup_bool_option(Globals, smart_indexing,
Indexing),
(
% Check for a switch on a type whose representation
% uses reserved addresses
list__member(Case, TaggedCases),
Case = case(_Priority, Tag, _ConsId, _Goal),
(
Tag = reserved_address(_)
;
Tag = shared_with_reserved_addresses(_, _)
)
->
% XXX This may be be inefficient in some cases.
switch_gen__generate_all_cases(TaggedCases, CaseVar, CodeModel,
CanFail, GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
;
Indexing = yes,
SwitchCategory = atomic_switch,
code_info__get_maybe_trace_info(!.CI, MaybeTraceInfo),
MaybeTraceInfo = no,
list__length(TaggedCases, NumCases),
globals__lookup_int_option(Globals, lookup_switch_size,
LookupSize),
NumCases >= LookupSize,
globals__lookup_int_option(Globals, lookup_switch_req_density,
ReqDensity),
lookup_switch__is_lookup_switch(CaseVar, TaggedCases,
GoalInfo, CanFail, ReqDensity, StoreMap, no,
MaybeEndPrime, CodeModel, FirstVal, LastVal,
NeedRangeCheck, NeedBitVecCheck, OutVars, CaseVals,
MLiveness, !CI)
->
MaybeEnd = MaybeEndPrime,
lookup_switch__generate(CaseVar, OutVars, CaseVals,
FirstVal, LastVal, NeedRangeCheck, NeedBitVecCheck,
MLiveness, StoreMap, no, Code, !CI)
;
Indexing = yes,
SwitchCategory = atomic_switch,
list__length(TaggedCases, NumCases),
globals__lookup_int_option(Globals, dense_switch_size,
DenseSize),
NumCases >= DenseSize,
globals__lookup_int_option(Globals, dense_switch_req_density,
ReqDensity),
dense_switch__is_dense_switch(!.CI, CaseVar, TaggedCases,
CanFail, ReqDensity, FirstVal, LastVal, CanFail1)
->
dense_switch__generate(TaggedCases,
FirstVal, LastVal, CaseVar, CodeModel, CanFail1,
GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
;
Indexing = yes,
SwitchCategory = string_switch,
list__length(TaggedCases, NumCases),
globals__lookup_int_option(Globals, string_switch_size,
StringSize),
NumCases >= StringSize
->
string_switch__generate(TaggedCases, CaseVar, CodeModel,
CanFail, GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
;
Indexing = yes,
SwitchCategory = tag_switch,
list__length(TaggedCases, NumCases),
globals__lookup_int_option(Globals, tag_switch_size,
TagSize),
NumCases >= TagSize
->
tag_switch__generate(TaggedCases, CaseVar, CodeModel, CanFail,
GoalInfo, EndLabel, no, MaybeEnd, Code, !CI)
;
% To generate a switch, first we flush the
% variable on whose tag we are going to switch, then we
% generate the cases for the switch.
switch_gen__generate_all_cases(TaggedCases, CaseVar,
CodeModel, CanFail, GoalInfo, EndLabel, no, MaybeEnd,
Code, !CI)
),
code_info__after_all_branches(StoreMap, MaybeEnd, !CI).
%---------------------------------------------------------------------------%
% We categorize switches according to whether the value
% being switched on is an atomic type, a string, or
% something more complicated.
:- func switch_gen__determine_category(code_info, prog_var) = switch_category.
switch_gen__determine_category(CI, CaseVar) = SwitchCategory :-
Type = code_info__variable_type(CI, CaseVar),
code_info__get_module_info(CI, ModuleInfo),
classify_type(ModuleInfo, Type) = TypeCategory,
SwitchCategory = switch_util__type_cat_to_switch_cat(TypeCategory).
%---------------------------------------------------------------------------%
:- pred switch_gen__lookup_tags(code_info::in, list(case)::in, prog_var::in,
cases_list::out) is det.
switch_gen__lookup_tags(_, [], _, []).
switch_gen__lookup_tags(CI, [Case | Cases], Var, [TaggedCase | TaggedCases]) :-
Case = case(ConsId, Goal),
Tag = code_info__cons_id_to_tag(CI, Var, ConsId),
Priority = switch_util__switch_priority(Tag),
TaggedCase = case(Priority, Tag, ConsId, Goal),
switch_gen__lookup_tags(CI, Cases, Var, TaggedCases).
%---------------------------------------------------------------------------%
%---------------------------------------------------------------------------%
% Generate a switch as a chain of if-then-elses.
%
% To generate a case for a switch we generate
% code to do a tag-test and fall through to the next case in
% the event of failure.
%
% Each case except the last consists of
%
% a tag test, jumping to the next case if it fails
% the goal for that case
% code to move variables to where the store map says they
% ought to be
% a branch to the end of the switch.
%
% For the last case, if the switch covers all cases that can occur,
% we don't need to generate the tag test, and we never need to
% generate the branch to the end of the switch.
%
% After the last case, we put the end-of-switch label which other
% cases branch to after their case goals.
%
% In the important special case of a det switch with two cases,
% we try to find out which case will be executed more frequently,
% and put that one first. This minimizes the number of pipeline
% breaks caused by taken branches.
:- pred switch_gen__generate_all_cases(list(extended_case)::in, prog_var::in,
code_model::in, can_fail::in, hlds_goal_info::in, label::in,
branch_end::in, branch_end::out, code_tree::out,
code_info::in, code_info::out) is det.
switch_gen__generate_all_cases(Cases0, Var, CodeModel, CanFail, GoalInfo,
EndLabel, !MaybeEnd, Code, !CI) :-
code_info__produce_variable(Var, VarCode, _Rval, !CI),
(
CodeModel = model_det,
CanFail = cannot_fail,
Cases0 = [Case1, Case2],
Case1 = case(_, _, _, Goal1),
Case2 = case(_, _, _, Goal2)
->
code_info__get_pred_id(!.CI, PredId),
code_info__get_proc_id(!.CI, ProcId),
count_recursive_calls(Goal1, PredId, ProcId, Min1, Max1),
count_recursive_calls(Goal2, PredId, ProcId, Min2, Max2),
(
Max1 = 0, % Goal1 is a base case
Min2 = 1 % Goal2 is probably singly recursive
->
Cases = [Case2, Case1]
;
Max2 = 0, % Goal2 is a base case
Min1 > 1 % Goal1 is at least doubly recursive
->
Cases = [Case2, Case1]
;
Cases = Cases0
)
;
Cases = Cases0
),
switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
GoalInfo, EndLabel, !MaybeEnd, CasesCode, !CI),
Code = tree(VarCode, CasesCode).
:- pred switch_gen__generate_cases(list(extended_case)::in, prog_var::in,
code_model::in, can_fail::in, hlds_goal_info::in, label::in,
branch_end::in, branch_end::out, code_tree::out,
code_info::in, code_info::out) is det.
% At the end of a locally semidet switch, we fail because we
% came across a tag which was not covered by one of the cases.
% It is followed by the end of switch label to which the cases
% branch.
switch_gen__generate_cases([], _Var, _CodeModel, CanFail, _GoalInfo,
EndLabel, !MaybeEnd, Code, !CI) :-
( CanFail = can_fail ->
code_info__generate_failure(FailCode, !CI)
;
FailCode = empty
),
EndCode = node([
label(EndLabel) -
"end of switch"
]),
Code = tree(FailCode, EndCode).
switch_gen__generate_cases([case(_, _, Cons, Goal) | Cases], Var, CodeModel,
CanFail, SwitchGoalInfo, EndLabel, !MaybeEnd, CasesCode,
!CI) :-
code_info__remember_position(!.CI, BranchStart),
goal_info_get_store_map(SwitchGoalInfo, StoreMap),
(
( Cases = [_|_] ; CanFail = can_fail )
->
unify_gen__generate_tag_test(Var, Cons, branch_on_failure,
NextLabel, TestCode, !CI),
trace__maybe_generate_internal_event_code(Goal, SwitchGoalInfo,
TraceCode, !CI),
code_gen__generate_goal(CodeModel, Goal, GoalCode, !CI),
code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode,
!CI),
ElseCode = node([
goto(label(EndLabel)) -
"skip to the end of the switch",
label(NextLabel) -
"next case"
]),
ThisCaseCode =
tree(TestCode,
tree(TraceCode,
tree(GoalCode,
tree(SaveCode,
ElseCode))))
;
trace__maybe_generate_internal_event_code(Goal, SwitchGoalInfo,
TraceCode, !CI),
code_gen__generate_goal(CodeModel, Goal, GoalCode, !CI),
code_info__generate_branch_end(StoreMap, !MaybeEnd, SaveCode,
!CI),
ThisCaseCode =
tree(TraceCode,
tree(GoalCode,
SaveCode))
),
code_info__reset_to_position(BranchStart, !CI),
% generate the rest of the cases.
switch_gen__generate_cases(Cases, Var, CodeModel, CanFail,
SwitchGoalInfo, EndLabel, !MaybeEnd, OtherCasesCode, !CI),
CasesCode = tree(ThisCaseCode, OtherCasesCode).
%------------------------------------------------------------------------------%