[m-rev.] for review: inter-module analysis framework
Simon Taylor
stayl at cs.mu.OZ.AU
Tue Aug 27 16:15:06 AEST 2002
On 23-Aug-2002, Fergus Henderson <fjh at cs.mu.OZ.AU> wrote:
> > > > Index: analysis/mer_analysis.m
> > > > ===================================================================
> > > > RCS file: analysis/mer_analysis.m
> > > > diff -N analysis/mer_analysis.m
> > > > --- /dev/null 1 Jan 1970 00:00:00 -0000
> > > > +++ analysis/mer_analysis.m 1 Aug 2002 10:24:36 -0000
> > > > @@ -0,0 +1,3 @@
> > > > +:- module mer_analysis.
> > > > +
> > > > +:- import_module analysis.
> > >
> > > What's the purpose of this module?
> >
> > Just to match the naming of the other libraries in the Mercury system.
>
> Oh, you mean that this module is actually a "library", in the sense
> explained in the "Libraries" chapter of the Mercury user's guide, and
> the name is chosen so that it matches our library naming convention?
>
> There should be a comment in the source code explaining this.
Done.
> What about analysis of class methods?
>
> The analysis framework looks OK for analysis of ordinary
> procedure calls, but doesn't address higher-order calls
> or class method calls.
>
> If that is intentional, then I think it is worth noting
> in the design documentation.
It is intentional.
> > Each analysis is described by a call pattern type and an
> > answer pattern type. Call and answer patterns must form
> > a partial order, and must be convertible to strings.
>
> I think it would be helpful to explain what "call patterns"
> and "answer patterns" are supposed to represent.
Done.
> > Analysis dependency checker (NYI)
> > =================================
> ...
> > If the interface of a function changes, all of its answers are
> > marked as invalid,
>
> Did you mean to say "If the *implementation* of a function changes, ..."?
Yes.
> > For greatest fixpoint analyses, if the new answer is
> > - less precise than or incomparable with the old result,
> > all users of the call pattern are marked `invalid'.
> > - equal to the old result, no entries need to be marked.
> > - more precise than the old result, callers are marked
> > as `suboptimal'.
> >
> > If any `suboptimal' answers are used in computing the new answer,
> > or there are any `suboptimal' answers in the SCC of the analysis
> > dependency graph containing the entry, the entry for the function
> > is marked as `suboptimal', otherwise it is marked as `optimal'.
>
> The algorithm here is not quite right -- it will never reach the
> `optimal' fixpoint, but instead will converge on a fixpoint in
> which all results are marked as `suboptimal'. You need to
> initially assume that results are optimal and then only
> mark them as suboptimal if they depend on something which
> has changed. (In other words, computing optimality itself
> needs to be a least fixpoint computation rather than a
> greatest fixpoint computation.)
Fixed.
> > Recompilation must proceed until there are no `invalid' or `fixpoint_invalid'
> > entries. Optionally, optimization can proceed until there are no new requests
> > or `suboptimal' answers.
>
> In the case where you are proceeding until there are no new requests,
> how do you ensure termination? What requirements are there on each
> compiler's analyses to ensure overall termination?
It's up to the analysis passes to generate a finite number of requests.
Simon.
--- README 2002/08/26 06:01:59 1.1
+++ README 2002/08/27 06:00:07
@@ -29,8 +29,12 @@
wants to perform.
Each analysis is described by a call pattern type and an
-answer pattern type. Call and answer patterns must form
-a partial order, and must be convertible to strings.
+answer pattern type. A call pattern describes the information
+known about the argument variables before analysing a call
+(by executing it in the abstract domain used by the analysis).
+An answer pattern describes the information known after analysing
+the call. Call and answer patterns must form a partial order, and
+must be convertible to strings.
Analysis database
=================
@@ -44,6 +48,11 @@
to ask that a specialized version be created on the next compilation
of the client module.
+There is currently no way to analyse higher-order or class method
+calls. It might be possible to analyse such calls where the set of
+possibly called predicates is known, but it is better to optimize away
+higher-order or class method calls where possible.
+
When compilation of a module is complete, the client should
call `analysis__write_analysis_files' to write out all
information collected during the compilation.
@@ -62,10 +71,11 @@
is strictly less precise than the old answer (moving towards to
correct answer). `fixpoint_invalid' entries may be used when analysing
a module, but code must not be generated which uses `fixpoint_invalid'
- results. In addition, code must not be generated when compiling a module
- in a strongly connected component of the analysis dependency graph which
- contains `fixpoint_invalid' entries. (Note that the method for handling
- least fixpoint analyses is not described in Nicholas Nethercote's thesis).
+ results (even indirectly). In addition, code must not be generated when
+ compiling a module in a strongly connected component of the analysis
+ dependency graph which contains `fixpoint_invalid' entries. (Note that
+ the method for handling least fixpoint analyses is not described in
+ Nicholas Nethercote's thesis).
* suboptimal - the entry does not depend on any `invalid' or
`fixpoint_invalid' entries, but may be improved by further
@@ -92,11 +102,11 @@
of entries in the database, then invokes the compiler's build tools
(through a typeclass method) to recompile modules in the correct order.
-If the interface of a function changes, all of its answers are
-marked as invalid, and the results of the functions it directly
-uses in the SCC of the analysis dependency graph containing it are
-reset to `top' (marked `suboptimal') for greatest fixpoint analyses,
-or `bottom' (marked `fixpoint_invalid') for least fixpoint analyses.
+If the implementation of a function changes, all of its answers are
+marked as invalid, and the results of the functions it directly uses
+in the SCC of the analysis dependency graph containing it are reset
+to `top' (marked `suboptimal') for greatest fixpoint analyses, or
+`bottom' (marked `fixpoint_invalid') for least fixpoint analyses.
This ensures that the new result for the function is not computed
using potentially invalid information.
@@ -110,27 +120,24 @@
- more precise than the old result, callers are marked
as `suboptimal'.
-If any `suboptimal' answers are used in computing the new answer,
-or there are any `suboptimal' answers in the SCC of the analysis
-dependency graph containing the entry, the entry for the function
-is marked as `suboptimal', otherwise it is marked as `optimal'.
-
For least fixpoint analyses, if the new answer is
- less precise than or incomparable with the old result,
all users of the call pattern are marked `invalid'.
- equal to the old result, no entries need to be marked.
- more precise than the old result, callers are marked
- as `suboptimal'.
+ as `fixpoint_invalid'.
-If any `fixpoint_invalid' answers are used in computing the new answer
-or there are any `fixpoint_invalid' answers in the strongly connected
-component of the analysis dependency graph containing the entry,
-the entry for the function is marked as `fixpoint_invalid', otherwise
-it is marked as `optimal'.
+The new answer itself will be marked as `optimal'. This isn't
+necessarily correct -- further recompilations may change its status
+to `fixpoint_invalid' or `suboptimal' (or `invalid' if there
+are source code changes).
Recompilation must proceed until there are no `invalid' or `fixpoint_invalid'
entries. Optionally, optimization can proceed until there are no new requests
or `suboptimal' answers.
+
+It the responsibility of the analysis implementor to ensure termination of
+the analysis process by not generating an infinite number of requests.
Granularity of dependencies
===========================
--- analysis.file.m 2002/08/26 06:26:04 1.2
+++ analysis.file.m 2002/08/26 15:26:28
@@ -1,5 +1,13 @@
%-----------------------------------------------------------------------------%
+% Copyright (C) 2002 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: analysis.file.m
+% Main author: stayl
+%
% An analysis file contains analysis results for a single module.
+%-----------------------------------------------------------------------------%
:- module analysis__file.
:- interface.
@@ -28,7 +36,7 @@
% The format of an analysis file is:
%
% version_number.
-% analysis_name(func_id, call_pattern, answer_pattern).
+% analysis_name(analysis_version, func_id, call_pattern, answer_pattern).
%-----------------------------------------------------------------------------%
:- import_module bool, exception, parser, term, term_io, varset.
@@ -47,32 +55,33 @@
`with_inst` parse_entry <= compiler(Compiler).
parse_result_entry(Compiler, Term, Results0, Results) :-
- (
- Term = term__functor(term__atom(AnalysisName),
- [FuncIdTerm, CallPatternTerm,
- AnswerPatternTerm], _),
- FuncIdTerm =
- term__functor(term__string(FuncId), [], _),
- CallPatternTerm = term__functor(
+ (
+ Term = term__functor(term__atom(AnalysisName),
+ [VersionNumberTerm, FuncIdTerm,
+ CallPatternTerm, AnswerPatternTerm], _),
+ FuncIdTerm = term__functor(term__string(FuncId), [], _),
+ CallPatternTerm = term__functor(
term__string(CallPatternString), [], _),
- AnswerPatternTerm = term__functor(
+ AnswerPatternTerm = term__functor(
term__string(AnswerPatternString), [], _),
- analysis_type(_ `with_type` unit(FuncInfo),
- _ `with_type` unit(Call),
+ analysis_type(_ `with_type` unit(FuncInfo), _ `with_type` unit(Call),
_ `with_type` unit(Answer)) =
analyses(Compiler, AnalysisName),
- CallPattern = from_string(CallPatternString)
- `with_type` Call,
- AnswerPattern = from_string(AnswerPatternString)
- `with_type` Answer
+ CallPattern = from_string(CallPatternString) `with_type` Call,
+ AnswerPattern = from_string(AnswerPatternString) `with_type` Answer
+ ->
+ (
+ VersionNumber = analysis_version_number(
+ _ `with_type` FuncInfo, _ `with_type` Call,
+ _ `with_type` Answer),
+ VersionNumberTerm = term__functor(
+ term__integer(VersionNumber), [], _)
->
- Result = 'new analysis_result'(unit1 `with_type` unit(FuncInfo),
+ Result = 'new analysis_result'(
+ unit1 `with_type` unit(FuncInfo),
CallPattern, AnswerPattern),
- (
- AnalysisResults0 = map__search(Results0,
- AnalysisName)
- ->
+ ( AnalysisResults0 = map__search(Results0, AnalysisName) ->
AnalysisResults1 = AnalysisResults0
;
AnalysisResults1 = map__init
@@ -88,9 +97,13 @@
Results = map__set(Results0, AnalysisName,
map__set(AnalysisResults1,
FuncId, FuncResults))
- ;
- throw(invalid_analysis_file)
- ).
+ ;
+ % Ignore results with an out-of-date version number.
+ Results = Results0
+ )
+ ;
+ throw(invalid_analysis_file)
+ ).
read_module_analysis_requests(Info, ModuleId, ModuleRequests, !IO) :-
read_analysis_file(Info ^ compiler, ModuleId, ".request",
@@ -101,46 +114,54 @@
`with_type` parse_entry(module_analysis_map(analysis_request))
`with_inst` parse_entry <= compiler(Compiler).
-parse_request_entry(Compiler, Term, Results0, Results) :-
- (
- Term = term__functor(term__atom(AnalysisName),
- [FuncIdTerm, CallPatternTerm], _),
- FuncIdTerm =
- term__functor(term__string(FuncId), [], _),
- CallPatternTerm = term__functor(
- term__string(CallPatternString), [], _),
- analysis_type(_ `with_type` unit(FuncInfo),
- _ `with_type` unit(Call), _) =
- analyses(Compiler, AnalysisName),
-
- CallPattern = from_string(CallPatternString)
- `with_type` Call
+parse_request_entry(Compiler, Term, Requests0, Requests) :-
+ (
+ Term = term__functor(term__atom(AnalysisName),
+ [VersionNumberTerm, FuncIdTerm, CallPatternTerm], _),
+ FuncIdTerm = term__functor(term__string(FuncId), [], _),
+ CallPatternTerm = term__functor(
+ term__string(CallPatternString), [], _),
+ analysis_type(_ `with_type` unit(FuncInfo),
+ _ `with_type` unit(Call), _ `with_type` unit(Answer)) =
+ analyses(Compiler, AnalysisName),
+ CallPattern = from_string(CallPatternString) `with_type` Call
+ ->
+ (
+ VersionNumber = analysis_version_number(
+ _ `with_type` FuncInfo, _ `with_type` Call,
+ _ `with_type` Answer),
+ VersionNumberTerm = term__functor(
+ term__integer(VersionNumber), [], _)
->
Result = 'new analysis_request'(
unit1 `with_type` unit(FuncInfo),
CallPattern),
(
- AnalysisResults0 = map__search(Results0,
+ AnalysisRequests0 = map__search(Requests0,
AnalysisName)
->
- AnalysisResults1 = AnalysisResults0
+ AnalysisRequests1 = AnalysisRequests0
;
- AnalysisResults1 = map__init
+ AnalysisRequests1 = map__init
),
(
- FuncResults0 = map__search(AnalysisResults1,
+ FuncRequests0 = map__search(AnalysisRequests1,
FuncId)
->
- FuncResults = [Result | FuncResults0]
+ FuncRequests = [Result | FuncRequests0]
;
- FuncResults = [Result]
+ FuncRequests = [Result]
),
- Results = map__set(Results0, AnalysisName,
- map__set(AnalysisResults1,
- FuncId, FuncResults))
- ;
- throw(invalid_analysis_file)
- ).
+ Requests = map__set(Requests0, AnalysisName,
+ map__set(AnalysisRequests1,
+ FuncId, FuncRequests))
+ ;
+ % Ignore requests with an out-of-date version number.
+ Requests = Requests0
+ )
+ ;
+ throw(invalid_analysis_file)
+ ).
:- type parse_entry(T) == pred(term, T, T).
:- inst parse_entry == (pred(in, in, out) is det).
@@ -233,7 +254,8 @@
( AppendResult = ok(AppendStream) ->
io__set_output_stream(AppendStream,
OldOutputStream, !IO),
- write_analysis_entries(write_request_entry,
+ write_analysis_entries(
+ write_request_entry(Info ^ compiler),
ModuleRequests, !IO),
io__set_output_stream(OldOutputStream, _, !IO),
io__close_output(AppendStream, !IO),
@@ -249,7 +271,8 @@
),
( Appended = no ->
write_analysis_file(Info ^ compiler, ModuleId, ".request",
- write_request_entry, ModuleRequests, !IO)
+ write_request_entry(Info ^ compiler),
+ ModuleRequests, !IO)
;
true
).
@@ -258,20 +281,40 @@
`with_inst` write_entry.
write_result_entry(AnalysisName, FuncId,
- analysis_result(_, Call, Answer), !IO) :-
+ analysis_result(_ `with_type` unit(FuncInfo), Call, Answer),
+ !IO) :-
+ VersionNumber = analysis_version_number(_ `with_type` FuncInfo,
+ Call, Answer),
term_io__write_term_nl(varset__init `with_type` varset,
functor(atom(AnalysisName), [
+ functor(integer(VersionNumber), [], context_init),
functor(string(FuncId), [], context_init),
functor(string(to_string(Call)), [], context_init),
functor(string(to_string(Answer)), [], context_init)
], context_init), !IO).
-:- pred write_request_entry `with_type` write_entry(analysis_request)
- `with_inst` write_entry.
+:- pred write_request_entry(Compiler::in)
+ `with_type` write_entry(analysis_request)
+ `with_inst` write_entry <= compiler(Compiler).
-write_request_entry(AnalysisName, FuncId, analysis_request(_, Call), !IO) :-
+write_request_entry(Compiler, AnalysisName, FuncId,
+ analysis_request(_, Call), !IO) :-
+ (
+ analysis_type(_ `with_type` unit(FuncInfo),
+ _ `with_type` unit(Call),
+ _ `with_type` unit(Answer)) =
+ analyses(Compiler, AnalysisName)
+ ->
+ VersionNumber = analysis_version_number(
+ _ `with_type` FuncInfo, _ `with_type` Call,
+ _ `with_type` Answer)
+ ;
+ error("write_request_entry: unknown analysis type")
+
+ ),
term_io__write_term_nl(varset__init `with_type` varset,
functor(atom(AnalysisName), [
+ functor(integer(VersionNumber), [], context_init),
functor(string(FuncId), [], context_init),
functor(string(to_string(Call)), [], context_init)
], context_init), !IO).
--- analysis.m 2002/08/26 06:26:04 1.2
+++ analysis.m 2002/08/27 05:45:35
@@ -1,3 +1,19 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2002 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: analysis.m
+% Main author: stayl
+%
+% An inter-module analysis framework, as described in
+%
+% Nicholas Nethercote. The Analysis Framework of HAL,
+% Chapter 7: Inter-module Analysis, Master's Thesis,
+% University of Melbourne, September 2001, revised April 2002.
+% <http://www.cl.cam.ac.uk/~njn25/pubs/masters2001.ps.gz>.
+%
+%-----------------------------------------------------------------------------%
:- module analysis.
:- interface.
@@ -38,6 +54,12 @@
[
func analysis_name(FuncInfo::unused, Call::unused, Answer::unused) =
(analysis_name::out) is det,
+
+ % The version number should be changed when the Call or Answer
+ % types are changed so that results which use the old types
+ % can be discarded.
+ func analysis_version_number(FuncInfo::unused, Call::unused,
+ Answer::unused) = (int::out) is det,
func preferred_fixpoint_type(FuncInfo::in,
Call::unused, Answer::unused) =
--- mer_analysis.m 2002/07/26 13:53:37 1.1
+++ mer_analysis.m 2002/08/26 14:06:19
@@ -1,3 +1,14 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2002 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: mer_analysis.m
+% Main author: stayl
+%
+% This module exists to make the name of the inter-module analysis
+% library match the usual naming convention.
+%-----------------------------------------------------------------------------%
:- module mer_analysis.
:- import_module analysis.
--------------------------------------------------------------------------
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