14
15:- module(call_graph_test, []). 16
17:- use_module(library(lists)). 18:- use_module(pdt_call_graph). 19
20refs_to(RName, RArity, Refs) :-
21 ensure_call_graph_generated,
22 findall([Module, Name, Arity], calls(call_graph_examples, RName, RArity, Module, Name, Arity, _NumberOfCalls), Refs).
23
24:- begin_tests(call_simple_meta). 25
26test(direct_meta_call) :-
27 refs_to(abc_de, 0, Refs),
28 member([call_graph_examples, simple0, 0], Refs),
29 !.
30
31test(nested_meta_call) :-
32 refs_to(abc_de, 0, Refs),
33 member([call_graph_examples, simple1, 0], Refs),
34 !.
35
36test(meta_call_in_disjunction) :-
37 refs_to(abc_de, 0, Refs),
38 member([call_graph_examples, simple2, 0], Refs),
39 !.
40
41:- end_tests(call_simple_meta). 42
43
44:- begin_tests(call_unification). 45
46test(variable) :-
47 refs_to(abc_de, 0, Refs),
48 member([call_graph_examples, unify0, 0], Refs),
49 !.
50
51test(term) :-
52 refs_to(abc_de, 0, Refs),
53 member([call_graph_examples, unify1, 0], Refs),
54 !.
55
56test(chain) :-
57 refs_to(abc_de, 0, Refs),
58 member([call_graph_examples, unify2, 0], Refs),
59 !.
60
61test(chain_other_order) :-
62 refs_to(abc_de, 0, Refs),
63 member([call_graph_examples, unify3, 0], Refs),
64 !.
65
66test(multiple_in_term) :-
67 refs_to(abc_de, 0, Refs),
68 member([call_graph_examples, unify4, 0], Refs),
69 refs_to(de_abc, 0, Refs2),
70 member([call_graph_examples, unify4, 0], Refs2),
71 !.
72
73test(chain_via_term) :-
74 refs_to(abc_de, 0, Refs),
75 member([call_graph_examples, unify5, 0], Refs),
76 !.
77
78test(after_meta_call_not_relevant) :-
79 refs_to(abc_de, 0, Refs),
80 member([call_graph_examples, unify6, 0], Refs),
81 !.
82
83:- end_tests(call_unification). 84
85
86:- begin_tests(call_term_construction). 87
88test(univ_2) :-
89 refs_to(abc_de, 0, Refs),
90 member([call_graph_examples, construct_term1, 0], Refs),
91 !.
92
93:- end_tests(call_term_construction). 94
95
96:- begin_tests(call_functor_construction). 97
98test(atom_concat_3_add_prefix) :-
99 refs_to(abc_de, 0, Refs),
100 member([call_graph_examples, construct_functor0, 0], Refs),
101 !.
102
103test(atom_concat_3_add_suffix) :-
104 refs_to(de_abc, 0, Refs),
105 member([call_graph_examples, construct_functor1, 0], Refs),
106 !.
107
108test(atom_concat_3_add_suffix_construct_term_with_functor_3) :-
109 refs_to(de_abc, 1, Refs),
110 member([call_graph_examples, construct_functor3, 0], Refs),
111 !.
112
113:- end_tests(call_functor_construction). 114
115
116:- begin_tests(call_uncalled). 117
118test(uncalled) :-
119 refs_to(xyz, 0, Refs),
120 Refs == [].
121
122:- end_tests(call_uncalled).