%
          %   This file contains the source code for first optimization,  
          %   which implements the algorithm to eliminate backtracking for 
          %   non-interacting processes.
          %

:- import updat/1 from updates.
:- import append/3 from basics.

% define directive opt1_trans

opt1_trans(File_ctr) :-
                in_opt(File_ctr,File1),
                see(File1),
                remove_upd,
               insert_upd(Preds),
                remove_graph,
                opt_read_and_create_graph(File1),
                seen,
                see(File1),
                out_opt(File_ctr,FileOut),
                unix('rm -f FileOut 2>/dev/null', R1),
                tell(FileOut),
                opt_read_and_compile(File1,FileOut),
                seen, told.

% parse rules from object file repeatedly
% to create dependency graph

opt_read_and_create_graph(FileIn) :-
        read(Term),
        (
        (Term == end_of_file) -> true
        ;
        opt_read_rule(Term,FileIn),
        opt_read_and_create_graph(FileIn)  ).

% read transaction base object file
opt_read_and_compile(FileIn,FileOut) :-
        read(Term),
        (
        (Term == end_of_file) -> true
        ;
        opt_read_and_write_rule(Term,FileIn,FileOut),
        opt_read_and_compile(FileIn,FileOut)  ).

% translation of a transaction clause
opt_read_rule(':-'(trans(Lhs),Rhs),_) :-
        Lhs =..Lname,
        Lname = [Name|_],
        insert_edge(Name, Rhs).

opt_read_rule(':-'(Lhs,Rhs),_).

% write optimized transaction rules
opt_read_and_write_rule(':-'(trans(Lhs),Rhs),_,_) :-
        write(trans(Lhs)),
        write(' :-  '),
        remove_dep,
        optI(Rhs, PRhs),
        write(PRhs),
        write('.'), nl.

opt_read_and_write_rule(':-'(Lhs,Rhs),_,_) :-
        write(Lhs),
        write(' :-  '),
        write(Rhs),
        write('.'), nl.

% optimization is performed only on isolated processes
optI(isolate(P), isolate(R)) :- optN(P, R).
optI(isolate1(P), isolate1(R)) :- optN(P, R).
optI(seq(L), seq(L1)) :- optI_list(L, L1).
optI(conc(L), conc(L1)) :- optI_list(L, L1).
optI(P, P).

optN(isolate(P), isolate(R)) :- optN(P, R).
optN(isolate1(P), isolate1(R)) :- optN(P, R).
optN(seq(L), seq(L1)) :- optN_list(L, L1).
optN(conc(L), conc(L1)) :- check_interact(L),
                           dep(1),
                           optI_list(L, L1).
optN(conc(L), conc1(L1)) :- optN_list(L, L1).
optN(P, P).

% check for interaction
check_interact([]).
check_interact(L) :- L = [Head|Tail],
                     P = Head,
                     remove_dep,
                     check_tail(P, Tail),
                     not(dep(1)),
                     check_interact(Tail).
check_interact(L) :- dep(1).

check_tail(P, []).
check_tail(P, Tail) :- Tail = [H1|Tail1],
                       (interact(P, H1),
                        not(dep(1)),
                        assert(dep(1))
                        ;
                        check_tail(P, Tail1)).

optI_list([], []).
optI_list(L, L1) :- L = [H0|Tail0],
                    L1 = [H1|Tail1],
                    optI(H0, H1),
                    optI_list(Tail0, Tail1).

optN_list([], []).
optN_list(L, L1) :- L = [H0|Tail0],
                    L1 = [H1|Tail1],
                    optN(H0, H1),
                    optN_list(Tail0, Tail1).

% build dependency graph
insert_edge(Name, Rhs) :- appears(Rhs, X),
                          not(edge(Name, X)),
                          assert(edge(Name, X)),
                          fail.

insert_edge(Name, Rhs).

insert_upd(Preds) :- updat(Preds),
                     Preds =..Lpreds,
                     Lpreds = [Name|_],
                     assert(upd(Name)), fail.

insert_upd(Preds).

% edges between predicate in Head of rules
% and predicates or elementary op in rule boby
appears(conc(L), X) :- L = [Head|_],
                       appears(Head, X).

appears(conc(L), X) :- L = [_|Tail],
                       appears(conc(Tail), X).

appears(seq(L), X) :- L = [Head|_],
                       appears(Head, X).

appears(seq(L), X) :- L = [_|Tail],
                      appears(seq(Tail), X).

appears(isolate1(E), X) :- !, appears(E, X).

appears(isolate(E), X) :- !, appears(E, X).

appears(ins(X), Y) :- !, X =..Pred,
                      Pred = [Name|_],
                      Y = ins(Name).

appears(del(X), Y) :- !, X =..Pred,
                      Pred = [Name|_],
                      Y = del(Name).

appears(P, Y) :- P =..Pred,
                 Pred = [Name|_],
                 not(Name = conc),
                 not(Name = seq),
                 not(Name = isolate),
                 not(Name = isolate1),
                 atom(Name),
                 Y = Name.

% check if nodes in dependency graph are connected
reachable(P, P).
reachable(P, Q) :- edge(P, Q).
reachable(P, Q) :- edge(P, R), reachable(R, Q).

% definition for query sets
qref(Q, Q) :- Q =..Pred,
              Pred = [Name|_],
              upd(Name).
qref(E, Q) :- appears(E, P), reachable(P, Q), upd(Q).

% definition for insert sets
iref(ins(Q), Q).
iref(E, Q) :- appears(E, P), reachable(P, ins(Q)).

% definition for delete sets
dref(del(Q), Q).
dref(E, Q) :- appears(E, P), reachable(P, del(Q)).

% definition of interaction in the graph
interact1(P, Q) :- qref(P, B), iref(Q, B).
interact1(P, Q) :- qref(P, B), dref(Q, B).
interact1(P, Q) :- iref(P, B), dref(Q, B).

interact(P, Q) :- interact1(P, Q).
interact(P, Q) :- interact1(Q, P).

independent(P, Q) :- not(interact(P, Q)).

add_isolate([], []).
add_isolate(L, L1) :- L = [H0|Tail0],
                      L1 = [H1|Tail1],
                      H1 = isolate(H0),
                      add_isolate(Tail0, Tail1).

% remove any work tuples before starting optimization
remove_upd :- retract(upd(X)), fail.
remove_upd.

% delete dependency graph
remove_graph :- retract(edge(X, Y)), fail.
remove_graph.

remove_dep :- retract(dep(1)).
remove_dep.

remove(K) :- retract(dep(K)).
remove(K).

% create object file name used as input
in_opt(FileIn,FileOut) :-
        name(FileIn,NameIn),
        append(NameIn,".ctr.o",NameOut),
        name(FileOut,NameOut).

% create optimized file name used as output
out_opt(FileIn,FileOut) :-
        name(FileIn,NameIn),
        append(NameIn,".opt1.o",NameOut),
        name(FileOut,NameOut).

opt_insert_file(FileName) :-
        seeing(X),
        see(FileName),
        opt_read_and_add_line,
        see(X).

opt_read_and_add_line :-
        read(Line),
        (
        (Line == end_of_file)   -> true
        ;
        assert(Line),
        opt_read_and_add_line ).

edge(dummy, dummy) :- fail.
modifiable(dummy) :- fail.
upd(dummy) :- fail.
dep(dummy) :- fail.