[m-rev.] [reuse] diff: further clean up of aliase modules
Nancy Mazur
Nancy.Mazur at cs.kuleuven.ac.be
Tue Jun 8 15:13:03 AEST 2004
Hi,
===================================================================
Estimated hours taken: 2
Branches: reuse
Clean up/document the alias-modules: pa_datastruct, pa_selector,
pa_prelim_run, pa_run, and pa_util.
pa_datastruct.m:
pa_selector.m:
pa_prelim_run.m:
pa_run.m:
pa_util.m:
Clean up/document, including some argument-reordering.
pa_alias.m:
pa_alias_as.m:
pa_alias_set.m:
sr_data.m:
sr_live.m:
Effect of cleaning up the other modules.
Index: pa_alias.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_alias.m,v
retrieving revision 1.1.2.17
diff -u -r1.1.2.17 pa_alias.m
--- pa_alias.m 7 Jun 2004 08:14:51 -0000 1.1.2.17
+++ pa_alias.m 8 Jun 2004 05:03:33 -0000
@@ -76,9 +76,9 @@
{ Alias0 = D1 - D2 },
io__write_string(FrontString),
io__write_string("pair("),
- pa_datastruct__print(D1, ProcInfo, PredInfo),
+ pa_datastruct__print(PredInfo, ProcInfo, D1),
io__write_string(" , "),
- pa_datastruct__print(D2, ProcInfo, PredInfo),
+ pa_datastruct__print(PredInfo, ProcInfo, D2),
io__write_string(") "),
io__write_string(EndString).
@@ -133,8 +133,8 @@
contains_one_of_vars(Set, Alias, DATA) :-
Alias = Data1 - Data2,
- pa_datastruct__get_var(Data1, Var1),
- pa_datastruct__get_var(Data2, Var2),
+ Var1 = Data1^var,
+ Var2 = Data2^var,
(
set__member(Var1, Set)
->
@@ -451,12 +451,7 @@
list(pa_datastruct__datastruct)::out) is det.
one_of_vars_is_live_ordered(ModuleInfo, ProcInfo, List, ALIAS, List_Xsx1) :-
ALIAS = Xsx - Ysy,
- pa_datastruct__get_var(Ysy, Y),
- list__filter(
- pred(D::in) is semidet :-
- (pa_datastruct__get_var(D,Y)),
- List,
- Y_List),
+ list__filter(same_vars(Ysy), List, Y_List),
(
% first try to find one of the found datastructs which is
% fully alive: so that Ysy is less or equal to at least one
Index: pa_alias_as.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_alias_as.m,v
retrieving revision 1.1.2.32
diff -u -r1.1.2.32 pa_alias_as.m
--- pa_alias_as.m 8 Jun 2004 03:08:46 -0000 1.1.2.32
+++ pa_alias_as.m 8 Jun 2004 05:03:37 -0000
@@ -1118,8 +1118,8 @@
parse_list_term(TypesTerm, ListTypesTerms)
->
list__map(term__coerce, ListTypesTerms, Types),
- pa_selector__from_types(Types, Selector),
- pa_datastruct__create(ProgVar, Selector, Data)
+ pa_selector__init(Types, Selector),
+ pa_datastruct__init(ProgVar, Selector, Data)
;
format_context(Context, ContextString),
string__append_list([
Index: pa_alias_set.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_alias_set.m,v
retrieving revision 1.1.2.10
diff -u -r1.1.2.10 pa_alias_set.m
--- pa_alias_set.m 8 Jun 2004 03:08:47 -0000 1.1.2.10
+++ pa_alias_set.m 8 Jun 2004 05:03:42 -0000
@@ -292,12 +292,10 @@
pred(SelData::in, Alias::out) is semidet:-
(
SelData = Selector - Datastruct,
- pa_datastruct__get_var(Datastruct,
- DataVar),
- term__var_to_int(DataVar,
+ term__var_to_int(Datastruct^var,
DataVarInt),
DataVarInt =< VarInt,
- pa_datastruct__create(Var,
+ pa_datastruct__init(Var,
Selector, NewDatastruct),
Alias = NewDatastruct - Datastruct
),
@@ -1027,7 +1025,7 @@
map__foldl(
pred(Sel0::in, DataSet0::in, M0::in, M::out) is det:-
(
- pa_selector__normalize_wti(Type, ModuleInfo,
+ pa_selector__normalize_wti(ModuleInfo, Type,
Sel0, Sel0Norm),
data_set_normalize(ModuleInfo, ProcInfo,
DataSet0, DataSet1),
@@ -1076,10 +1074,10 @@
DataSet0, DataSet1),
% widening of the selector
- pa_datastruct__create(ProgVar, Sel0, Data0),
+ pa_datastruct__init(ProgVar, Sel0, Data0),
pa_datastruct__apply_widening(ModuleInfo,
ProcInfo, Data0, Data),
- pa_datastruct__get_selector(Data, Sel),
+ Sel = Data^selector,
% regroup the widened dataset with the dataset
% that is associated with the widened Sel, as this
@@ -1244,7 +1242,7 @@
data_set_normalize(ModuleInfo, ProcInfo, DataSet0, DataSet):-
data_set_map(
- pa_datastruct__normalize_wti(ProcInfo, ModuleInfo),
+ pa_datastruct__normalize_wti(ModuleInfo, ProcInfo),
DataSet0,
DataSet).
Index: pa_datastruct.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_datastruct.m,v
retrieving revision 1.1.2.10
diff -u -r1.1.2.10 pa_datastruct.m
--- pa_datastruct.m 2 Jun 2004 10:30:48 -0000 1.1.2.10
+++ pa_datastruct.m 8 Jun 2004 05:03:43 -0000
@@ -42,62 +42,60 @@
%-------------------------------------------------------------------%
% init(Var, D)
% Create an initial top-datastruct for variable Var.
-:- pred init(prog_var, datastruct).
-:- mode init(in, out) is det.
+:- pred init(prog_var::in, datastruct::out) is det.
+:- func init(prog_var) = datastruct.
-:- pred get_var(datastruct, prog_var).
-:- mode get_var(in, out) is det.
-
-:- pred get_selector(datastruct, selector).
-:- mode get_selector(in, out) is det.
+ % Initialise a datastructure by its variable and selector.
+:- pred init(prog_var::in, selector::in, datastruct::out) is det.
% init(Var, Cons, Index, D)
- % Create an initial datastruct with an initial path Cons-Index
-:- pred init(prog_var, cons_id, int, datastruct).
-:- mode init(in, in, in, out) is det.
+ % Create an initial datastruct Var^(Cons,Index), thus a data structure
+ % with a selector consisting of only one unit selector, namely the one
+ % identified by the constructor and index within that constructor.
+:- pred init(prog_var::in, cons_id::in, int::in, datastruct::out) is det.
+
+:- pred get_var(datastruct::in, prog_var::out) is det.
+:- func var(datastruct) = prog_var.
-:- pred create(prog_var::in, selector::in, datastruct::out) is det.
+:- pred get_selector(datastruct::in, selector::out) is det.
+:- func selector(datastruct) = selector.
% Extend the given datastructure with an additional path.
-:- pred termshift(datastruct, selector, datastruct).
-:- mode termshift(in, in, out) is det.
+:- pred termshift(datastruct::in, selector::in, datastruct::out) is det.
% less_or_equal(LongerData,ShorterData,Selector)
% Check whether by extending the ShorterData with some selector
% Selector one can obtain LongerData.
% If the datastructs concern different variables, fail right away.
-:- pred less_or_equal(module_info, proc_info, datastruct, datastruct, selector).
-:- mode less_or_equal(in, in, in, in, out) is semidet.
+:- pred less_or_equal(module_info::in, proc_info::in, datastruct::in,
+ datastruct::in, selector::out) is semidet.
% Check whether the two given datastructs are related to the
% same variable or not.
-:- pred same_vars(datastruct, datastruct).
-:- mode same_vars(in,in) is semidet.
+:- pred same_vars(datastruct::in, datastruct::in) is semidet.
% Check whether the given datastructs are identical or not.
-:- pred equal(datastruct, datastruct).
-:- mode equal(in, in) is semidet.
+:- pred equal(datastruct::in, datastruct::in) is semidet.
% Rename the variable of the given datastruct.
-:- pred rename(map(prog_var,prog_var), datastruct, datastruct).
-:- mode rename(in, in, out) is det.
+:- pred rename(map(prog_var,prog_var)::in, datastruct::in,
+ datastruct::out) is det.
:- pred rename_types(term__substitution(tvar_type)::in,
- datastruct::in, datastruct::out) is det.
+ datastruct::in, datastruct::out) is det.
% Printing routines
-:- pred print(datastruct, proc_info, pred_info, io__state, io__state).
-:- mode print(in, in, in, di, uo) is det.
+:- pred print(pred_info::in, proc_info::in, datastruct::in,
+ io__state::di, io__state::uo) is det.
-:- pred to_user_declared(datastruct, prog_varset, tvarset, string).
-:- mode to_user_declared(in, in, in, out) is det.
+:- pred to_user_declared(datastruct::in, prog_varset::in,
+ tvarset::in, string::out) is det.
% Parsing routines
-:- pred parse_term(term(T), datastruct).
-:- mode parse_term(in, out) is det.
+:- pred parse_term(term(T)::in, datastruct::out) is det.
-:- pred normalize_wti(proc_info, module_info, datastruct, datastruct).
-:- mode normalize_wti(in, in, in, out) is det.
+:- pred normalize_wti(module_info::in, proc_info::in,
+ datastruct::in, datastruct::out) is det.
:- pred apply_widening(module_info::in, proc_info::in, datastruct::in,
datastruct::out) is det.
@@ -117,8 +115,10 @@
:- type datastruct ---> cel(prog_var, pa_selector__selector).
-get_var(cel(VAR, _Sel), VAR).
-get_selector(cel(_Var, SEL), SEL).
+get_var(cel(Var, _Sel), Var).
+var(cel(Var, _Sel)) = Var.
+get_selector(cel(_Var, Sel), Sel).
+selector(cel(_Var, Sel)) = Sel.
rename(MAP, DATAin, DATAout) :-
@@ -164,10 +164,12 @@
init(V, Dout) :-
SEL = [],
Dout = cel(V, SEL).
-create(V, Sel, Dout) :-
+init(V) = D :- init(V, D).
+
+init(V, Sel, Dout) :-
Dout = cel(V, Sel).
-print(D, ProcInfo, PredInfo) -->
+print(PredInfo, ProcInfo, D) -->
{ D = cel(ProgVar, SEL) },
{ proc_info_varset(ProcInfo, ProgVarset) },
{ varset__lookup_name(ProgVarset, ProgVar, ProgName) },
@@ -222,19 +224,19 @@
).
-normalize_wti(ProcInfo, HLDS, Din, Dout):-
+normalize_wti(HLDS, ProcInfo, Din, Dout):-
proc_info_vartypes(ProcInfo, VarTypes),
- normalize_wti_2(VarTypes, HLDS, Din, Dout).
+ normalize_wti_2(HLDS, VarTypes, Din, Dout).
% normalize with type information
-:- pred normalize_wti_2(vartypes, module_info,
+:- pred normalize_wti_2(module_info, vartypes,
datastruct, datastruct).
:- mode normalize_wti_2(in, in, in, out) is det.
-normalize_wti_2(VarTypes, HLDS, D0, D):-
+normalize_wti_2(HLDS, VarTypes, D0, D):-
D0 = cel(ProgVar, SEL0),
map__lookup(VarTypes, ProgVar, VarType),
- pa_selector__normalize_wti(VarType, HLDS, SEL0, SEL),
+ pa_selector__normalize_wti(HLDS, VarType, SEL0, SEL),
D = cel(ProgVar, SEL).
apply_widening(ModuleInfo, ProcInfo, D0, D):-
Index: pa_prelim_run.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_prelim_run.m,v
retrieving revision 1.1.2.9
diff -u -r1.1.2.9 pa_prelim_run.m
--- pa_prelim_run.m 2 Jun 2004 10:30:49 -0000 1.1.2.9
+++ pa_prelim_run.m 8 Jun 2004 05:03:44 -0000
@@ -26,12 +26,46 @@
:- import_module io.
+ % Before the alias analysis starts for a module starts, all the
+ % alias-pragma's for the exported procedures imported by that module
+ % are stored in the HLDS. They are stored as a list of
+ % "unproc_alias_pragmas" (cf. hlds_module). It is up to the predicate
+ % defined here, process_imported_predicates, to process each of these
+ % stored pragma's, and store them in the procedure info for each of
+ % these procedures.
+ % XXX the type unproc_alias_pragma should not be in terms of alias_as
+ % but in terms of the to be defined public form of alias information.
:- pred process_imported_predicates(module_info::in, module_info::out,
io__state::di, io__state::uo) is det.
+ % The pre-births and post-deaths as derived by the liveness pass
+ % (where liveness should be seen as the liveness in the context of
+ % llds) are interesting for the alias-derivation, as these sets make it
+ % possible to downsize the number of aliases to propagate: for
+ % deconstructions, only aliases between the pre-births need to be
+ % generated, and for unifications in general, it is worthwhile to
+ % remove all the aliases regarding variables that are in the post-death
+ % set, i.e. that do not appear in the user code after these
+ % unifications.
+ % XXX Question for later: same optimization possible also for procedure
:- pred annotate_all_liveness_in_module(module_info::in, module_info::out,
io__state::di, io__state::uo) is det.
+ % This pass annotates every goal with the set of variables that are in
+ % the scope of the current goal _AND_ are not local to the current
+ % goal. Such vars are called outscope-vars here.
+ % Apparently this information is only used in the structure reuse pass
+ % where it is used to determine the possible candidates for reusing a
+ % dead data structure.
+ % XXX So why is this annotation performed at the beginning of the
+ % XXX And can this information not be used by the alias pass to reduce
+ % projecting the alias sets to the outscope variables, as aliases
+ % regarding local variables of a goal, may not be of any influence on
+ % XXX To find out!!!
:- pred annotate_all_outscope_vars_in_module(module_info::in,
module_info::out) is det.
Index: pa_run.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_run.m,v
retrieving revision 1.1.2.28
diff -u -r1.1.2.28 pa_run.m
--- pa_run.m 7 Jun 2004 08:14:52 -0000 1.1.2.28
+++ pa_run.m 8 Jun 2004 05:03:46 -0000
@@ -5,9 +5,11 @@
%-----------------------------------------------------------------------------%
% module pa_run: implements the process of annotating each procedure
-% with possible alias information, i.e. with information
-% which states which additional parts of the
-% head-variables might become aliased after the procedure exits
+% with possible alias information. The analysis is
+% goal-independent, and thus returns only those aliases that
+% are created by the analysed procedure, without taking into
+% account the possible aliases that might exist when calling
+% that procedure. (cf. Phd Nancy, chapter 6).
% main author: nancy
:- module possible_alias__pa_run.
@@ -22,16 +24,21 @@
:- import_module io, list.
% the main pass
-:- pred pa_run__aliases_pass(module_info, module_info, io__state, io__state).
-:- mode pa_run__aliases_pass(in, out, di, uo) is det.
+:- pred pa_run__aliases_pass(module_info::in, module_info::out,
+ io__state::di, io__state::uo) is det.
- % write the pa_info pragma for the given pred_id (if that
+ % Write the pa_info pragma for the given pred_id (if that
% pred_id does not belong to the list(pred_id).
-:- pred pa_run__write_pred_pa_info(module_info, list(pred_id), pred_id,
- io__state, io__state).
-:- mode pa_run__write_pred_pa_info(in, in, in, di, uo) is det.
+ %
+ % XXX The result of the analysis should be possible alias information
+ % written as a publicly available type within the HLDS. The predicate
+ % for actually writing out the pragma should be moved to somewhere (?)
+ % else. Note that this predicate is used in "trans_opt", while the
+ % "public" types will probably be defined in prog_data.
+:- pred pa_run__write_pred_pa_info(module_info::in, list(pred_id)::in,
+ pred_id::in, io__state::di, io__state::uo) is det.
- % lookup the alias-information for some pred_id proc_id in the
+ % Lookup the alias-information for some pred_id proc_id in the
% module_info. Rename the alias-information to the given
% actual parameters, and extend the given alias_as with the
% looked up alias_as.
@@ -50,11 +57,14 @@
% proc is called
% AliasIN = alias at moment of call
% AliasOUT = alias at end of call
-:- pred pa_run__extend_with_call_alias(module_info, proc_info,
- pred_id, proc_id,
- list(prog_var),
- list((type)), alias_as, alias_as).
-:- mode pa_run__extend_with_call_alias(in, in, in, in, in, in, in, out) is det.
+ %
+ % XXX While the result of the possible alias pass should be expressed
+ % in a "public" type for outputting the HLDS and alike, yet it is
+ % preferrable to keep the optimised representation as well for its
+ % use during the structure reuse pass. This is a bit of a dilemma.
+:- pred pa_run__extend_with_call_alias(module_info::in, proc_info::in,
+ pred_id::in, proc_id::in, list(prog_var)::in,
+ list((type))::in, alias_as::in, alias_as::out) is det.
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
Index: pa_selector.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_selector.m,v
retrieving revision 1.1.2.14
diff -u -r1.1.2.14 pa_selector.m
--- pa_selector.m 2 Jun 2004 10:30:49 -0000 1.1.2.14
+++ pa_selector.m 8 Jun 2004 05:03:48 -0000
@@ -4,16 +4,11 @@
% Public License - see the file COPYING in the Mercury distribution.
%-----------------------------------------------------------------------------%
-% module pa_selector: defines the selectors as they are used within
+% module pa_selector: Defines the selectors as they are used within
% the possible alias analysis.
% main author: nancy
-
-% notes:
-% 1. this code is quite similar to (and in fact based on) the code Wim
-% wrote for his BTA where he also uses the concept of a selector. At
-% some point this code could be really shared by both analysis.
-% 2. _partially instantiated datastructures_ : the day they'll be
-% introduced, a couple of things will have to be changed.
+%
+% XXX will be moved to prog_data.
:- module possible_alias__pa_selector.
@@ -43,27 +38,24 @@
% create an initial selector with given constructor and index.
:- pred init(cons_id::in, int::in, selector::out) is det.
-
-:- pred from_types(list(type)::in, selector::out) is det.
+
+ % create an initial (type)selector using the list of types.
+:- pred init(list(type)::in, selector::out) is det.
% check whether the selector is a top-selector.
:- pred top(selector::in) is semidet.
- % select_first_part(InputSelector, Head_unit_selector, Tail).
- % Select the first unit selector from the given selector,
- % and return also the remainders.
- % The predicate produces a software error when the input
- % selector is a top-selector.
-:- pred select_first_part(selector, unit_sel, selector).
-:- mode select_first_part(in, out, out) is det.
+ % head(S,H,T) returns H, the head of selector S, and T, the tail of S
+ % when removing that head. The predicate aborts when the input is a
+ % top-level selector.
+:- pred head(selector::in, unit_sel::out, selector::out) is det.
% termshift(InputSelector, NewExtension, ResultingSelector).
% Extend the given selector with a new extension (unit selector).
-:- pred unit_termshift(selector, unit_sel, selector).
-:- mode unit_termshift(in, in, out) is det.
+:- pred unit_termshift(selector::in, unit_sel::in, selector::out) is det.
-:- pred termshift(selector, selector, selector).
-:- mode termshift(in, in, out) is det.
+ % Extend the selector with a new selector.
+:- pred termshift(selector::in, selector::in, selector::out) is det.
% less_or_equal(HLDS, S1, S2, T, EXT):
% Find out whether selector S1 of a variable of type T is
@@ -80,12 +72,11 @@
io__state::di, io__state::uo) is det.
:- pred to_user_declared(selector::in, tvarset::in, string::out) is det.
-:- pred parse_term(term(T), selector).
-:- mode parse_term(in, out) is det.
+:- pred parse_term(term(T)::in, selector::out) is det.
% normalize with type information
-:- pred normalize_wti((type), module_info, selector, selector).
-:- mode normalize_wti(in, in, in, out) is det.
+:- pred normalize_wti(module_info::in, (type)::in, selector::in,
+ selector::out) is det.
% widening
:- pred apply_widening(module_info::in, (type)::in,
@@ -111,10 +102,10 @@
:- import_module assoc_list, map.
init([]).
-init(CONS, INDEX, SEL):-
- US = us(CONS, INDEX),
- SEL = [US].
-from_types(Types, Selector):-
+init(Cons, Index, Sel):-
+ US = us(Cons, Index),
+ Sel = [US].
+init(Types, Selector):-
list__map(
pred(T::in, US::out) is det :-
US = ts(T),
@@ -124,11 +115,11 @@
top([]).
-select_first_part(SEL0, US, SEL):-
+head(Sel0, US, Sel):-
(
- SEL0 = [ F | R ]
+ Sel0 = [ F | R ]
->
- US = F, SEL = R
+ US = F, Sel = R
;
error("(pa_selector): trying to split empty selector!")
).
@@ -142,8 +133,7 @@
% subsumed by"), i.e. S1 can be selected by extending S2 with
% the extension EXT (output).
% PRECONDITION: the selectors do not contain any type-selectors.
-:- pred less_or_equal(selector, selector, selector).
-:- mode less_or_equal(in, in, out) is semidet.
+:- pred less_or_equal(selector::in, selector::in, selector::out) is semidet.
less_or_equal(S1, S2, EXT) :-
list__append(S2, EXT , S1).
@@ -170,8 +160,8 @@
io__write_list(Selector, ",", print_unit_selector(ProgVarSet)),
io__write_string("]").
-:- pred print_unit_selector(tvarset, unit_sel, io__state, io__state).
-:- mode print_unit_selector(in, in, di, uo) is det.
+:- pred print_unit_selector(tvarset::in, unit_sel::in,
+ io__state::di, io__state::uo) is det.
print_unit_selector(_ProgVarSet, us(Cons, Index)) -->
{ hlds_data__cons_id_arity(Cons, Arity) },
@@ -218,55 +208,54 @@
us_to_user_declared(ts(Type), TVarSet,
mercury_type_to_string(TVarSet, Type)).
-parse_term(TERM, SEL):-
+parse_term(Term, Sel):-
(
- TERM = term__functor(term__atom(CONS), Args, _)
+ Term = term__functor(term__atom(Cons), Args, _)
->
(
- CONS = "[|]",
+ Cons = "[|]",
Args = [ First , Rest ]
->
parse_unit_selector(First, US),
- parse_term(Rest, SELrest),
- SEL = [ US | SELrest ]
+ parse_term(Rest, SelRest),
+ Sel = [ US | SelRest ]
;
- SEL = []
+ Sel = []
)
;
error("(pa_selector) parse_term: term not a functor")
).
-:- pred parse_unit_selector(term(T), unit_sel).
-:- mode parse_unit_selector(in, out) is det.
+:- pred parse_unit_selector(term(T)::in, unit_sel::out) is det.
-parse_unit_selector(TERM, US):-
+parse_unit_selector(Term, US):-
(
- TERM = term__functor(term__atom(CONS), Args, _)
+ Term = term__functor(term__atom(Cons), Args, _)
->
(
- CONS = "sel",
- Args = [ CONS_TERM, ARITY_TERM, POS_TERM ]
+ Cons = "sel",
+ Args = [ ConsTerm, ArityTerm, PosTerm ]
->
(
- prog_io__sym_name_and_args(CONS_TERM, ConsID_SN, ConsID_ARGS),
- ConsID_ARGS = [],
- ARITY_TERM = term__functor(term__integer(Arity), _, _),
- POS_TERM = term__functor(term__integer(Pos), _, _)
+ prog_io__sym_name_and_args(ConsTerm, ConsID_SN, ConsID_Args),
+ ConsID_Args = [],
+ ArityTerm = term__functor(term__integer(Arity), _, _),
+ PosTerm = term__functor(term__integer(Pos), _, _)
->
ConsID = cons(ConsID_SN, Arity),
US = us(ConsID, Pos)
;
- CONS_TERM = term__functor(term__integer(X), _, _)
+ ConsTerm = term__functor(term__integer(X), _, _)
->
ConsID = int_const(X),
US = us(ConsID, 0)
;
- CONS_TERM = term__functor(term__float(X), _, _)
+ ConsTerm = term__functor(term__float(X), _, _)
->
ConsID = float_const(X),
US = us(ConsID, 0)
;
- CONS_TERM = term__functor(term__string(S), _, _)
+ ConsTerm = term__functor(term__string(S), _, _)
->
ConsID = string_const(S),
US = us(ConsID, 0)
@@ -275,7 +264,7 @@
)
;
- CONS = "typesel",
+ Cons = "typesel",
Args = [ TypeSelectorTerm ]
->
term__coerce(TypeSelectorTerm, TypeSelector),
@@ -288,23 +277,23 @@
).
-normalize_wti(VarType, HLDS, SEL0, SEL):-
+normalize_wti(HLDS, VarType, Sel0, Sel):-
(
type_util__is_introduced_type_info_type(VarType)
->
- SEL = SEL0
+ Sel = Sel0
;
branch_map_init(B0),
- init(TOP),
- branch_map_insert(VarType, TOP, B0, B1),
- normalize_wti_2(VarType, HLDS, B1, TOP, SEL0, SEL)
+ init(Top),
+ branch_map_insert(VarType, Top, B0, B1),
+ normalize_wti_2(HLDS, VarType, B1, Top, Sel0, Sel)
).
-:- pred normalize_wti_2(type, module_info, branch_map,
+:- pred normalize_wti_2(module_info, type, branch_map,
selector, selector, selector).
:- mode normalize_wti_2(in, in, in, in, in, out) is det.
-normalize_wti_2(VarType, HLDS, B0, Acc0, SEL0, SEL):-
+normalize_wti_2(HLDS, VarType, B0, Acc0, SEL0, SEL):-
(
SEL0 = [ US | SELR ]
->
@@ -335,14 +324,14 @@
branch_map_search(B0, CType,
BSel)
->
- normalize_wti_2(CType, HLDS,
+ normalize_wti_2(HLDS, CType,
B0, BSel, SELR, SEL)
;
unit_termshift(Acc0, US,
Acc1),
branch_map_insert(CType,
Acc1, B0, B1),
- normalize_wti_2(CType, HLDS,
+ normalize_wti_2(HLDS, CType,
B1, Acc1, SELR, SEL)
)
;
@@ -490,8 +479,8 @@
less_or_equal(HLDS, S1, S2, MainType, EXT):-
- normalize_wti(MainType, HLDS, S1, NormS1),
- normalize_wti(MainType, HLDS, S2, NormS2),
+ normalize_wti(HLDS, MainType, S1, NormS1),
+ normalize_wti(HLDS, MainType, S2, NormS2),
less_or_equal_2(HLDS, NormS1, NormS2, MainType, EXT).
:- pred less_or_equal_2(module_info::in, selector::in, selector::in,
Index: pa_util.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/pa_util.m,v
retrieving revision 1.1.2.12
diff -u -r1.1.2.12 pa_util.m
--- pa_util.m 2 Jun 2004 10:30:49 -0000 1.1.2.12
+++ pa_util.m 8 Jun 2004 05:03:49 -0000
@@ -4,8 +4,12 @@
% Public License - see the file COPYING in the Mercury distribution.
%-----------------------------------------------------------------------------%
-% module pa_util: extra datastructures and predicates needed by the
-% KUL aliasing pass
+% module pa_util:
+% * Defines the fixpoint table used in the analysis of possible
+% aliases.
+% * Defines some type-related predicates (should be moved to somewhere
+% else though). XXX
+%
% main author: nancy
:- module possible_alias__pa_util.
@@ -19,46 +23,50 @@
:- type pa_fixpoint_table.
+ % Initialise the fixpoint table for the given set of pred_proc_id's.
:- pred pa_fixpoint_table_init(list(pred_proc_id)::in,
- pa_fixpoint_table::out) is det.
+ pa_fixpoint_table::out) is det.
- % the datastructure keeps track of the number of fixpoint runs
- % performed, this predicates adds one.
-:- pred pa_fixpoint_table_new_run(pa_fixpoint_table::in, pa_fixpoint_table::out) is det.
+ % Add the results of a new analysis pass to the already existing
+ % fixpoint table.
+:- pred pa_fixpoint_table_new_run(pa_fixpoint_table::in,
+ pa_fixpoint_table::out) is det.
+ % The fixpoint table keeps track of the number of analysis passes. This
+ % predicate returns this number.
:- pred pa_fixpoint_table_which_run(pa_fixpoint_table::in, int::out) is det.
- % check whether all entries are stable. If so, one has reached
- % a fixpoint
-:- pred pa_fixpoint_table_all_stable(pa_fixpoint_table:: in) is semidet.
-
- % at the end of the analysis of one single pred_proc_id,
- % the new exit alias information is stored. This might
- % change the stability of the table.
- % if the pred_proc_id is not in the table --> error
-:- pred pa_fixpoint_table_new_as(module_info, proc_info,
- pred_proc_id, alias_as,
- pa_fixpoint_table, pa_fixpoint_table).
-:- mode pa_fixpoint_table_new_as(in, in, in, in, in, out) is det.
-
- % retreive the alias abstract substitution of a given
- % pred_proc_id. If this information is not available,
- % the general character of the fixpoint-table will be
- % set to `recursive'
- % if the pred_proc_id is not in the table --> fail
-:- pred pa_fixpoint_table_get_as(pred_proc_id, alias_as,
- pa_fixpoint_table, pa_fixpoint_table).
-:- mode pa_fixpoint_table_get_as(in, out, in, out) is semidet.
+ % A fixpoint is reached if all entries in the table are stable,
+ % i.e. haven't been modified by the last analysis pass.
+:- pred pa_fixpoint_table_all_stable(pa_fixpoint_table::in) is semidet.
+
+ % Enter the newly computed alias description for a given procedure.
+ % If the description is different from the one that was already stored
+ % for that procedure, the stability of the fixpoint table is set to
+ % "unstable".
+ % Aborts if the procedure is not already in the fixpoint table.
+:- pred pa_fixpoint_table_new_as(module_info::in, proc_info::in,
+ pred_proc_id::in, alias_as::in,
+ pa_fixpoint_table::in, pa_fixpoint_table::out) is det.
+
+ % Retreive the alias description of a given
+ % pred_proc_id. If this information is not available, this means that
+ % the set of pred_proc_id's to which the fixpoint table relates are
+ % mutually recursive, hence the table is characterised as recursive.
+ % Fails if the procedure is not in the table.
+:- pred pa_fixpoint_table_get_as(pred_proc_id::in, alias_as::out,
+ pa_fixpoint_table::in, pa_fixpoint_table::out) is semidet.
- % retreive alias_as information, without changing the
+ % Retreive alias_as information, without changing the
% table. To be used after fixpoint has been reached.
-:- pred pa_fixpoint_table_get_final_as(pred_proc_id, alias_as,
- pa_fixpoint_table).
-:- mode pa_fixpoint_table_get_final_as(in, out, in) is det.
-
-:- pred pa_fixpoint_table_get_final_as_semidet(pred_proc_id, alias_as,
- pa_fixpoint_table).
-:- mode pa_fixpoint_table_get_final_as_semidet(in, out, in) is semidet.
+ % Aborts if the procedure is not in the table.
+:- pred pa_fixpoint_table_get_final_as(pred_proc_id::in, alias_as::out,
+ pa_fixpoint_table::in) is det.
+
+ % Same as pa_fixpoint_table_get_final_as, yet fails instead of aborting
+ % if the procedure is not in the table.
+:- pred pa_fixpoint_table_get_final_as_semidet(pred_proc_id::in, alias_as::out,
+ pa_fixpoint_table::in) is semidet.
%-----------------------------------------------------------------------------%
Index: sr_data.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/sr_data.m,v
retrieving revision 1.1.2.23
diff -u -r1.1.2.23 sr_data.m
--- sr_data.m 7 Jun 2004 08:14:52 -0000 1.1.2.23
+++ sr_data.m 8 Jun 2004 05:04:13 -0000
@@ -279,8 +279,7 @@
ALIASi, AliasedData),
list__filter(
pred(Data::in) is semidet :-
- (pa_datastruct__get_var(Data,V),
- list__member(V, HVs)),
+ (list__member(Data^var, HVs)),
AliasedData,
Nodes)
),
@@ -351,10 +350,7 @@
% write out the list of headvar-nodes involved
io__write_string("["),
io__write_list(NodesList, ",",
- pred( D::in, IO1::di, IO2::uo) is det :-
- (pa_datastruct__print(D, ProcInfo,
- PredInfo, IO1, IO2))
- ),
+ pa_datastruct__print(PredInfo, ProcInfo)),
io__write_string("], "),
% write out LUiH, list of prog_vars
@@ -407,8 +403,7 @@
list__condense([ OLD_NODES | LISTS_ALL_NEW_NODES], ALL_NEW_NODES),
list__filter(
pred(DATA::in) is semidet :-
- (pa_datastruct__get_var(DATA,V),
- list__member(V, HVs)),
+ (list__member(DATA^var, HVs)),
ALL_NEW_NODES,
NEW_NODES),
(
@@ -418,7 +413,7 @@
;
% normalize all the datastructs
list__map(
- pa_datastruct__normalize_wti(ProcInfo, HLDS),
+ pa_datastruct__normalize_wti(HLDS, ProcInfo),
NEW_NODES,
NORM_NODES
),
Index: sr_live.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/Attic/sr_live.m,v
retrieving revision 1.1.2.5
diff -u -r1.1.2.5 sr_live.m
--- sr_live.m 2 Jun 2004 10:30:54 -0000 1.1.2.5
+++ sr_live.m 8 Jun 2004 05:04:19 -0000
@@ -203,8 +203,7 @@
list__filter(
pred(D::in) is semidet :-
(
- pa_datastruct__get_var(D, Var),
- list__member(Var, VARS)
+ list__member(D^var, VARS)
),
Datastructs,
FilteredDatastructs),
--
nancy.mazur at cs.kuleuven.ac.be ------------ Katholieke Universiteit Leuven -
tel: +32-16-327596 - fax: +32-16-327996 ------- Dept. of Computer Science -
--------------------------------------------------------------------------
mercury-reviews mailing list
post: mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------
More information about the reviews
mailing list