Skip to content

Instantly share code, notes, and snippets.

@hsk
Last active August 17, 2020 07:22
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save hsk/e3a7054f52b5854899cdd2414454fbf1 to your computer and use it in GitHub Desktop.
Save hsk/e3a7054f52b5854899cdd2414454fbf1 to your computer and use it in GitHub Desktop.
Reaching Definition
% https://qiita.com/fukkun/items/05160e8dae0e15ae201e
reset:- nb_setval(cnt,0),retractall(tmp(_,_)).
genid(C1):- nb_getval(cnt,C),C1 is C+1,nb_setval(cnt,C1).
gentmp(T):- genid(C),atomic_list_concat([t,C],T).
gentmp(E,T):- tmp(E,T).
gentmp(E,T):- gentmp(T),assert(tmp(E,T)).
tran([N:(X=A+B)|C],[N:(T=A+B),NA:(X=T)|C_]) :- gentmp(A+B,T),atom_concat(N,*,NA),tran(C,C_).
tran([N:(X=A-B)|C],[N:(T=A-B),NA:(X=T)|C_]) :- gentmp(A-B,T),atom_concat(N,*,NA),tran(C,C_).
tran([N:I|C],[N:I|C_]):- tran(C,C_).
tran([],[]).
kill(C,Kill) :- maplist(kill1,C,Kill).
kill1(N:(T=_),N:K) :- findall(E,(tmp(E,_),E=..[_|P],member(T,P)),K).
kill1(N:_,N:[]).
gen(C,Kill,Gen) :- maplist(gen1,C,Kill,Gen).
gen1(N:(T=E),N:K,N:V):- tmp(E,T),subtract([E],K,V).
gen1(N:_,N:_,N:[]).
pred([],[]).
pred([N:if(_,goto(A),goto(B))|C],[N:A,N:B|P]):-pred(C,P).
pred([N:goto(A)|C],[N:A|P]):-pred(C,P).
pred([(N:_)|C],[(N:A)|P]):-npred(A:_,C),pred(C,P).
pred([_],[]).
npred(N:A,[N:A|_]).
allE(AllE):- findall(E,tmp(E,_),Es),list_to_set(Es,AllE).
init(C,I>O):- allE(AllE),maplist(init1(AllE),C,I,O).
init1(AllE,1:_,1:[],1:AllE).
init1(AllE,N:_,N:AllE,N:AllE).
cse(C,C1,C_) :-
reset,tran(C,C1),writeln(C1),
kill(C1,Kill),
gen(C1,Kill,Gen),writeln(gen:Gen),writeln(kill:Kill),!,
init(C1,I>O),!,
pred(C1,Pred),
cse0(Pred,Gen,Kill,I>O,I_>O_),writeln(in:I_),writeln(out:O_),
maplist(rm,C1,I_,C2),rmnop(C2,C_).
cse0(Pred,Gen,Kill,IO,IO_) :- cse1(Pred,Gen,Kill,IO,IO1),(IO=IO1->IO_=IO1;cse0(Pred,Gen,Kill,IO1,IO_)).
cse1(Pred,Gen,Kill,I>O,I_>O_):- foldl(cse2(Pred,Kill),Gen,I>O,I_>O_).
%cse2(_,_,NA:_,I>O,I>O):- atom(NA).
cse2(Pred,Kill,N:G,I>O,I_>O_):- cse3(N,O,Pred,I,I_),member(N:K,Kill),cse4(N,G,I_,K,O,O_).
cse3(N,O,Pred,I,I_) :- select(N:V,I,N:V_,I_),findall(OP,(member(P:N,Pred),member(P:OP,O)),Os),foldl(intersection,Os,V,V_).
cse4(N,G,I,K,O,O_) :- member(N:IV,I),select(N:_,O,N:V_,O_),subtract(IV,K,IK),union(G,IK,V_).
rm(N:(_=E),N:I,N:nop):-member(E,I).
rm(N:C1,N:_,N:C1).
rmnop(C,C_):-foldl(rmnop1(C),C,C_,[]).
rmnop1(_,_:nop,L,L).
rmnop1(C,N:goto(I),[N:goto(I_)|L],L):- rmnopnext(C,I,I_).
rmnop1(C,N:if(E,goto(A),goto(B)),[N:if(E,goto(A_),goto(B_))|L],L):-
rmnopnext(C,A,A_),rmnopnext(C,B,B_).
rmnop1(_,N:I,[N:I|L],L).
rmnopnext([N:nop|C],N,N_):- !,rmnopnext2(C,N_).
rmnopnext([N:_|_],N,N).
rmnopnext([_|C],N,N_):-rmnopnext(C,N,N_).
rmnopnext2([_:nop|C],N_):- rmnopnext2(C,N_).
rmnopnext2([N:_|_],N).
:- cse([
1: (x = a + b),
2: if(a < 5,goto(3),goto(5)),
3: (y = a + b),
4: goto(8),
5: (a = 10),
6: (x = a - b),
7: goto(8),
8: (z = a + b)
],C,C_),!,C=[
1 : (t1 = a + b),
'1*': (x = t1),
2 : if(a < 5,goto(3),goto(5)),
3 : (t1 = a + b),
'3*': (y = t1),
4 : goto(8),
5 : (a = 10),
6 : (t2 = a - b),
'6*': (x = t2),
7 : goto(8),
8 : (t1 = a + b),
'8*': (z = t1)
],C_=[
1 :(t1=a+b),
'1*':(x=t1),
2 :if(a<5,goto('3*'),goto(5)),
'3*':(y=t1),
4 :goto(8),
5 :(a=10),
6 :(t2=a-b),
'6*':(x=t2),
7 :goto(8),
8 :(t1=a+b),
'8*':(z=t1)
].
:-halt.
% https://qiita.com/fukkun/items/f25b11e5a4dd39d994ef
%a ::= i | x.
%s ::= if(a<a,goto(i),goto(i))|x=a|x=a+a|goto(i).
%p ::= list(i:s).
pred([],[]).
pred([N:if(_,goto(A),goto(B))|C],[N:A,N:B|P]):-pred(C,P).
pred([N:goto(A)|C],[N:A|P]):-pred(C,P).
pred([(N:_),(A:I)|C],[(N:A)|P]):-pred([A:I|C],P).
pred([_],[]).
gen(C,Gen) :- findall(N:V,(member(N:I,C),gen1(I,V)),Gen).
gen1(_=A+B,[A,B]):-!.
gen1(_=A*B,[A,B]):-!.
gen1(if(A<B,_,_),[A,B]):-!.
gen1(_,[]).
kill(C,Kill) :- findall(N:K,(member(N:I,C),(I=(T=_)->K=[T];K=[])),Kill).
init(C,I,O):- maplist(init1,C,I,O).
init1(N:_,N:[],N:[]).
dce(C,C_):-pred(C,Pred),gen(C,Gen),kill(C,Kill),init(C,I,O),
writeln(pred:Pred),
writeln(gen:Gen),
writeln(kill:Kill),
writeln(in:I),
writeln(out:O),!,
dce0(Pred,Gen,Kill,I>O,_>O_),
writeln(out_:O_),
maplist(rm,C,O_,C1),rmnop(C1,C_).
rm(N:(A=I),N:O,N:nop):- \+member(A,O),integer(I).
rm(N:I,_,N:I).
rmnop(C,C_):-foldl(rmnop1(C),C,C_,[]).
rmnop1(_,_:nop,L,L).
rmnop1(C,N:goto(I),[N:goto(I_)|L],L):- rmnopnext(C,I,I_).
rmnop1(C,N:if(E,goto(A),goto(B)),[N:if(E,goto(A_),goto(B_))|L],L):-
rmnopnext(C,A,A_),rmnopnext(C,B,B_).
rmnop1(_,N:I,[N:I|L],L).
rmnopnext([N:nop|C],N,N_):- !,rmnopnext2(C,N_).
rmnopnext([N:_|_],N,N).
rmnopnext([_|C],N,N_):-rmnopnext(C,N,N_).
rmnopnext2([_:nop|C],N_):- rmnopnext2(C,N_).
rmnopnext2([N:_|_],N).
dce0(Pred,Gen,Kill,IO,IO_):-
dce1(Pred,Gen,Kill,IO,IO1),!,(IO=IO1->IO_=IO;dce0(Pred,Gen,Kill,IO1,IO_)).
dce1(_,[],[],In>[],In>[]).
dce1(Pred,[(N:G)|Gen],[(N:K)|Kill],In>[(N:O)|Out],In_>[(N:O_)|Out_]):-
dce1(Pred,Gen,Kill,In>Out,In1>Out_),
findall(I1,(member(N:S,Pred),member(S:I1,In1)),O1),
foldl(union,O1,O,O_),
subtract(O_,K,OK),union(G,OK,IV),select(N:_,In1,N:IV,In_).
:- dce([
1:(a=1),
2:(b=2),
3:if(v<a,goto(4),goto(6)),
4:(x=a+b),
5:goto(9),
6:(a=10),
7:(b=5),
8:goto(9),
9:(a=100),
10:(x=a*b),
11:(b=20)
],O_),
O_=[
1:(a=1),
2:(b=2),
3:if(v<a,goto(4),goto(7)),
4:(x=a+b),
5:goto(9),
7:(b=5),
8:goto(9),
9:(a=100),
10:(x=a*b)
].
:- halt.
/*
https://qiita.com/fukkun/items/39c40abb1e9e5e53b7d7
a ::= i | x.
s ::= if(a<a,goto(i),goto(i))|x=a|x=a+a|goto(i).
p ::= list(i:s).
*/
pred([],[]).
pred([N:if(_,goto(A),goto(B))|C],[N:A,N:B|P]):-pred(C,P).
pred([N:goto(A)|C],[N:A|P]):-pred(C,P).
pred([(N:_),(A:I)|C],[(N:A)|P]):-pred([A:I|C],P).
pred([_],[]).
def(C,T,Def) :- findall(N,member(N:(T=_),C),Def).
gen(C,Gen) :- findall(N:V,(member(N:I,C),(I=(_=_)->V=[N];V=[])),Gen).
kill(C,Kill) :- findall(N:K,(member(N:I,C),(I=(T=_)->def(C,T,DT),subtract(DT,[N],K);K=[])),Kill).
reach(C,I_>O_):-pred(C,Pred),gen(C,Gen),kill(C,Kill),rinit(C,I>O),r0(C,Pred,Gen,Kill,I>O,I_>O_).
rinit(C,I>O):- findall(N:[],member(N:_,C),I),findall(N:[],member(N:_,C),O).
r0(C,Pred,Gen,Kill,I>O,I_>O_):- r1(Pred,Gen,Kill,C,I>O,I1>O1),(I=I1,O=O1->I_=I,O_=O1;r0(C,Pred,Gen,Kill,I1>O1,I_>O_)).
r1(Pred,Gen,Kill,[N:_|C],I>O,I_>O_):-
findall(P,member(P:N,Pred),Ps),foldl(r2(N),Ps,I>O,I1>O),member(N:IV,I1),member(N:KV,Kill),member(N:GV,Gen),
subtract(IV,KV,IKV),union(GV,IKV,OV),select(N:_,O,N:OV,O1),
r1(Pred,Gen,Kill,C,I1>O1,I_>O_).
r1(_,_,_,[],I>O,I>O).
r2(N,P,I>O,I1>O):-select(N:IV,I,N:IV1,I1),member(P:OV,O),union(IV,OV,IV1).
reach_def(C,C2):-reach(C,I>_),maplist(rd(C),I,C,C2).
rd0(C,I,A,As):- findall(VI,(member(NI,I),member(NI:(A=VI),C)),As),!.
rdr(C,I,A,A_):-rd0(C,I,A,[A_]);A_=A.
rd(C,_:I,N:(V=A+B),N:(V=A_+B_)) :- rdr(C,I,A,A_),rdr(C,I,B,B_).
rd(C,_:I,N:(V=A),N:(V=A_)) :- rdr(C,I,A,A_).
rd(C,_:I,N:if(A<B,D,E),N:if(A_<B_,D,E)) :- rdr(C,I,A,A_),rdr(C,I,B,B_).
rd(_,_,N:A,N:A).
:- reach_def([
1:(a=1),
2:(b=2),
3:if(x<10,goto(4),goto(6)),
4:(a=5),
5:goto(9),
6:(b=3),
7:(c=a+b),
8:goto(9),
9:(d=a+b)
],C2),!,
C2=[
1:(a=1),
2:(b=2),
3:if(x<10,goto(4),goto(6)),
4:(a=5),
5:goto(9),
6:(b=3),
7:(c=1+3),
8:goto(9),
9:(d=a+b)
].
:- halt.
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment