3:- mpred_unload_file. 4
5:- set_prolog_flag_until_eof(do_renames,term_expansion). 6
7:- file_begin(pfc). 8
9:- set_fileAssertMt(baseKB). 11:- prolog_load_context(file,F), ain(mpred_unload_option(F,never)). 12
13argumentsConstrained(G):- cwc,ground(G),!.
14
18
19functor_any(CONSQ,F,A):- cwc, length(IST,A),apply_term(F,IST,CONSQ),!.
20
21fa_replace_arg(F,A,N,CONSQ,CSLOT,ASLOT,ANTE):-cwc,
22 functor_any(CONSQ,F,A),arg(N,CONSQ,CSLOT),replace_arg(CONSQ,N,ASLOT,ANTE),!.
23
25(((transitiveViaArg(P,B,N) ), arity(P,A),{fa_replace_arg(P,A,N,CONSQ,CSLOT,ASLOT,ANTE), P\=B,BExpr =..[B,CSLOT,ASLOT]}) ==>
26 (CONSQ:- (cwc,argumentsConstrained(CONSQ),dif(CSLOT,ASLOT),call(BExpr), argumentsConstrained(ANTE),call(ANTE)))).
27
28(transitiveViaArgInverse(P,B,N),arity(P,A),{fa_replace_arg(P,A,N,CONSQ,CSLOT,ASLOT,ANTE), P\=B,BExpr =..[B,ASLOT,CSLOT]})==>
29 (CONSQ:- (cwc,argumentsConstrained(CONSQ),dif(CSLOT,ASLOT),call(BExpr), argumentsConstrained(ANTE),call(ANTE))).
30
31
32coExtensional(A,B)==>
33 (((genls(A,Supers)<==>genls(B,Supers)) , (genls(Subs,A)<==>genls(Subs,B)), (isa(I,A)<==>isa(I,B))),
34 coExtensional(B,A)).
35
38
39:- dynamic(anatomicallyCapableOf/3). 40
41ttRelationType('rtCapabilityPredicate').
42isa(CAP_PRED,'rtCapabilityPredicate') ==>
43 transitiveViaArg(CAP_PRED,genls,2).
44
45
46==> rtCapabilityPredicate(
47 anatomicallyCapableOf('mobEmbodiedAgent','ttFirstOrderCollection','rtBinaryRolePredicate')).
48
50
54
81:- set_prolog_flag(do_renames,restore).