Merge branch 'master' of /home/pl/chr
[chr.git] / Examples / deadcode.pl
blobd9051f507b710c1a38c2c953f4143c508b1ac973
1 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2 % Simple example of maniuplating predicate call graph in CHR
3 % to detect dead code.
5 % author: Tom Schrijvers
6 % copyright: K.U.Leuven 2005-2006
8 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
9 :- module(deadcode,[deadcode/2]).
11 :- use_module(library(chr)).
13 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
14 :- constraints
15 defined_predicate(+any),
16 calls(+any,+any),
17 live(+any),
18 print_dead_predicates.
20 defined_predicate(P) \ defined_predicate(P) <=> true.
22 calls(P,Q) \ calls(P,Q) <=> true.
24 live(P) \ live(P) <=> true.
26 live(P), calls(P,Q) ==> live(Q).
28 print_dead_predicates \ live(P), defined_predicate(P) <=> true.
29 print_dead_predicates \ defined_predicate(P) <=>
30 writeln(P).
31 print_dead_predicates \ calls(_,_) <=> true.
32 print_dead_predicates \ live(_) <=> true.
33 print_dead_predicates <=> true.
34 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
36 deadcode(File,Starts) :-
37 readfile(File,Clauses),
38 exported_predicates(Clauses,Exports),
39 findall(C, ( member(C,Clauses), C \= (:- _) , C \= (?- _)), Cs),
40 process_clauses(Cs),
41 append(Starts,Exports,Alive),
42 live_predicates(Alive),
43 print_dead_predicates.
45 exported_predicates(Clauses,Exports) :-
46 ( member( (:- module(_, Exports)), Clauses) ->
47 true
49 Exports = []
51 process_clauses([]).
52 process_clauses([C|Cs]) :-
53 hb(C,H,B),
54 extract_predicates(B,Ps,[]),
55 functor(H,F,A),
56 defined_predicate(F/A),
57 calls_predicates(Ps,F/A),
58 process_clauses(Cs).
60 calls_predicates([],FA).
61 calls_predicates([P|Ps],FA) :-
62 calls(FA,P),
63 calls_predicates(Ps,FA).
65 hb(C,H,B) :-
66 ( C = (H :- B) ->
67 true
69 C = H,
70 B = true
73 live_predicates([]).
74 live_predicates([P|Ps]) :-
75 live(P),
76 live_predicates(Ps).
78 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
79 extract_predicates(!,L,L) :- ! .
80 extract_predicates(_ < _,L,L) :- ! .
81 extract_predicates(_ = _,L,L) :- ! .
82 extract_predicates(_ =.. _ ,L,L) :- ! .
83 extract_predicates(_ =:= _,L,L) :- ! .
84 extract_predicates(_ == _,L,L) :- ! .
85 extract_predicates(_ > _,L,L) :- ! .
86 extract_predicates(_ \= _,L,L) :- ! .
87 extract_predicates(_ \== _,L,L) :- ! .
88 extract_predicates(_ is _,L,L) :- ! .
89 extract_predicates(arg(_,_,_),L,L) :- ! .
90 extract_predicates(atom_concat(_,_,_),L,L) :- ! .
91 extract_predicates(atomic(_),L,L) :- ! .
92 extract_predicates(b_getval(_,_),L,L) :- ! .
93 extract_predicates(call(_),L,L) :- ! .
94 extract_predicates(compound(_),L,L) :- ! .
95 extract_predicates(copy_term(_,_),L,L) :- ! .
96 extract_predicates(del_attr(_,_),L,L) :- ! .
97 extract_predicates(fail,L,L) :- ! .
98 extract_predicates(functor(_,_,_),L,L) :- ! .
99 extract_predicates(get_attr(_,_,_),L,L) :- ! .
100 extract_predicates(length(_,_),L,L) :- ! .
101 extract_predicates(nb_setval(_,_),L,L) :- ! .
102 extract_predicates(nl,L,L) :- ! .
103 extract_predicates(nonvar(_),L,L) :- ! .
104 extract_predicates(once(G),L,T) :- !,
105 ( nonvar(G) ->
106 extract_predicates(G,L,T)
108 L = T
110 extract_predicates(op(_,_,_),L,L) :- ! .
111 extract_predicates(prolog_flag(_,_),L,L) :- ! .
112 extract_predicates(prolog_flag(_,_,_),L,L) :- ! .
113 extract_predicates(put_attr(_,_,_),L,L) :- ! .
114 extract_predicates(read(_),L,L) :- ! .
115 extract_predicates(see(_),L,L) :- ! .
116 extract_predicates(seen,L,L) :- ! .
117 extract_predicates(setarg(_,_,_),L,L) :- ! .
118 extract_predicates(tell(_),L,L) :- ! .
119 extract_predicates(term_variables(_,_),L,L) :- ! .
120 extract_predicates(told,L,L) :- ! .
121 extract_predicates(true,L,L) :- ! .
122 extract_predicates(var(_),L,L) :- ! .
123 extract_predicates(write(_),L,L) :- ! .
124 extract_predicates((G1,G2),L,T) :- ! ,
125 extract_predicates(G1,L,T1),
126 extract_predicates(G2,T1,T).
127 extract_predicates((G1->G2),L,T) :- !,
128 extract_predicates(G1,L,T1),
129 extract_predicates(G2,T1,T).
130 extract_predicates((G1;G2),L,T) :- !,
131 extract_predicates(G1,L,T1),
132 extract_predicates(G2,T1,T).
133 extract_predicates(\+ G, L, T) :- !,
134 extract_predicates(G, L, T).
135 extract_predicates(findall(_,G,_),L,T) :- !,
136 extract_predicates(G,L,T).
137 extract_predicates(bagof(_,G,_),L,T) :- !,
138 extract_predicates(G,L,T).
139 extract_predicates(_^G,L,T) :- !,
140 extract_predicates(G,L,T).
141 extract_predicates(_:Call,L,T) :- !,
142 extract_predicates(Call,L,T).
143 extract_predicates(Call,L,T) :-
144 ( var(Call) ->
145 L = T
147 functor(Call,F,A),
148 L = [F/A|T]
151 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
153 %% File Reading
155 readfile(File,Declarations) :-
156 see(File),
157 readcontent(Declarations),
158 seen.
160 readcontent(C) :-
161 read(X),
162 ( X = (:- op(Prec,Fix,Op)) ->
163 op(Prec,Fix,Op)
165 true
167 ( X == end_of_file ->
168 C = []
170 C = [X | Xs],
171 readcontent(Xs)
173 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%