[m-dev.] for review: `possible' alias analysis stage

Nancy Mazur Nancy.Mazur at cs.kuleuven.ac.be
Fri Mar 10 20:38:00 AEDT 2000


> > Is this a rationale enough? Or should it be explained more 
> > thoroughly? 
> 
> Well, the Mercury compiler is already quite capable of
> not reusing the top-level list cell in the example above ;-)

it was a small example. 
In attachment I've included a file that Mission Critical once gave us, 
and for which explicit di/uo annotations are written, but for which
our liveness analysis can automatically derive them. That wouldn't
have been possible with the alias branch (as the alias branch 
needs those di/uo's), and wouldn't have been possible without 
possible aliasing information. 

Definite aliasing is (in the liveness analysis context) definitely 
not enough for deciding whether some structures may be reused or not. 
While there might be no definitie alias between some variable X and
some variable Y, you cannot safely decide that one of those may be
reused at some point. Only if you're sure that there will never ever
be an alias between those two, you can safely make the decision. In
order to know this 'never ever', possible aliasing information is
needed.

> It would help more to have examples of where possible
> aliasing information helps to reuse things that could not
> otherwise be reused, using just the analyses that
> Mercury compiler already performs (plus definite aliasing,
> which is currently only supported on the `alias' branch).

with the example in the attachment, you will probably argue that
the alias-branch does allow the reuse. But the only reason why it'll
work on that file, is that some kind programmer provided the di/uo's.

> If most of the reuse that we want to do can be done using just definite
> aliasing, then it may not be worth the additional complexity of possible
> aliasing analysis.

As said above, possible aliasing is essential for liveness analysis. 
Now I do admit that during the development of some program, 
extensive reuse-analysis might not be worth the trouble, but in
my opinion it is certainly worth the trouble to fully analyse the
final program, and releive the programmer of spending hours on 
tedious (now don't tell me they're not tedious) di/uo annotations of
any kind. 

Nancy

-------------- next part --------------
%------------------------
% $Id: frm_counters.m,v 1.1 1997/11/21 14:06:06 ddw Exp $
%------------------------

:-module frm_counters.

:-interface.

:-import_module io.

% types, abstract decl.

:- pred main(io__state::di, io__state::uo) is det.
%:- pred main(io__state::di, io__state::uo) is cc_multi.

% pred declaractions

:-implementation.

:-import_module int,list,require,string,char,benchmarking.

% statistics
:- type stat ---> stat(int,int).

 
main -->
        heap_expand(16000), /* start with a 16 M heap */
        io__command_line_arguments(Files),
        report_stats,
        (   
                {Files= [File]}
         ->
                io__open_input(File,Res),
                doit(File,Res)
         ;
                {Files= []}
         ->
                {true}
         ;
                io__print("Only one file arg expected")),
        report_stats.

:-pred doit(string::in,io:res((io:input_stream))::in,
            io__state::di, io__state::uo).
doit(File,ok(Stream))-->
        {string:format("Opened file '%s'\n",[s(File)],S)},io:print(S),
        process_counters(Stream,stat(0,0),StatsOut),
        io__close_input(Stream),
        io__print("Statistics:"),
        io__print(StatsOut),io:nl.
doit(File,error(Code))-->
        {string:format("Could not open file '%s'\n",[s(File)],S)},io:print(S),
        {io:error_message(Code,Msg)},
        io:print(Msg).

%:-pred process_counters(io:input_stream::in,stat::in,stat::out,
%                       io__state::di, io__state::uo).
:- pred process_counters((io:input_stream), (frm_counters:stat), (frm_counters:stat), (io:state), (io:state)).
:- mode process_counters(in, di, uo, di, uo).
process_counters(Stream,StatsIn,StatsOut)-->
        io:read_line(Stream,Res),
        process_lines(Stream,Res,StatsIn,StatsOut).

% identifies a person (sirocco number)
:-type ident == string.
% counters
:-type counters ---> cnt(int,int,int,int,int,
                         int,int,int,int,int,
                         int,int,int,int,int,
                         int,int,int,int,int).
:-type line_err ---> goodline(ident,counters);badline.

:- pred process_lines((io:input_stream), (io:result((list:list(character)))), (frm_counters:stat), (frm_counters:stat), (io:state), (io:state)).
:- mode process_lines(in, in, di, uo, di, uo).
process_lines(_S,eof,StatsIn,StatsOut)-->
        {StatsOut=StatsIn}.
process_lines(S,ok(Line),stat(Lines,Errs),StatsOut)-->
        { process_line(Line,Res) },
        update_errs(Res,Errs,ErrsOut),
        {Lines1 is Lines +1},
        process_counters(S,stat(Lines1,ErrsOut),StatsOut).
process_lines(S,error(Code),StatsIn,StatsOut)-->
        {io:error_message(Code,Msg)},
        io:print(Msg),io:nl,
        process_counters(S,StatsIn,StatsOut).

:- pred update_errs((frm_counters:line_err), int, int, (io:state), (io:state)).
:- mode update_errs(di, di, uo, di, uo).
:- mode update_errs(in, di, uo, di, uo).
update_errs(goodline(ID,Counters),Err,Err)-->
        io__print(ID),io__print(":"),print_counters(Counters),io__print("\n").
update_errs(badline,Err,Err1,IOS,IOS):-Err1 is Err+1.

%:-pred process_line(list(char)::in,line_err::out).
:- pred process_line((list:list(character)), (frm_counters:line_err)).
:- mode process_line(in, out).
process_line(Line,Res):-
        ( analyze_line(ID,cnt(0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0),
                       Counters,Line,[]) 
         ->
          Res=goodline(ID,Counters)
         ;
          Res=badline).


:- pred print_counters((frm_counters:counters), (io:state), (io:state)).
:- mode print_counters(di, di, uo).
:- mode print_counters(in, di, uo).
print_counters(cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                   CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ))-->
        print_one('0',C0,1),
        print_one('1',C1,1),
        print_one('2',C2,1),
        print_one('3',C3,1),
        print_one('4',C4,1),
        print_one('5',C5,1),
        print_one('6',C6,1),
        print_one('7',C7,1),
        print_one('8',C8,1),
        print_one('9',C9,1),
        print_one('A',CA,1),
        print_one('B',CB,1),
        print_one('C',CC,1),
        print_one('D',CD,1),
        print_one('E',CE,1),
        print_one('F',CF,1),
        print_one('G',CG,1),
        print_one('H',CH,1),
        print_one('I',CI,1),
        print_one('J',CJ,0).

:- pred print_one(T, int, int, (io:state), (io:state)).
:- mode print_one(di, in, di, di, uo).
:- mode print_one(di, di, di, di, uo).
print_one(Key,Value,Sep)-->
        ( {Value = 0} 
         -> []
         ;
          io__print(Key),io__print(":"),io__print(Value),
          ({Sep=1}->io__print(",");{true})).

:- pred update_counters(character, (frm_counters:counters), (frm_counters:counters)).
:- mode update_counters(in, di, uo).
update_counters('0',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0+1,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('1',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1+1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('2',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2+1,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('3',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3+1,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('4',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4+1,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('5',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5+1,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('6',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6+1,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('7',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7+1,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('8',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8+1,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('9',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9+1,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('A',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA+1,CB,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('B',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB+1,CC,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('C',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC+1,CD,CE,CF,CG,CH,CI,CJ)).
update_counters('D',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD+1,CE,CF,CG,CH,CI,CJ)).
update_counters('E',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE+1,CF,CG,CH,CI,CJ)).
update_counters('F',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF+1,CG,CH,CI,CJ)).
update_counters('G',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG+1,CH,CI,CJ)).
update_counters('H',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH+1,CI,CJ)).
update_counters('I',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI+1,CJ)).
update_counters('J',cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ),
                cnt(C0,C1,C2,C3,C4,C5,C6,C7,C8,C9,
                        CA,CB,CC,CD,CE,CF,CG,CH,CI,CJ+1)).
update_counters('-',C,C).

%:-pred dummy(string,counters,counters,list(char),list(char)).
:- pred dummy(string, T3, T3, (list:list(character)), (list:list(character))).
dummy("DUMMY",Ci,Co)-->
        (  ['\n']
         ->
           {true,Ci=Co}
         ;
           [_],dummy(_,Ci,Co)).
   
analyze_line(ID,CountersIn,CountersOut)-->
        prefix, 
        sirocco(ID),
        brol,   /* dummy(_ID,CountersIn,CountersOut). */
        num_counters(N),
        counters(N,CountersIn,CountersOut),
        suffix. 

:- pred prefix((list:list(T)), (list:list(T))).
:- mode prefix(in, out).
prefix--> skip(2).
:- pred suffix((list:list(character)), (list:list(character))).
:- mode suffix(in, di).
suffix--> ['\n'].

% decl needed for type inference to work elsewhere
:-pred sirocco(string::out,list(char)::in,list(char)::out).
sirocco(ID)-->
        [C1,C2,C3,C4,C5,C6,C7,C8],
        {string__from_char_list([C1,C2,C3,C4,C5,C6,C7,C8],ID)}.

% skip next N input chars
:- pred skip(int, (list:list(T)), (list:list(T))).
:- mode skip(di, in, out).
skip(N)-->
        (  {N=0}
         -> []
         ; [_],skip(N-1)).

% :- pred brol((list:list(T)), (list:list(T))).

:- pred brol((list:list(T)), (list:list(T))).
:- mode brol(in, out).
brol--> skip(40). 

% get the number of counters taht follow. This number is 3 digits.
:- pred num_counters(int, (list:list(character)), (list:list(character))).
:- mode num_counters(out, in, out).
num_counters(N)-->
        [N1,N2,N3],{char:is_digit(N1),char:is_digit(N2),char:is_digit(N3)},
        {string__from_char_list([N1,N2,N3],NS),
         string__to_int(NS,N)}.


:- pred counters(int, (frm_counters:counters), (frm_counters:counters),
                 (list:list(character)), (list:list(character))).
:- mode counters(in, di, uo, in, out).
counters(N,CountersIn,CountersOut)-->
        (    {N=0} 
         ->
             [], {CountersOut=CountersIn}
         ;
             [_Cat1,_Cat2,_Y1,_Y2,_M1,_M2,Type],
             {update_counters(Type,CountersIn,Counters0),
              N1 is N-1},
             counters(N1,Counters0,CountersOut)).

:-pred heap_expand(int::di,io__state::di,io__state::uo) is det.
:-pragma c_code(heap_expand(Size::di,IOI::di,IOO::uo),
                may_call_mercury,
                "while(Size>0){
                    GC_expand_hp(min(8000,Size)*1024);
                    Size=Size-8000;
                 }
                 IOO=IOI;").

:-end_module frm_counters.



More information about the developers mailing list