2:- module(mpred_pttp_testing,[]). 4:- '$set_source_module'(baseKB). 5
15
18:- ensure_loaded(dbase_i_mpred_pttp). 19
20:- kb_shared(pttp_test/2). 21:- discontiguous(pttp_test/2). 22:- kb_shared(pttp_logic/2). 23:- discontiguous(pttp_logic/2). 24
25pttp_test(chang_lee_example1,
26 ((
27 p(g(X,Y),X,Y),
28 p(X,h(X,Y),Y),
29 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
30 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
31 (query :- p(k(X),X,k(X)))
32 ))).
33
34
35
36
46
47pttp_test(chang_lee_example2,
48 ((
49 p(e,X,X),
50 p(X,e,X),
51 p(X,X,e),
52 p(a,b,c),
53 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
54 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
55 (query :- p(b,a,c))
56 ))).
57
65
66:- was_export(chang_lee_example3/0). 67pttp_test(chang_lee_example3,
68 ((
69 p(e,X,X),
70 p(i(X),X,e),
71 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
72 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
73 (query :- p(a,e,a))
74 ))).
75
76
85pttp_test(chang_lee_example4,
86 ((
87 p(e,X,X),
88 p(i(X),X,e),
89 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
90 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
91 (query :- p(a,X,e))
92 ))).
93
94
104
105pttp_test(chang_lee_example5,
106 ((
107 p(e,X,X),
108 p(X,e,X),
109 p(X,i(X),e),
110 p(i(X),X,e),
111 s(a),
112 (s(Z) :- s(X) , s(Y) , p(X,i(Y),Z)),
113 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
114 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
115 (query :- s(e))
116 ))).
117
127
128pttp_test(chang_lee_example6,
129 ((
130 p(e,X,X),
131 p(X,e,X),
132 p(X,i(X),e),
133 p(i(X),X,e),
134 s(b),
135 (s(Z) :- s(X) , s(Y) , p(X,i(Y),Z)),
136 (p(U,Z,W) :- p(X,Y,U) , p(Y,Z,V) , p(X,V,W)),
137 (p(X,V,W) :- p(X,Y,U) , p(Y,Z,V) , p(U,Z,W)),
138 (query :- s(i(b)))
139 ))).
140
157
158pttp_test(chang_lee_example7,
159 ((
160 p(a),
161 m(a,s(c),s(b)),
162 m(X,X,s(X)),
163 (not_m(X,Y,Z) ; m(Y,X,Z)),
164 (not_m(X,Y,Z) ; d(X,Z)),
165 (not_p(X) ; not_m(Y,Z,U) ; not_d(X,U) ; d(X,Y) ; d(X,Z)),
166 (query :- d(a,b))
167 ))).
168
186
187:- kb_shared(pttp_test_fails_is_ok/1). 188:- discontiguous(pttp_test_fails_is_ok/1). 189
191pttp_test(chang_lee_example8,
192 ((
193 l(1,a),
194 d(X,X),
195 (p(X) ; d(g(X),X)),
196 (p(X) ; l(1,g(X))),
197 (p(X) ; l(g(X),X)),
198 (not_p(X) ; not_d(X,a)), 199 (not_d(X,Y) ; not_d(Y,Z) ; d(X,Z)),
200 (not_l(1,X) ; not_l(X,a) ; p(f(X))),
201 (not_l(1,X) ; not_l(X,a) ; d(f(X),X)),
202 (query :- (p(X) , d(X,a)))
203 ))).
204
212
213pttp_test(chang_lee_example9,
214 ((
215 l(X,f(X)),
216 not_l(X,X),
217 (not_l(X,Y) ; not_l(Y,X)),
218 (not_d(X,f(Y)) ; l(Y,X)),
219 (p(X) ; d(h(X),X)),
220 (p(X) ; p(h(X))),
221 (p(X) ; l(h(X),X)),
222 (not_p(X) ; not_l(a,X) ; l(f(a),X)), 223 (query :- p(X) , l(a,X) , not_l(f(a),X))
224 ))).
225
238
240
241pttp_test_skipped(overbeek_example4a,
242 ((
243 (p(e(X,e(e(Y,e(Z,X)),e(Z,Y))))),
244 ((p(Y) :- p(e(X,Y)), p(X))),
245 ((queryXXX :- p(e(e(e(a,e(b,c)),c),e(b,a))))),
246 ((query:- call(pttp_prove(queryXXX,100,0,2))))
247 ))).
248
249
250pttp_test_fails_is_ok(overbeek_example4).
251pttp_test(overbeek_example4,
252 ((
253 (p(e(X,e(e(Y,e(Z,X)),e(Z,Y))))),
254 ((p(Y) :- p(e(X,Y)), p(X))),
255 ((query :- p(e(e(e(a,e(b,c)),c),e(b,a)))))
256 ))).
257
259pttp_test_query(overbeek_example4,pttp_prove(query,100,0,2)). 261
262
263
264pttp_test(logicmoo_example1,
265 ((
266 mudMother(iJoe,iSue),
267 (mudMother(X,Y) => isa(Y,tFemale)),
268 (mudChild(Y,X) => (mudMother(X,Y);mudFather(X,Y))),
269 (query:- isa(Y,tFemale))
270 ))).
271
272
273
274pttp_test(logicmoo_example1_holds,
275 ((
276 asserted_t(mudMother,iJoe,iSue),
277 (asserted_t(mudMother,X,Y) => isa(Y,tFemale)),
278 (asserted_t(mudChild,Y,X) => (true_t(mudMother,X,Y);true_t(mudFather,X,Y))),
279 (query:- isa(Y,tFemale))
280 ))).
281
282pttp_logic(logicmoo_prules,
283 ((
284 uses_logic(logicmoo_kb_refution),
285 (mudMother(X,Y) => isa(Y,tFemale)),
286 (mudChild(Y,X) => (mudMother(X,Y);mudFather(X,Y))),
287 (asserted_t(mudMother,X,Y) => isa(Y,tFemale)),
288 (asserted_t(mudChild,Y,X) => (true_t(mudMother,X,Y);true_t(mudFather,X,Y)))))).
289
290
296pttp_test(logicmoo_example2,
297 ((
298 uses_logic(logicmoo_prules),
299 mudMother(iJoe,iSue),
300 asserted_t(mudChild,iGun,iSonOfGun),
301 (-isa(iGun,tFemale)),
302 (query:- true_t(What,iSonOfGun,iGun))
303 304 ))):-What='$VAR'('?MUD-FATHER').
305
306pttp_test(logicmoo_example22,
307 ((
308 uses_logic(logicmoo_prules),
309 asserted_t(mudChild,iGun,iSonOfGun),
310 (-isa(iGun,tFemale)),
311 (query:- true_t(What,iSonOfGun,iGun))
312 313 ))):-What='$VAR'('?MUD-FATHER').
314
315
318
319baseKB:sanity_test:- do_pttp_test(logicmoo_example3).
320
321baseKB:regression_test:- do_pttp_test(logicmoo_example3).
322
323
325pttp_test(logicmoo_example3,
326 ((
327 uses_logic(logicmoo_kb_logic),
328 pred_t(genlInverse,mudParent,mudChild),
329 pred_t(genlPreds,mudMother,mudParent),
330 pred_isa_t(predIrreflexive,mudChild),
331 asserted_t(mudParent, iSon1, iFather1),
332 (query:- (not_true_t(mudChild, iSon1, iFather1)))
333
334 335 ))).
336
337
338
339
341pttp_test(logicmoo_example4,
342 ((
343 uses_logic(logicmoo_kb_logic),
344 pred_t(genlInverse,mudParent,mudChild),
345 pred_t(genlPreds,mudMother,mudParent),
346 pred_isa_t(predIrreflexive,mudChild),
347 asserted_t(mudParent, iSon1, iFather1),
348 (query:- -(possible_t(mudChild, iSon1, iFather1)))
349 350 ))).
351
352
353pttp_logic(Name,Data):- pttp_test(Name,Data).
354
355:- foreach(pttp_logic(N,_),(asserta_if_new(N:- pttp_load_wid(N)),export(N/0))). 356:- foreach(pttp_test(N,_),(asserta_if_new(N:- do_pttp_test(N)),export(N/0))). 357
358:- if_startup_script(do_pttp_tests). 359
360
361:- fixup_exports.