1 | % (c) 2009-2020 Lehrstuhl fuer Softwaretechnik und Programmiersprachen, | |
2 | % Heinrich Heine Universitaet Duesseldorf | |
3 | % This software is licenced under EPL 1.0 (http://www.eclipse.org/org/documents/epl-v10.html) | |
4 | ||
5 | ||
6 | :- multifile user:term_expansion/6. | |
7 | ||
8 | :- volatile definitionnr/3, clause_counter_collected/6, call_counter_collected/4. | |
9 | :- dynamic definitionnr/3, clause_counter_collected/6, call_counter_collected/4. | |
10 | ||
11 | :- use_module(library(lists)). | |
12 | :- use_module(module_information). | |
13 | ||
14 | % use module_info/3 because we are not in a module here | |
15 | :- module_info(coverage_term_expander,group,coverage_analysis). | |
16 | :- module_info(coverage_term_expander,description,'This module generates various statistics by expanding and counting terms. Used in the coverage reports.'). | |
17 | ||
18 | %failing_clause(fail). % fail is no longer counted as a failing predicate - usually this is not an error but used on purpose | |
19 | failing_clause(add_error_fail(_,_,_)). | |
20 | failing_clause(add_error_and_fail(_,_)). | |
21 | failing_clause(add_error_and_fail(_,_,_)). | |
22 | % the following are not failing per se, but can never be covered if there is no internal error in ProB | |
23 | failing_clause(add_internal_error(_,_)). | |
24 | failing_clause(add_internal_error(_,_,_,_)). | |
25 | failing_clause(add_failed_call_error(_)). | |
26 | failing_clause(add_internal_error_with_span(_,_,_,_)). | |
27 | ||
28 | reviewed_clause('$NOT_COVERED'(_)). | |
29 | ||
30 | uncoverable_clause(X) :- failing_clause(X), ! ; reviewed_clause(X). | |
31 | ||
32 | layout_sub_term([],_,[]). | |
33 | layout_sub_term([H|T],N,Res) :- | |
34 | (N=<1 -> Res=H ; N1 is N-1, layout_sub_term(T,N1,Res)). | |
35 | ||
36 | % do not use the internal_flatten/2 defined in tools to avoid loading a module before the term expansion is complete | |
37 | % same goes for internal_assert_once/1 | |
38 | internal_flatten(List,FlatList) :- internal_flatten1(List,[],FlatList). | |
39 | internal_flatten1([],Acc,FlatList) :- !, Acc = FlatList. | |
40 | internal_flatten1([H|T],Tail,List) :- !, internal_flatten1(H,FlatList,List), internal_flatten1(T,Tail,FlatList). | |
41 | internal_flatten1(NonList,Tail,[NonList|Tail]). | |
42 | internal_assert_once(Predicate) :- | |
43 | ( call(Predicate) -> true | |
44 | ; otherwise -> assert(Predicate)). | |
45 | ||
46 | coverage_counter_body(X,_Layout,coverable,_File,_Name,_Counter) :- var(X),!. | |
47 | % look into not and ~~mnf | |
48 | coverage_counter_body(\+(X),Layout,Result,File,Name,Counter) :- | |
49 | !, | |
50 | coverage_counter_body(X,Layout,Result,File,Name,Counter). | |
51 | coverage_counter_body((_A -> B),Layout,Result,File,Name,Counter) :- | |
52 | !, | |
53 | layout_sub_term(Layout,3,Layout2), | |
54 | ? | coverage_counter_body(B,Layout2,Result,File,Name,Counter). |
55 | coverage_counter_body((_A -> B ; C),Layout,Result,File,Name,Counter) :- | |
56 | !, | |
57 | layout_sub_term(Layout,2,LayoutAB), | |
58 | layout_sub_term(LayoutAB,3,LayoutB), | |
59 | layout_sub_term(Layout,3,LayoutC), | |
60 | ? | coverage_counter_body(B,LayoutB,ResultB,File,Name,Counter), |
61 | ? | coverage_counter_body(C,LayoutC,ResultC,File,Name,Counter), |
62 | ? | merge_results(ResultB,ResultC,Result). |
63 | coverage_counter_body(if(_A,B,C),Layout,Result,File,Name,Counter) :- | |
64 | !, | |
65 | layout_sub_term(Layout,3,LayoutB), | |
66 | layout_sub_term(Layout,4,LayoutC), | |
67 | coverage_counter_body(B,LayoutB,ResultB,File,Name,Counter), | |
68 | coverage_counter_body(C,LayoutC,ResultC,File,Name,Counter), | |
69 | ? | merge_results(ResultB,ResultC,Result). |
70 | coverage_counter_body((A,B),Layout,Result,File,Name,Counter) :- | |
71 | !, | |
72 | layout_sub_term(Layout,2,LayoutA), | |
73 | layout_sub_term(Layout,3,LayoutB), | |
74 | ? | coverage_counter_body(A,LayoutA,ResultA,File,Name,Counter), |
75 | ? | coverage_counter_body(B,LayoutB,ResultB,File,Name,Counter), |
76 | ((ResultA = uncoverable ; ResultB = uncoverable) | |
77 | -> Result = uncoverable, | |
78 | assert_call_counter(File,Name,Counter,LayoutA), | |
79 | assert_call_counter(File,Name,Counter,LayoutB) | |
80 | ; Result = coverable). | |
81 | coverage_counter_body((A;B),Layout,Result,File,Name,Counter) :- | |
82 | !, | |
83 | layout_sub_term(Layout,2,LayoutA), | |
84 | layout_sub_term(Layout,3,LayoutB), | |
85 | coverage_counter_body(A,LayoutA,ResultA,File,Name,Counter), | |
86 | coverage_counter_body(B,LayoutB,ResultB,File,Name,Counter), | |
87 | merge_results(ResultA,ResultB,Result). | |
88 | coverage_counter_body(X,Layout,uncoverable,File,Name,Counter) :- | |
89 | uncoverable_clause(X), | |
90 | !, assert_call_counter(File,Name,Counter,Layout). | |
91 | coverage_counter_body(_X,_Layout,coverable,_File,_Name,_Counter). | |
92 | ||
93 | merge_results(uncoverable,uncoverable,uncoverable). | |
94 | merge_results(coverable,uncoverable,coverable). | |
95 | merge_results(uncoverable,coverable,coverable). | |
96 | merge_results(coverable,coverable,coverable). | |
97 | ||
98 | assert_call_counter(File,Name,Counter,Layout) :- | |
99 | internal_flatten(Layout,Flat), | |
100 | maplist(assert_call_counter2(File,Name,Counter),Flat). | |
101 | assert_call_counter2(File,Name,Counter,SingleLine) :- | |
102 | internal_assert_once(user:call_counter_collected(File,Name,Counter,SingleLine)). | |
103 | ||
104 | coverage_counter((:- _),_Layout) :- !. | |
105 | coverage_counter(end_of_file,_Layout) :- !. | |
106 | ||
107 | coverage_counter((Head :- Body), [LayoutHead | LayoutSub]) :- | |
108 | !, | |
109 | prolog_load_context(file,File), | |
110 | prolog_load_context(module,Module), | |
111 | functor(Head,Name,Arity), | |
112 | ? | (retract(definitionnr(Module,Name/Arity,Counter)) -> true ; Counter = 0), |
113 | CNeu is Counter + 1, | |
114 | assert(definitionnr(Module,Name/Arity,CNeu)), | |
115 | layout_sub_term([LayoutHead|LayoutSub],3,SubLay), | |
116 | ? | coverage_counter_body(Body,SubLay,Result,File,Module:Name/Arity,Counter), |
117 | ( | |
118 | (Result = uncoverable ; uncoverable_clause(Head)) | |
119 | -> internal_flatten([LayoutHead|LayoutSub],FlatLayout), | |
120 | FlatLayout = [FirstLine|_], last(FlatLayout,LastLine), | |
121 | internal_assert_once(user:clause_counter_collected(File,Module:Name/Arity,Counter,LayoutHead,FirstLine,LastLine)) | |
122 | ; true | |
123 | ). | |
124 | coverage_counter(Fact, _Layout) :- | |
125 | !, | |
126 | prolog_load_context(module,Module), | |
127 | functor(Fact,Name,Arity), | |
128 | ? | (retract(definitionnr(Module,Name/Arity,Counter)) -> true ; Counter = 0), |
129 | CNeu is Counter + 1, | |
130 | assert(definitionnr(Module,Name/Arity,CNeu)). | |
131 | ||
132 | % Term Expansion to count intentional fails | |
133 | user:term_expansion(Term1, Lay1, Tokens1, Term1, Lay1, [coverage_tracing | Tokens1]) :- | |
134 | nonmember(coverage_tracing, Tokens1), % do not expand if already expanded | |
135 | ? | coverage_counter(Term1, Lay1), |
136 | !. |