mirror of
https://github.com/Mercury-Language/mercury.git
synced 2025-12-20 08:19:28 +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.
210 lines
7.5 KiB
Mathematica
210 lines
7.5 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.
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
% Main author: zs.
|
|
|
|
% This module traverses the goal for each procedure, looking
|
|
% for conjunctions containing assignment unifications to or from
|
|
% a variable that is local to the conjunction. Such unifications
|
|
% effectively just introduce a new local name for a variable.
|
|
% This module optimizes away such unifications by replacing all
|
|
% occurrences of the local name with the other name.
|
|
%
|
|
% Note that the output of this pass is not in super-homogeneous form,
|
|
% since if two equivalent variables are passed in two argument positions,
|
|
% they will not be distinct after this pass. This is not a problem, since
|
|
% this pass occurs after the passes that rely on super-homogeneous form.
|
|
%
|
|
% This HLDS-to-HLDS optimization is applied after the front end has
|
|
% completed all of its semantic checks (i.e. after determinism analysis),
|
|
% but before code generation.
|
|
%
|
|
% It allows optimizations such as middle recursion to be simplified,
|
|
% and it reduces the pressure on the stack slot allocator.
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
:- module excess.
|
|
|
|
:- interface.
|
|
|
|
:- import_module hlds_module, hlds_pred.
|
|
|
|
% optimize away excess assignments for a single procedure
|
|
:- pred excess_assignments_proc(proc_info, module_info, proc_info).
|
|
% :- mode excess_assignments_proc(di, in, uo) is det.
|
|
:- mode excess_assignments_proc(in, in, out) is det.
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
:- implementation.
|
|
|
|
:- import_module hlds_goal, goal_util, prog_data, varset, term.
|
|
:- import_module list, bool, map, set, std_util.
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
excess_assignments_proc(ProcInfo0, _ModuleInfo, ProcInfo) :-
|
|
proc_info_goal(ProcInfo0, Goal0),
|
|
excess_assignments_in_goal(Goal0, [], Goal, ElimVars),
|
|
proc_info_set_goal(ProcInfo0, Goal, ProcInfo1),
|
|
|
|
% XXX We probably ought to remove these vars from the type map as well.
|
|
proc_info_varset(ProcInfo1, Varset0),
|
|
varset__delete_vars(Varset0, ElimVars, Varset),
|
|
proc_info_set_varset(ProcInfo1, Varset, ProcInfo).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
% We want to replace code sequences of the form
|
|
%
|
|
% (
|
|
% <Foo>,
|
|
% LocalVar = OtherVar,
|
|
% <Bar>
|
|
% )
|
|
%
|
|
% with
|
|
%
|
|
% (
|
|
% <Foo> [LocalVar/OtherVar],
|
|
% <Bar> [LocalVar/OtherVar],
|
|
% )
|
|
%
|
|
% where <Foo> and <Bar> are sequences of conjuncts,
|
|
% LocalVar is a variable that is local to the conjuncts,
|
|
% and the notation `<Foo> [X/Y]' means <Foo> with all
|
|
% occurrences of `X' replaced with `Y'.
|
|
|
|
:- pred excess_assignments_in_goal(hlds_goal, list(prog_var),
|
|
hlds_goal, list(prog_var)).
|
|
:- mode excess_assignments_in_goal(in, in, out, out) is det.
|
|
|
|
excess_assignments_in_goal(GoalExpr0 - GoalInfo0, ElimVars0, Goal, ElimVars) :-
|
|
(
|
|
GoalExpr0 = conj(Goals0),
|
|
goal_info_get_nonlocals(GoalInfo0, NonLocals),
|
|
excess_assignments_in_conj(Goals0, [], ElimVars0, NonLocals,
|
|
Goals, ElimVars),
|
|
conj_list_to_goal(Goals, GoalInfo0, Goal)
|
|
;
|
|
GoalExpr0 = par_conj(Goals0, _SM),
|
|
goal_info_get_nonlocals(GoalInfo0, NonLocals),
|
|
excess_assignments_in_conj(Goals0, [], ElimVars0, NonLocals,
|
|
Goals, ElimVars),
|
|
par_conj_list_to_goal(Goals, GoalInfo0, Goal)
|
|
;
|
|
GoalExpr0 = disj(Goals0, SM),
|
|
excess_assignments_in_disj(Goals0, ElimVars0, Goals, ElimVars),
|
|
Goal = disj(Goals, SM) - GoalInfo0
|
|
;
|
|
GoalExpr0 = not(NegGoal0),
|
|
excess_assignments_in_goal(NegGoal0, ElimVars0,
|
|
NegGoal, ElimVars),
|
|
Goal = not(NegGoal) - GoalInfo0
|
|
;
|
|
GoalExpr0 = switch(Var, CanFail, Cases0, SM),
|
|
excess_assignments_in_switch(Cases0, ElimVars0,
|
|
Cases, ElimVars),
|
|
Goal = switch(Var, CanFail, Cases, SM) - GoalInfo0
|
|
;
|
|
GoalExpr0 = if_then_else(Vars, Cond0, Then0, Else0, SM),
|
|
excess_assignments_in_goal(Cond0, ElimVars0, Cond, ElimVars1),
|
|
excess_assignments_in_goal(Then0, ElimVars1, Then, ElimVars2),
|
|
excess_assignments_in_goal(Else0, ElimVars2, Else, ElimVars),
|
|
Goal = if_then_else(Vars, Cond, Then, Else, SM) - GoalInfo0
|
|
;
|
|
GoalExpr0 = some(Var, CanRemove, SubGoal0),
|
|
excess_assignments_in_goal(SubGoal0, ElimVars0,
|
|
SubGoal, ElimVars),
|
|
Goal = some(Var, CanRemove, SubGoal) - GoalInfo0
|
|
;
|
|
GoalExpr0 = generic_call(_, _, _, _),
|
|
Goal = GoalExpr0 - GoalInfo0,
|
|
ElimVars = ElimVars0
|
|
;
|
|
GoalExpr0 = call(_, _, _, _, _, _),
|
|
Goal = GoalExpr0 - GoalInfo0,
|
|
ElimVars = ElimVars0
|
|
;
|
|
GoalExpr0 = unify(_, _, _, _, _),
|
|
Goal = GoalExpr0 - GoalInfo0,
|
|
ElimVars = ElimVars0
|
|
;
|
|
GoalExpr0 = pragma_c_code(_, _, _, _, _, _, _),
|
|
Goal = GoalExpr0 - GoalInfo0,
|
|
ElimVars = ElimVars0
|
|
),
|
|
!.
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
% We apply each substitution as soon as we find the need for it.
|
|
% This is to handle code which has V_4 = V_5, V_5 = V_6. If at most
|
|
% one of these variables is nonlocal, we can eliminate both assignments.
|
|
% If (say) V_4 and V_6 are nonlocal, then after the V_5 => V_4
|
|
% substitution has been made, the second assignment V_4 = V_6
|
|
% is left alone.
|
|
%
|
|
% This code is used for both sequential conjunction (conj/1) and
|
|
% parallel conjunction (par_conj/2).
|
|
|
|
:- pred excess_assignments_in_conj(list(hlds_goal), list(hlds_goal),
|
|
list(prog_var), set(prog_var), list(hlds_goal), list(prog_var)).
|
|
:- mode excess_assignments_in_conj(in, in, in, in, out, out) is det.
|
|
|
|
excess_assignments_in_conj([], RevGoals, ElimVars, _, Goals, ElimVars) :-
|
|
list__reverse(RevGoals, Goals).
|
|
excess_assignments_in_conj([Goal0 | Goals0], RevGoals0, ElimVars0, NonLocals,
|
|
Goals, ElimVars) :-
|
|
(
|
|
Goal0 = unify(_, _, _, Unif, _) - _,
|
|
Unif = assign(LeftVar, RightVar),
|
|
( \+ set__member(LeftVar, NonLocals) ->
|
|
LocalVar = LeftVar, ReplacementVar = RightVar
|
|
; \+ set__member(RightVar, NonLocals) ->
|
|
LocalVar = RightVar, ReplacementVar = LeftVar
|
|
;
|
|
fail
|
|
)
|
|
->
|
|
map__init(Subn0),
|
|
map__det_insert(Subn0, LocalVar, ReplacementVar, Subn),
|
|
goal_util__rename_vars_in_goals(Goals0, no, Subn, Goals1),
|
|
goal_util__rename_vars_in_goals(RevGoals0, no, Subn, RevGoals1),
|
|
ElimVars1 = [LocalVar | ElimVars0]
|
|
;
|
|
Goals1 = Goals0,
|
|
excess_assignments_in_goal(Goal0, ElimVars0, Goal1, ElimVars1),
|
|
RevGoals1 = [Goal1 | RevGoals0]
|
|
),
|
|
excess_assignments_in_conj(Goals1, RevGoals1, ElimVars1,
|
|
NonLocals, Goals, ElimVars).
|
|
|
|
%-----------------------------------------------------------------------------%
|
|
|
|
:- pred excess_assignments_in_disj(list(hlds_goal), list(prog_var),
|
|
list(hlds_goal), list(prog_var)).
|
|
:- mode excess_assignments_in_disj(in, in, out, out) is det.
|
|
|
|
excess_assignments_in_disj([], ElimVars, [], ElimVars).
|
|
excess_assignments_in_disj([Goal0 | Goals0], ElimVars0,
|
|
[Goal | Goals], ElimVars) :-
|
|
excess_assignments_in_goal(Goal0, ElimVars0, Goal, ElimVars1),
|
|
excess_assignments_in_disj(Goals0, ElimVars1, Goals, ElimVars).
|
|
|
|
:- pred excess_assignments_in_switch(list(case), list(prog_var),
|
|
list(case), list(prog_var)).
|
|
:- mode excess_assignments_in_switch(in, in, out, out) is det.
|
|
|
|
excess_assignments_in_switch([], ElimVars, [], ElimVars).
|
|
excess_assignments_in_switch([case(Cons, Goal0) | Cases0], ElimVars0,
|
|
[case(Cons, Goal) | Cases], ElimVars) :-
|
|
excess_assignments_in_goal(Goal0, ElimVars0, Goal, ElimVars1),
|
|
excess_assignments_in_switch(Cases0, ElimVars1, Cases, ElimVars).
|
|
|
|
%-----------------------------------------------------------------------------%
|