mirror of
https://github.com/Mercury-Language/mercury.git
synced 2025-12-20 16:31:04 +00:00
Estimated hours taken: 220
Aditi update syntax, type and mode checking.
Change the hlds_goal for constructions in preparation for
structure reuse to avoid making multiple conflicting changes.
compiler/hlds_goal.m:
Merge `higher_order_call' and `class_method_call' into a single
`generic_call' goal type. This also has alternatives for the
various Aditi builtins for which type declarations can't
be written.
Remove the argument types field from higher-order/class method calls.
It wasn't used often, and wasn't updated by optimizations
such as inlining. The types can be obtained from the vartypes
field of the proc_info.
Add a `lambda_eval_method' field to lambda_goals.
Add a field to constructions to identify which RL code fragment should
be used for an top-down Aditi closure.
Add fields to constructions to hold structure reuse information.
This is currently ignored -- the changes to implement structure
reuse will be committed to the alias branch.
This is included here to avoid lots of CVS conflicts caused by
changing the definition of `hlds_goal' twice.
Add a field to `some' goals to specify whether the quantification
can be removed. This is used to make it easier to ensure that
indexes are used for updates.
Add a field to lambda_goals to describe whether the modes were
guessed by the compiler and may need fixing up after typechecking
works out the argument types.
Add predicate `hlds_goal__generic_call_id' to work out a call_id
for a generic call for use in error messages.
compiler/purity.m:
compiler/post_typecheck.m:
Fill in the modes of Aditi builtin calls and closure constructions.
This needs to know which are the `aditi__state' arguments, so
it must be done after typechecking.
compiler/prog_data.m:
Added `:- type sym_name_and_arity ---> sym_name/arity'.
Add a type `lambda_eval_method', which describes how a closure
is to be executed. The alternatives are normal Mercury execution,
bottom-up execution by Aditi and top-down execution by Aditi.
compiler/prog_out.m:
Add predicate `prog_out__write_sym_name_and_arity', which
replaces duplicated inline code in a few places.
compiler/hlds_data.m:
Add a `lambda_eval_method' field to `pred_const' cons_ids and
`pred_closure_tag' cons_tags.
compiler/hlds_pred.m:
Remove type `pred_call_id', replace it with type `simple_call_id',
which combines a `pred_or_func' and a `sym_name_and_arity'.
Add a type `call_id' which describes all the different types of call,
including normal calls, higher-order and class-method calls
and Aditi builtins.
Add `aditi_top_down' to the type `marker'.
Remove `aditi_interface' from type `marker'. Interfacing to
Aditi predicates is now handled by `generic_call' hlds_goals.
Add a type `rl_exprn_id' which identifies a predicate to
be executed top-down by Aditi.
Add a `maybe(rl_exprn_id)' field to type `proc_info'.
Add predicate `adjust_func_arity' to convert between the arity
of a function to its arity as a predicate.
Add predicates `get_state_args' and `get_state_args_det' to
extract the DCG state arguments from an argument list.
Add predicate `pred_info_get_call_id' to get a `simple_call_id'
for a predicate for use in error messages.
compiler/hlds_out.m:
Write the new representation for call_ids.
Add a predicate `hlds_out__write_call_arg_id' which
replaces similar code in mode_errors.m and typecheck.m.
compiler/prog_io_goal.m:
Add support for `aditi_bottom_up' and `aditi_top_down' annotations
on pred expressions.
compiler/prog_io_util.m:
compiler/prog_io_pragma.m:
Add predicates
- `prog_io_util:parse_name_and_arity' to parse `SymName/Arity'
(moved from prog_io_pragma.m).
- `prog_io_util:parse_pred_or_func_name_and_arity to parse
`pred SymName/Arity' or `func SymName/Arity'.
- `prog_io_util:parse_pred_or_func_and_args' to parse terms resembling
a clause head (moved from prog_io_pragma.m).
compiler/type_util.m:
Add support for `aditi_bottom_up' and `aditi_top_down' annotations
on higher-order types.
Add predicates `construct_higher_order_type',
`construct_higher_order_pred_type' and
`construct_higher_order_func_type' to avoid some code duplication.
compiler/mode_util.m:
Add predicate `unused_mode/1', which returns `builtin:unused'.
Add functions `aditi_di_mode/0', `aditi_ui_mode/0' and
`aditi_uo_mode/0' which return `in', `in', and `out', but will
be changed to return `di', `ui' and `uo' when alias tracking
is implemented.
compiler/goal_util.m:
Add predicate `goal_util__generic_call_vars' which returns
any arguments to a generic_call which are not in the argument list,
for example the closure passed to a higher-order call or
the typeclass_info for a class method call.
compiler/llds.m:
compiler/exprn_aux.m:
compiler/dupelim.m:
compiler/llds_out.m:
compiler/opt_debug.m:
Add builtin labels for the Aditi update operations.
compiler/hlds_module.m:
Add predicate predicate_table_search_pf_sym, used for finding
possible matches for a call with the wrong number of arguments.
compiler/intermod.m:
Don't write predicates which build `aditi_top_down' goals,
because there is currently no way to tell importing modules
which RL code fragment to use.
compiler/simplify.m:
Obey the `cannot_remove' field of explicit quantification goals.
compiler/make_hlds.m:
Parse Aditi updates.
Don't typecheck clauses for which syntax errors in Aditi updates
are found - this avoids spurious "undefined predicate `aditi_insert/3'"
errors.
Factor out some common code to handle terms of the form `Head :- Body'.
Factor out common code in the handling of pred and func expressions.
compiler/typecheck.m:
Typecheck Aditi builtins.
Allow the argument types of matching predicates to be adjusted
when typechecking the higher-order arguments of Aditi builtins.
Change `typecheck__resolve_pred_overloading' to take a list of
argument types rather than a `map(var, type)' and a list of
arguments to allow a transformation to be performed on the
argument types before passing them.
compiler/error_util.m:
Move the part of `report_error_num_args' which writes
"wrong number of arguments (<x>; expected <y>)" from
typecheck.m for use by make_hlds.m when reporting errors
for Aditi builtins.
compiler/modes.m:
compiler/unique_modes.m:
compiler/modecheck_call.m:
Modecheck Aditi builtins.
compiler/lambda.m:
Handle the markers for predicates introduced for
`aditi_top_down' and `aditi_bottom_up' lambda expressions.
compiler/polymorphism.m:
Add extra type_infos to `aditi_insert' calls
describing the tuple to insert.
compiler/call_gen.m:
Generate code for Aditi builtins.
compiler/unify_gen.m:
compiler/bytecode_gen.m:
Abort on `aditi_top_down' and `aditi_bottom_up' lambda
expressions - code generation for them is not yet implemented.
compiler/magic.m:
Use the `aditi_call' generic_call rather than create
a new procedure for each Aditi predicate called from C.
compiler/rl_out.pp:
compiler/rl_gen.m:
compiler/rl.m:
Move some utility code used by magic.m and call_gen.m into rl.m.
Remove an XXX comment about reference counting being not yet
implemented - Evan has fixed that.
library/ops.m:
compiler/mercury_to_mercury.m:
doc/transition_guide.texi:
Add unary prefix operators `aditi_bottom_up' and `aditi_top_down',
used as qualifiers on lambda expressions.
Add infix operator `==>' to separate the tuples in an
`aditi_modify' call.
compiler/follow_vars.m:
Thread a `map(prog_var, type)' through, needed because
type information is no longer held in higher-order call goals.
compiler/table_gen.m:
Use the `make_*_construction' predicates in hlds_goal.m
to construct constants.
compiler/*.m:
Trivial changes to add extra fields to hlds_goal structures.
doc/reference_manual.texi:
Document Aditi updates.
Use @samp{pragma base_relation} instead of
@samp{:- pragma base_relation} throughout the Aditi documentation
to be consistent with other parts of the reference manual.
tests/valid/Mmakefile:
tests/valid/aditi_update.m:
tests/valid/aditi.m:
Test case.
tests/valid/Mmakefile:
Remove some hard-coded --intermodule-optimization rules which are
no longer needed because `mmake depend' is now run in this directory.
tests/invalid/*.err_exp:
Fix expected output for changes in reporting of call_ids
in typecheck.m.
tests/invalid/Mmakefile
tests/invalid/aditi_update_errors.{m,err_exp}:
tests/invalid/aditi_update_mode_errors.{m,err_exp}:
Test error messages for Aditi updates.
tests/valid/aditi.m:
tests/invalid/aditi.m:
Cut down version of extras/aditi/aditi.m to provide basic declarations
for Aditi compilation such as `aditi__state' and the modes
`aditi_di', `aditi_uo' and `aditi_ui'. Installing extras/aditi/aditi.m
somewhere would remove the need for these.
667 lines
24 KiB
Mathematica
667 lines
24 KiB
Mathematica
%---------------------------------------------------------------------------%
|
|
% Copyright (C) 1995-1999 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.
|
|
%---------------------------------------------------------------------------%
|
|
%
|
|
% Original author: squirrel (Jane Anna Langley).
|
|
% Some bugs fixed by fjh.
|
|
% Extensive revision by zs.
|
|
% More revision by stayl.
|
|
%
|
|
% This module attempts to optimise out instances where a variable is
|
|
% decomposed and then soon after reconstructed from the parts. If possible
|
|
% we would like to "short-circuit" this process.
|
|
% It also optimizes deconstructions of known cells, replacing them with
|
|
% assignments to the arguments where this is guaranteed to not increase
|
|
% the number of stack slots required by the goal.
|
|
% Repeated calls to predicates with the same input arguments are replaced by
|
|
% assigments and warnings are returned.
|
|
%
|
|
% IMPORTANT: This module does a small subset of the job of compile-time
|
|
% garbage collection, but it does so without paying attention to uniqueness
|
|
% information, since the compiler does not yet have such information.
|
|
% Once we implement ctgc, the assumptions made by this module will have
|
|
% to be revisited.
|
|
%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- module common.
|
|
:- interface.
|
|
|
|
:- import_module hlds_pred, hlds_goal, prog_data, simplify.
|
|
:- import_module list.
|
|
|
|
% If we find a deconstruction or a construction we cannot optimize,
|
|
% record the details of the memory cell in CommonInfo.
|
|
|
|
% If we find a construction that constructs a cell identical to one
|
|
% we have seen before, replace the construction with an assignment
|
|
% from the variable unified with that cell.
|
|
|
|
:- pred common__optimise_unification(unification, prog_var, unify_rhs,
|
|
unify_mode, unify_context, hlds_goal_expr, hlds_goal_info,
|
|
hlds_goal_expr, hlds_goal_info, simplify_info, simplify_info).
|
|
:- mode common__optimise_unification(in, in, in, in, in, in, in,
|
|
out, out, in, out) is det.
|
|
|
|
% Check whether this call has been seen before and is replaceable, if
|
|
% so produce assignment unification for the non-local output variables,
|
|
% and give a warning.
|
|
% A call is replaceable if it has no uniquely moded outputs and no
|
|
% destructive inputs.
|
|
|
|
:- pred common__optimise_call(pred_id, proc_id, list(prog_var), hlds_goal_expr,
|
|
hlds_goal_info, hlds_goal_expr, simplify_info, simplify_info).
|
|
:- mode common__optimise_call(in, in, in, in, in, out, in, out) is det.
|
|
|
|
:- pred common__optimise_higher_order_call(prog_var, list(prog_var), list(mode),
|
|
determinism, hlds_goal_expr, hlds_goal_info, hlds_goal_expr,
|
|
simplify_info, simplify_info).
|
|
:- mode common__optimise_higher_order_call(in, in, in, in, in, in, out,
|
|
in, out) is det.
|
|
|
|
% succeeds if the two variables are equivalent
|
|
% according to the specified equivalence class.
|
|
:- pred common__vars_are_equivalent(prog_var, prog_var, common_info).
|
|
:- mode common__vars_are_equivalent(in, in, in) is semidet.
|
|
|
|
% Assorted stuff used here that simplify.m doesn't need to know about.
|
|
:- type common_info.
|
|
|
|
:- pred common_info_init(common_info).
|
|
:- mode common_info_init(out) is det.
|
|
|
|
:- pred common_info_clear_structs(common_info, common_info).
|
|
:- mode common_info_clear_structs(in, out) is det.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- implementation.
|
|
|
|
:- import_module quantification, mode_util, type_util, prog_util.
|
|
:- import_module det_util, det_report, globals, options, inst_match, instmap.
|
|
:- import_module hlds_data, hlds_module, (inst), pd_cost, term.
|
|
:- import_module bool, map, set, eqvclass, require, std_util, string.
|
|
|
|
:- type structure
|
|
---> structure(prog_var, type, cons_id, list(prog_var)).
|
|
|
|
:- type call_args
|
|
---> call_args(prog_context, list(prog_var), list(prog_var)).
|
|
% input, output args. For higher-order calls,
|
|
% the closure is the first input argument.
|
|
|
|
:- type struct_map == map(cons_id, list(structure)).
|
|
:- type seen_calls == map(seen_call_id, list(call_args)).
|
|
|
|
:- type common_info
|
|
---> common(
|
|
eqvclass(prog_var),
|
|
struct_map, % all structs seen.
|
|
struct_map, % structs seen since the last call.
|
|
seen_calls
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
common_info_init(CommonInfo) :-
|
|
eqvclass__init(VarEqv0),
|
|
map__init(StructMap0),
|
|
map__init(SeenCalls0),
|
|
CommonInfo = common(VarEqv0, StructMap0, StructMap0, SeenCalls0).
|
|
|
|
% Clear structs seen since the last call. Replacing deconstructions
|
|
% of these structs with assignments after the call would cause an
|
|
% increase in the number of stack slots required.
|
|
common_info_clear_structs(common(VarEqv, StructMap, _, SeenCalls),
|
|
common(VarEqv, StructMap, Empty, SeenCalls)) :-
|
|
map__init(Empty).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
common__optimise_unification(Unification0, _Left0, _Right0, Mode, _Context,
|
|
Goal0, GoalInfo0, Goal, GoalInfo, Info0, Info) :-
|
|
(
|
|
Unification0 = construct(Var, ConsId, ArgVars, _, _, _, _),
|
|
(
|
|
% common__generate_assign assumes that the
|
|
% output variable is in the instmap_delta, which
|
|
% will not be true if the variable is a local.
|
|
% The optimization is pointless in that case.
|
|
goal_info_get_instmap_delta(GoalInfo0, InstMapDelta),
|
|
instmap_delta_search_var(InstMapDelta, Var, _),
|
|
common__find_matching_cell(Var, ConsId, ArgVars,
|
|
construction, Info0, OldStruct)
|
|
->
|
|
OldStruct = structure(OldVar, _, _, _),
|
|
common__generate_assign(Var, OldVar, GoalInfo0,
|
|
Goal - GoalInfo, Info0, Info1),
|
|
simplify_info_set_requantify(Info1, Info2),
|
|
pd_cost__goal(Goal0 - GoalInfo0, Cost),
|
|
simplify_info_incr_cost_delta(Info2, Cost, Info)
|
|
;
|
|
Goal = Goal0,
|
|
GoalInfo = GoalInfo0,
|
|
common__record_cell(Var, ConsId, ArgVars, Info0, Info)
|
|
)
|
|
;
|
|
Unification0 = deconstruct(Var, ConsId, ArgVars, _, _),
|
|
(
|
|
simplify_info_get_module_info(Info0, ModuleInfo),
|
|
Mode = LVarMode - _,
|
|
mode_get_insts(ModuleInfo, LVarMode, Inst0, Inst1),
|
|
% Don't optimise away partially instantiated
|
|
% deconstruction unifications.
|
|
inst_matches_binding(Inst0, Inst1, ModuleInfo),
|
|
common__find_matching_cell(Var, ConsId, ArgVars,
|
|
deconstruction, Info0, OldStruct)
|
|
->
|
|
OldStruct = structure(_, _, _, OldArgVars),
|
|
common__create_output_unifications(GoalInfo0, ArgVars,
|
|
OldArgVars, Goals, Info0, Info1),
|
|
simplify_info_set_requantify(Info1, Info2),
|
|
Goal = conj(Goals),
|
|
pd_cost__goal(Goal0 - GoalInfo0, Cost),
|
|
simplify_info_incr_cost_delta(Info2, Cost, Info)
|
|
;
|
|
Goal = Goal0,
|
|
common__record_cell(Var, ConsId, ArgVars, Info0, Info)
|
|
),
|
|
GoalInfo = GoalInfo0
|
|
;
|
|
Unification0 = assign(Var1, Var2),
|
|
Goal = Goal0,
|
|
common__record_equivalence(Var1, Var2, Info0, Info),
|
|
GoalInfo = GoalInfo0
|
|
;
|
|
Unification0 = simple_test(Var1, Var2),
|
|
Goal = Goal0,
|
|
common__record_equivalence(Var1, Var2, Info0, Info),
|
|
GoalInfo = GoalInfo0
|
|
;
|
|
Unification0 = complicated_unify(_, _, _),
|
|
Goal = Goal0,
|
|
Info = Info0,
|
|
GoalInfo = GoalInfo0
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- type unification_type
|
|
---> deconstruction
|
|
; construction.
|
|
|
|
:- pred common__find_matching_cell(prog_var, cons_id,
|
|
list(prog_var), unification_type, simplify_info, structure).
|
|
:- mode common__find_matching_cell(in, in, in, in, in, out) is semidet.
|
|
|
|
common__find_matching_cell(Var, ConsId, ArgVars, UniType, Info, OldStruct) :-
|
|
simplify_info_get_common_info(Info, CommonInfo),
|
|
simplify_info_get_var_types(Info, VarTypes),
|
|
CommonInfo = common(VarEqv, StructMapAll, StructMapSinceLastFlush, _),
|
|
(
|
|
UniType = construction,
|
|
StructMapToUse = StructMapAll
|
|
;
|
|
% For deconstructions, using the arguments of a cell
|
|
% created before the last stack flush would cause more
|
|
% variables to be saved on the stack.
|
|
UniType = deconstruction,
|
|
StructMapToUse = StructMapSinceLastFlush
|
|
),
|
|
map__search(StructMapToUse, ConsId, Structs),
|
|
common__find_matching_cell_2(Structs, Var, ConsId, ArgVars, UniType,
|
|
VarEqv, VarTypes, OldStruct).
|
|
|
|
:- pred common__find_matching_cell_2(list(structure), prog_var, cons_id,
|
|
list(prog_var),
|
|
unification_type, eqvclass(prog_var), map(prog_var, type), structure).
|
|
:- mode common__find_matching_cell_2(in, in, in, in, in,
|
|
in, in, out) is semidet.
|
|
|
|
common__find_matching_cell_2([Struct | Structs], Var, ConsId, ArgVars,
|
|
UniType, VarEqv, VarTypes, OldStruct) :-
|
|
Struct = structure(OldVar, StructType, StructConsId, StructArgVars),
|
|
(
|
|
% Are the arguments the same (or equivalent) variables?
|
|
ConsId = StructConsId,
|
|
(
|
|
UniType = construction,
|
|
common__var_lists_are_equiv(ArgVars,
|
|
StructArgVars, VarEqv),
|
|
|
|
% Two structures of the same shape may have different
|
|
% types and therefore different representations.
|
|
map__lookup(VarTypes, Var, VarType),
|
|
common__compatible_types(VarType, StructType)
|
|
;
|
|
UniType = deconstruction,
|
|
common__vars_are_equiv(Var, OldVar, VarEqv)
|
|
)
|
|
->
|
|
OldStruct = Struct
|
|
;
|
|
common__find_matching_cell_2(Structs, Var, ConsId, ArgVars,
|
|
UniType, VarEqv, VarTypes, OldStruct)
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% Two structures have compatible representations if the top
|
|
% level of their types are unifiable. % For example, if we have
|
|
%
|
|
% :- type maybe_err(T) --> ok(T) ; err(string).
|
|
%
|
|
% :- pred p(maybe_err(foo)::in, maybe_err(bar)::out) is semidet.
|
|
% p(err(X), err(X)).
|
|
%
|
|
% then we want to reuse the `err(X)' in the first arg rather than
|
|
% constructing a new copy of it for the second arg.
|
|
% The two occurrences of `err(X)' have types `maybe_err(int)'
|
|
% and `maybe(float)', but we know that they have the same
|
|
% representation.
|
|
|
|
:- pred common__compatible_types(type, type).
|
|
:- mode common__compatible_types(in, in) is semidet.
|
|
|
|
common__compatible_types(Type1, Type2) :-
|
|
type_to_type_id(Type1, TypeId1, _),
|
|
type_to_type_id(Type2, TypeId2, _),
|
|
TypeId1 = TypeId2.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% succeeds if the two lists of variables are equivalent
|
|
% according to the specified equivalence class.
|
|
:- pred common__var_lists_are_equiv(list(prog_var), list(prog_var),
|
|
eqvclass(prog_var)).
|
|
:- mode common__var_lists_are_equiv(in, in, in) is semidet.
|
|
|
|
common__var_lists_are_equiv([], [], _VarEqv).
|
|
common__var_lists_are_equiv([X | Xs], [Y | Ys], VarEqv) :-
|
|
common__vars_are_equiv(X, Y, VarEqv),
|
|
common__var_lists_are_equiv(Xs, Ys, VarEqv).
|
|
|
|
common__vars_are_equivalent(X, Y, CommonInfo) :-
|
|
CommonInfo = common(EqvVars, _, _, _),
|
|
common__vars_are_equiv(X, Y, EqvVars).
|
|
|
|
% succeeds if the two variables are equivalent
|
|
% according to the specified equivalence class.
|
|
:- pred common__vars_are_equiv(prog_var, prog_var, eqvclass(prog_var)).
|
|
:- mode common__vars_are_equiv(in, in, in) is semidet.
|
|
|
|
common__vars_are_equiv(X, Y, VarEqv) :-
|
|
% write('looking for equivalence of '),
|
|
% write(X),
|
|
% write(' and '),
|
|
% write(Y),
|
|
% nl,
|
|
(
|
|
X = Y
|
|
;
|
|
eqvclass__is_member(VarEqv, X),
|
|
eqvclass__is_member(VarEqv, Y),
|
|
eqvclass__same_eqvclass(VarEqv, X, Y)
|
|
).
|
|
% write('they are equivalent'),
|
|
% nl.
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred common__record_cell(prog_var, cons_id, list(prog_var),
|
|
simplify_info, simplify_info).
|
|
:- mode common__record_cell(in, in, in, in, out) is det.
|
|
|
|
common__record_cell(Var, ConsId, ArgVars, Info0, Info) :-
|
|
simplify_info_get_common_info(Info0, CommonInfo0),
|
|
simplify_info_get_var_types(Info0, VarTypes),
|
|
( ArgVars = [] ->
|
|
% Constants do not have memory cells to reuse,
|
|
% at least in the memory models we are interested in.
|
|
CommonInfo = CommonInfo0
|
|
;
|
|
CommonInfo0 = common(VarEqv, StructMapAll0,
|
|
StructMapLastCall0, SeenCalls),
|
|
map__lookup(VarTypes, Var, VarType),
|
|
Struct = structure(Var, VarType, ConsId, ArgVars),
|
|
common__do_record_cell(StructMapAll0, ConsId,
|
|
Struct, StructMapAll),
|
|
common__do_record_cell(StructMapLastCall0, ConsId, Struct,
|
|
StructMapLastCall),
|
|
CommonInfo = common(VarEqv, StructMapAll,
|
|
StructMapLastCall, SeenCalls)
|
|
),
|
|
simplify_info_set_common_info(Info0, CommonInfo, Info).
|
|
|
|
:- pred common__do_record_cell(struct_map, cons_id, structure, struct_map).
|
|
:- mode common__do_record_cell(in, in, in, out) is det.
|
|
|
|
common__do_record_cell(StructMap0, ConsId, Struct, StructMap) :-
|
|
( map__search(StructMap0, ConsId, StructList0Prime) ->
|
|
StructList0 = StructList0Prime
|
|
;
|
|
StructList0 = []
|
|
),
|
|
|
|
% Insert the new cell at the front of the list. If it hides
|
|
% an equivalent cell, at least the reuse of this cell will
|
|
% require saving its address over fewer calls.
|
|
|
|
StructList = [Struct | StructList0],
|
|
map__set(StructMap0, ConsId, StructList, StructMap).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred common__record_equivalence(prog_var, prog_var,
|
|
simplify_info, simplify_info).
|
|
:- mode common__record_equivalence(in, in, in, out) is det.
|
|
|
|
common__record_equivalence(Var1, Var2, Info0, Info) :-
|
|
simplify_info_get_common_info(Info0, CommonInfo0),
|
|
CommonInfo0 = common(VarEqv0, StructMap0, StructMap1, SeenCalls),
|
|
% write('ensuring equivalence of '),
|
|
% write(Var1),
|
|
% write(' and '),
|
|
% write(Var2),
|
|
% nl,
|
|
eqvclass__ensure_equivalence(VarEqv0, Var1, Var2, VarEqv),
|
|
CommonInfo = common(VarEqv, StructMap0, StructMap1, SeenCalls),
|
|
simplify_info_set_common_info(Info0, CommonInfo, Info).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
%---------------------------------------------------------------------------%
|
|
|
|
common__optimise_call(PredId, ProcId, Args, Goal0,
|
|
GoalInfo, Goal, Info0, Info) :-
|
|
(
|
|
goal_info_get_determinism(GoalInfo, Det),
|
|
common__check_call_detism(Det),
|
|
simplify_info_get_module_info(Info0, ModuleInfo),
|
|
module_info_pred_proc_info(ModuleInfo, PredId,
|
|
ProcId, _, ProcInfo),
|
|
proc_info_argmodes(ProcInfo, ArgModes),
|
|
common__partition_call_args(ModuleInfo, ArgModes, Args,
|
|
InputArgs, OutputArgs)
|
|
->
|
|
common__optimise_call_2(seen_call(PredId, ProcId), InputArgs,
|
|
OutputArgs, Goal0, GoalInfo, Goal, Info0, Info)
|
|
;
|
|
Goal = Goal0,
|
|
Info = Info0
|
|
).
|
|
|
|
common__optimise_higher_order_call(Closure, Args, Modes, Det, Goal0,
|
|
GoalInfo, Goal, Info0, Info) :-
|
|
(
|
|
common__check_call_detism(Det),
|
|
simplify_info_get_module_info(Info0, ModuleInfo),
|
|
common__partition_call_args(ModuleInfo, Modes, Args,
|
|
InputArgs, OutputArgs)
|
|
->
|
|
common__optimise_call_2(higher_order_call,
|
|
[Closure | InputArgs], OutputArgs, Goal0,
|
|
GoalInfo, Goal, Info0, Info)
|
|
;
|
|
Goal = Goal0,
|
|
Info = Info0
|
|
).
|
|
|
|
:- pred common__check_call_detism(determinism::in) is semidet.
|
|
|
|
common__check_call_detism(Det) :-
|
|
determinism_components(Det, _, SolnCount),
|
|
% Replacing nondet or mulidet calls would cause
|
|
% loss of solutions.
|
|
( SolnCount = at_most_one
|
|
; SolnCount = at_most_many_cc
|
|
).
|
|
|
|
:- pred common__optimise_call_2(seen_call_id, list(prog_var), list(prog_var),
|
|
hlds_goal_expr, hlds_goal_info, hlds_goal_expr,
|
|
simplify_info, simplify_info).
|
|
:- mode common__optimise_call_2(in, in, in, in, in, out, in, out) is det.
|
|
|
|
common__optimise_call_2(SeenCall, InputArgs, OutputArgs, Goal0,
|
|
GoalInfo, Goal, Info0, Info) :-
|
|
simplify_info_get_common_info(Info0, CommonInfo0),
|
|
CommonInfo0 = common(Eqv0, Structs0, Structs1, SeenCalls0),
|
|
(
|
|
map__search(SeenCalls0, SeenCall, SeenCallsList0)
|
|
->
|
|
( common__find_previous_call(SeenCallsList0, InputArgs,
|
|
Eqv0, OutputArgs2, PrevContext)
|
|
->
|
|
common__create_output_unifications(GoalInfo,
|
|
OutputArgs, OutputArgs2, Goals, Info0, Info1),
|
|
Goal = conj(Goals),
|
|
simplify_info_get_var_types(Info0, VarTypes),
|
|
(
|
|
simplify_do_warn_calls(Info1),
|
|
% Don't warn for cases such as:
|
|
% set__init(Set1 : set(int)),
|
|
% set__init(Set2 : set(float)).
|
|
map__apply_to_list(OutputArgs, VarTypes,
|
|
OutputArgTypes1),
|
|
map__apply_to_list(OutputArgs2, VarTypes,
|
|
OutputArgTypes2),
|
|
common__types_match_exactly_list(OutputArgTypes1,
|
|
OutputArgTypes2)
|
|
->
|
|
goal_info_get_context(GoalInfo, Context),
|
|
simplify_info_do_add_msg(Info1,
|
|
duplicate_call(SeenCall, PrevContext,
|
|
Context),
|
|
Info2)
|
|
;
|
|
Info2 = Info1
|
|
),
|
|
CommonInfo = common(Eqv0, Structs0,
|
|
Structs1, SeenCalls0),
|
|
pd_cost__goal(Goal0 - GoalInfo, Cost),
|
|
simplify_info_incr_cost_delta(Info2, Cost, Info3),
|
|
simplify_info_set_requantify(Info3, Info4)
|
|
;
|
|
goal_info_get_context(GoalInfo, Context),
|
|
ThisCall = call_args(Context, InputArgs, OutputArgs),
|
|
map__det_update(SeenCalls0, SeenCall,
|
|
[ThisCall | SeenCallsList0], SeenCalls),
|
|
CommonInfo = common(Eqv0, Structs0,
|
|
Structs1, SeenCalls),
|
|
Goal = Goal0,
|
|
Info4 = Info0
|
|
)
|
|
;
|
|
goal_info_get_context(GoalInfo, Context),
|
|
ThisCall = call_args(Context, InputArgs, OutputArgs),
|
|
map__det_insert(SeenCalls0, SeenCall, [ThisCall], SeenCalls),
|
|
CommonInfo = common(Eqv0, Structs0, Structs1, SeenCalls),
|
|
Goal = Goal0,
|
|
Info4 = Info0
|
|
),
|
|
simplify_info_set_common_info(Info4, CommonInfo, Info).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
% Partition the arguments of a call into inputs and outputs,
|
|
% failing if any of the outputs have a unique component
|
|
% or if any of the outputs contain any `any' insts.
|
|
:- pred common__partition_call_args(module_info::in, list(mode)::in,
|
|
list(prog_var)::in, list(prog_var)::out,
|
|
list(prog_var)::out) is semidet.
|
|
|
|
common__partition_call_args(_, [], [_ | _], _, _) :-
|
|
error("common__partition_call_args").
|
|
common__partition_call_args(_, [_ | _], [], _, _) :-
|
|
error("common__partition_call_args").
|
|
common__partition_call_args(_, [], [], [], []).
|
|
common__partition_call_args(ModuleInfo, [ArgMode | ArgModes], [Arg | Args],
|
|
InputArgs, OutputArgs) :-
|
|
common__partition_call_args(ModuleInfo, ArgModes, Args,
|
|
InputArgs1, OutputArgs1),
|
|
mode_get_insts(ModuleInfo, ArgMode, InitialInst, FinalInst),
|
|
( inst_matches_binding(InitialInst, FinalInst, ModuleInfo) ->
|
|
InputArgs = [Arg | InputArgs1],
|
|
OutputArgs = OutputArgs1
|
|
;
|
|
% Calls with partly unique outputs cannot be replaced,
|
|
% since a unique copy of the outputs must be produced.
|
|
inst_is_not_partly_unique(ModuleInfo, FinalInst),
|
|
|
|
% Don't optimize calls whose outputs include any
|
|
% `any' insts, since that would create false aliasing
|
|
% between the different variables.
|
|
% (inst_matches_binding applied to identical insts
|
|
% fails only for `any' insts.)
|
|
inst_matches_binding(FinalInst, FinalInst, ModuleInfo),
|
|
|
|
% Don't optimize calls where a partially instantiated
|
|
% variable is further instantiated (XXX why not???).
|
|
inst_is_free(ModuleInfo, InitialInst),
|
|
|
|
InputArgs = InputArgs1,
|
|
OutputArgs = [Arg | OutputArgs1]
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred common__find_previous_call(list(call_args)::in, list(prog_var)::in,
|
|
eqvclass(prog_var)::in, list(prog_var)::out,
|
|
prog_context::out) is semidet.
|
|
|
|
common__find_previous_call([SeenCall | SeenCalls], InputArgs,
|
|
Eqv, OutputArgs2, PrevContext) :-
|
|
SeenCall = call_args(PrevContext, InputArgs1, OutputArgs1),
|
|
( common__var_lists_are_equiv(InputArgs, InputArgs1, Eqv) ->
|
|
OutputArgs2 = OutputArgs1
|
|
;
|
|
common__find_previous_call(SeenCalls, InputArgs, Eqv,
|
|
OutputArgs2, PrevContext)
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred common__create_output_unifications(hlds_goal_info::in,
|
|
list(prog_var)::in, list(prog_var)::in, list(hlds_goal)::out,
|
|
simplify_info::in, simplify_info::out) is det.
|
|
|
|
% Create unifications to assign the non-local vars in OutputArgs from
|
|
% the corresponding var in OutputArgs2.
|
|
common__create_output_unifications(_, [], [], [], Info, Info).
|
|
common__create_output_unifications(_, [_ | _], [], _, _, _) :-
|
|
error("common__create_output_unifications").
|
|
common__create_output_unifications(_, [], [_ | _], _, _, _) :-
|
|
error("common__create_output_unifications").
|
|
common__create_output_unifications(GoalInfo, [OutputArg | OutputArgs],
|
|
[OutputArg2 | OutputArgs2], Goals, Info0, Info) :-
|
|
goal_info_get_nonlocals(GoalInfo, NonLocals),
|
|
(
|
|
set__member(OutputArg, NonLocals),
|
|
% This can happen if the first cell was created
|
|
% with a partially instantiated deconstruction.
|
|
OutputArg \= OutputArg2
|
|
->
|
|
common__generate_assign(OutputArg, OutputArg2,
|
|
GoalInfo, Goal, Info0, Info1),
|
|
common__create_output_unifications(GoalInfo,
|
|
OutputArgs, OutputArgs2, Goals1, Info1, Info),
|
|
Goals = [Goal | Goals1]
|
|
;
|
|
common__create_output_unifications(GoalInfo,
|
|
OutputArgs, OutputArgs2, Goals, Info0, Info)
|
|
).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
|
|
:- pred common__generate_assign(prog_var, prog_var, hlds_goal_info, hlds_goal,
|
|
simplify_info, simplify_info).
|
|
:- mode common__generate_assign(in, in, in, out, in, out) is det.
|
|
|
|
common__generate_assign(ToVar, FromVar, GoalInfo0, Goal, Info0, Info) :-
|
|
simplify_info_get_instmap(Info0, InstMap),
|
|
instmap__lookup_var(InstMap, FromVar, FromVarInst0),
|
|
|
|
( FromVarInst0 = free ->
|
|
% This may mean that the variable was local
|
|
% to the first unification or call. In that
|
|
% case we need to recompute the instmap_deltas
|
|
% for atomic goals.
|
|
simplify_info_set_recompute_atomic(Info0, Info1)
|
|
;
|
|
Info1 = Info0
|
|
),
|
|
|
|
goal_info_get_instmap_delta(GoalInfo0, InstMapDelta0),
|
|
simplify_info_get_var_types(Info0, VarTypes),
|
|
map__lookup(VarTypes, ToVar, ToVarType),
|
|
map__lookup(VarTypes, FromVar, FromVarType),
|
|
|
|
( common__types_match_exactly(ToVarType, FromVarType) ->
|
|
instmap__lookup_var(InstMap, ToVar, ToVarInst0),
|
|
( instmap_delta_search_var(InstMapDelta0, ToVar, ToVarInst1) ->
|
|
ToVarInst = ToVarInst1
|
|
;
|
|
term__var_to_int(ToVar, ToVarNum),
|
|
term__var_to_int(FromVar, FromVarNum),
|
|
string__format(
|
|
"common__generate_assign: assigned var %i=%i not in instmap_delta",
|
|
[i(ToVarNum), i(FromVarNum)], Msg),
|
|
error(Msg)
|
|
),
|
|
|
|
UnifyContext = unify_context(explicit, []),
|
|
UniMode = (ToVarInst0 -> ToVarInst) - (ToVarInst -> ToVarInst),
|
|
GoalExpr = unify(ToVar, var(FromVar), UniMode,
|
|
assign(ToVar, FromVar), UnifyContext)
|
|
;
|
|
% If the cells we are optimizing don't have exactly the same
|
|
% type, we insert explicit type casts to ensure type
|
|
% correctness. This avoids problems with HLDS optimizations
|
|
% such as inlining which expect the HLDS to be well-typed.
|
|
% Unfortunately this loses information for other optimizations,
|
|
% since the call to the type cast hides the equivalence of
|
|
% the input and output.
|
|
simplify_info_get_module_info(Info0, ModuleInfo),
|
|
module_info_get_predicate_table(ModuleInfo, PredTable),
|
|
mercury_private_builtin_module(MercuryBuiltin),
|
|
TypeCast = qualified(MercuryBuiltin, "unsafe_type_cast"),
|
|
(
|
|
predicate_table_search_pred_sym_arity(
|
|
PredTable, TypeCast, 2, [PredId])
|
|
->
|
|
hlds_pred__initial_proc_id(ProcId),
|
|
GoalExpr = call(PredId, ProcId, [FromVar, ToVar],
|
|
inline_builtin, no, TypeCast)
|
|
;
|
|
error("common__generate_assign: \
|
|
can't find unsafe_type_cast")
|
|
)
|
|
),
|
|
set__list_to_set([ToVar, FromVar], NonLocals),
|
|
instmap_delta_restrict(InstMapDelta0, NonLocals, InstMapDelta),
|
|
goal_info_init(NonLocals, InstMapDelta, det, GoalInfo),
|
|
Goal = GoalExpr - GoalInfo,
|
|
common__record_equivalence(ToVar, FromVar, Info1, Info).
|
|
|
|
:- pred common__types_match_exactly((type), (type)).
|
|
:- mode common__types_match_exactly(in, in) is semidet.
|
|
|
|
common__types_match_exactly(term__variable(Var), term__variable(Var)).
|
|
common__types_match_exactly(Type1, Type2) :-
|
|
type_to_type_id(Type1, TypeId1, Args1),
|
|
type_to_type_id(Type2, TypeId2, Args2),
|
|
TypeId1 = TypeId2,
|
|
common__types_match_exactly_list(Args1, Args2).
|
|
|
|
:- pred common__types_match_exactly_list(list(type), list(type)).
|
|
:- mode common__types_match_exactly_list(in, in) is semidet.
|
|
|
|
common__types_match_exactly_list([], []).
|
|
common__types_match_exactly_list([Type1 | Types1], [Type2 | Types2]) :-
|
|
common__types_match_exactly(Type1, Type2),
|
|
common__types_match_exactly_list(Types1, Types2).
|
|
|
|
%---------------------------------------------------------------------------%
|
|
%---------------------------------------------------------------------------%
|