1/* 
    2% ===================================================================
    3% File 'mpred_db_preds.pl'
    4% Purpose: Emulation of OpenCyc for SWI-Prolog
    5% Maintainer: Douglas Miles
    6% Contact: $Author: dmiles $@users.sourceforge.net ;
    7% Version: 'interface.pl' 1.0.0
    8% Revision:  $Revision: 1.9 $
    9% Revised At:   $Date: 2002/06/27 14:13:20 $
   10% ===================================================================
   11% File used as storage place for all predicates which change as
   12% the world is run.
   13%
   14%
   15% Dec 13, 2035
   16% Douglas Miles
   17*/
   18% File: /opt/PrologMUD/pack/logicmoo_base/prolog/logicmoo/mpred/mpred_hooks.pl
   19%:- if(( ( \+ ((current_prolog_flag(logicmoo_include,Call),Call))) )).
   20:- module(mpred_hooks,[
   21/*
   22lmcache:agent_session/2,
   23lmcache:session_agent/2,
   24lmcache:session_io/4,
   25lmcache:agent_session/2,
   26lmcache:session_agent/2,
   27lmcache:session_io/4,
   28*/
   29differentTerms/2,
   30relax_term/6,
   31fix_sentence/2,
   32holds_f/1,
   33holds_f/2,
   34holds_f/3,
   35holds_f/4,
   36holds_f/5,
   37holds_f/6,
   38holds_f/7,
   39holds_f/8,
   40holds_plist_t/2,
   41holds_relaxed_0_t/4,
   42holds_relaxed_t/3,
   43holds_t/1,
   44holds_t/2,
   45holds_t/3,
   46holds_t/4,
   47holds_t/5,
   48holds_t/6,
   49holds_t/7,
   50holds_t/8,
   51holds_f_p2/2,
   52holds_relaxed_0_f/4,
   53holds_relaxed_f/3,
   54assertion_f/1,
   55assertion_t/1,
   56call_f/3,
   57call_f/4,
   58call_f/5,
   59call_f/6,
   60call_f/7,
   61call_f/8,
   62call_f/9,
   63call_mt_f/4,
   64call_mt_f/5,
   65call_mt_f/6,
   66call_mt_f/7,
   67call_mt_f/8,
   68call_mt_f/9,
   69call_mt_f/10,
   70call_mt_f/11,
   71call_mt_t/4,
   72call_mt_t/5,
   73call_mt_t/6,
   74call_mt_t/7,
   75call_mt_t/8,
   76call_mt_t/9,
   77call_mt_t/10,
   78call_mt_t/11,
   79call_which_t/3,
   80call_which_t/4,
   81call_which_t/5,
   82call_which_t/6,
   83call_which_t/7,
   84call_which_t/8,
   85call_which_t/9,
   86call_whichlist_t/3,
   87callable_tf/2,
   88
   89xcall_f/1,
   90xcall_f/2,
   91xcall_f/3,
   92xcall_f/4,
   93xcall_f/5,
   94xcall_f/6,
   95xcall_f/7,
   96xcall_f/8,
   97xcall_f/9,
   98xcall_f/10,
   99xcall_t/1,
  100xcall_t/2,
  101xcall_t/3,
  102xcall_t/4,
  103xcall_t/5,
  104xcall_t/6,
  105xcall_t/7,
  106xcall_t/8,
  107xcall_t/9,
  108xcall_t/10,
  109
  110mpred_f/1,
  111which_f/1,
  112(which_t)/1,
  113
  114add_arg_parts_of_speech/4,
  115verb_after_arg/3,
  116
  117/*
  118local_qh_mpred_isa/2,
  119fact_always_true/1,
  120create_random_fact/1,
  121
  122deduce_facts/2,
  123*/
  124print_sentence/1,
  125argIsa_call_or_undressed/4,
  126compute_value/2,
  127compute_value_no_dice/2,
  128%fact_always_true/1,
  129%fact_is_false/2,
  130%fact_maybe_deduced/1,
  131flatten_append/3,
  132%fskel/7,
  133%hooked_random_instance/3,
  134%if_result/2,
  135insert_into/4,
  136into_plist/2,
  137into_plist_arities/4,
  138inverse_args/2,
  139isCycPredArity_ignoreable/2,
  140list_update_op/3,
  141%local_term_anglify/2,
  142
  143mpred_fact_arity/2,
  144%mpred_module_ready/0,
  145%mpred_fa_call/3,
  146%mpred_plist_t/2,
  147never_mpred_tcall/1,
  148prologHybridFact/1,
  149replace_arg/4,
  150replace_nth_arglist/4,
  151replace_nth_ref/5,
  152same_vars/2,
  153%tf_result/2,
  154%never_assert_u/2,
  155update_value/3
  156]).  157
  158
  159%:- include('mpred_header.pi').
  160
  161%:- endif.
  162:- system:import(replace_arg/4).  163/*
  164add_arg_parts_of_speech/4,
  165agent_action_queue/3,
  166agent_text_command/4,
  167
  168telnet_fmt_shown/3,
  169term_anglify_last/2,
  170term_anglify_np/3,
  171term_anglify_np_last/3,
  172verb_after_arg/3
  173
  174*/
  175
  176:- meta_predicate 
  177        holds_f(*,?,?,?,?,?),
  178        holds_f(*,?,?,?,?,?,?),
  179        holds_t(*,?,?,?,?,?),
  180        holds_t(*,?,?,?,?,?,?).  181        % if_result(0, 0),
  182        % mpred_fa_call(?, ?, 0).
  183        
  184
  185
  186:- meta_predicate 
  187      % common_logic_kb_hooks
  188      call_f(*,*,?),
  189      % common_logic_kb_hooks
  190      call_f(*,*,?,?,?,?),
  191      % common_logic_kb_hooks
  192      call_f(*,*,?,?,?,?,?,?),
  193      % common_logic_kb_hooks
  194      call_mt_f(*,*,?,?,?,?),
  195      % common_logic_kb_hooks
  196      call_mt_f(*,*,?,?,?,?,?,?),
  197      % common_logic_kb_hooks
  198      call_mt_t(*,?,?,?),
  199      % common_logic_kb_hooks
  200      call_mt_t(*,*,?,?,?),
  201      % common_logic_kb_hooks
  202      call_mt_t(*,*,?,?,?,?),
  203      % common_logic_kb_hooks
  204      call_mt_t(*,*,?,?,?,?,?),
  205      % common_logic_kb_hooks
  206      call_mt_t(*,*,?,?,?,?,?,?),
  207      % common_logic_kb_hooks
  208      xcall_f(?,?,?),
  209      % common_logic_kb_hooks
  210      xcall_f(*,?,?,?),
  211      % common_logic_kb_hooks
  212      xcall_f(*,?,?,?,?,?).  213
  214% XXXXXXXXXXXXXXXXXXXXXXXXXx
  215% XXXXXXXXXXXXXXXXXXXXXXXXXx
  216% XXXXXXXXXXXXXXXXXXXXXXXXXx
  217% XXXXXXXXXXXXXXXXXXXXXXXXXx
  218                                                                        
  219:- meta_predicate 
  220
  221        call_f(?,*,?),
  222        call_f(?,?,?,?),
  223        call_f(?,*,?,?,?),
  224        call_f(?,*,?,?,?,?),
  225        call_f(?,*,?,?,?,?,?),
  226        call_f(?,*,?,?,?,?,?,?),
  227        call_mt_f(?,?,?,?),
  228        call_mt_f(?,*,?,?,?),
  229        call_mt_f(?,*,?,?,?,?),
  230        call_mt_f(?,*,?,?,?,?,?),
  231        call_mt_f(?,*,?,?,?,?,?,?),
  232        call_mt_t(?,?,?,?),
  233        call_mt_t(?,*,?,?,?),
  234        call_mt_t(?,*,?,?,?,?),
  235        call_mt_t(?,*,?,?,?,?,?),
  236        call_mt_t(?,*,?,?,?,?,?,?),
  237        call_which_t(?,*,?),
  238        call_which_t(?,?,?,?),
  239        call_which_t(?,*,?,?,?),
  240        call_which_t(?,*,?,?,?,?),
  241        call_which_t(?,*,?,?,?,?,?),
  242        call_which_t(?,*,?,?,?,?,?,?),
  243        xcall_f(0),
  244        xcall_f(*,?),
  245        xcall_f(?,?,?),
  246        xcall_f(*,?,?,?),
  247        xcall_f(*,?,?,?,?),
  248        xcall_f(*,?,?,?,?,?),
  249        xcall_f(*,?,?,?,?,?,?),
  250        xcall_t(0),
  251        xcall_t(*,?),
  252        xcall_t(?,?,?),
  253        xcall_t(*,?,?,?),
  254        xcall_t(*,?,?,?,?),
  255        xcall_t(*,?,?,?,?,?),
  256        xcall_t(*,?,?,?,?,?,?).  257
  258:- meta_predicate xcall_f(0).  259:- meta_predicate xcall_f(*,?).  260:- meta_predicate xcall_f(?,?,?).  261:- meta_predicate xcall_f(*,?,?,?).  262:- meta_predicate xcall_f(*,?,?,?,?).  263:- meta_predicate xcall_f(*,?,?,?,?,?).  264:- meta_predicate xcall_f(*,?,?,?,?,?,?).  265:- meta_predicate xcall_t(0).  266:- meta_predicate xcall_t(*,?).  267:- meta_predicate xcall_t(?,?,?).  268:- meta_predicate xcall_t(*,?,?,?).  269:- meta_predicate xcall_t(*,?,?,?,?).  270:- meta_predicate xcall_t(*,?,?,?,?,?).  271:- meta_predicate xcall_t(*,?,?,?,?,?,?).  272:- meta_predicate call_f(?,*,?).  273:- meta_predicate call_f(?,?,?,?).  274:- meta_predicate call_f(?,*,?,?,?).  275:- meta_predicate call_f(?,*,?,?,?,?).  276:- meta_predicate call_f(?,*,?,?,?,?,?).  277:- meta_predicate call_f(?,*,?,?,?,?,?,?).  278:- meta_predicate call_mt_f(?,?,?,?).  279:- meta_predicate call_mt_f(?,*,?,?,?).  280:- meta_predicate call_mt_f(?,*,?,?,?,?).  281:- meta_predicate call_mt_f(?,*,?,?,?,?,?).  282:- meta_predicate call_mt_f(?,*,?,?,?,?,?,?).  283:- meta_predicate call_mt_t(?,?,?,?).  284:- meta_predicate call_mt_t(?,*,?,?,?).  285:- meta_predicate call_mt_t(?,*,?,?,?,?).  286:- meta_predicate call_mt_t(?,*,?,?,?,?,?).  287:- meta_predicate call_mt_t(?,*,?,?,?,?,?,?).  288:- meta_predicate call_which_t(?,*,?).  289:- meta_predicate call_which_t(?,?,?,?).  290:- meta_predicate call_which_t(?,*,?,?,?).  291:- meta_predicate call_which_t(?,*,?,?,?,?).  292:- meta_predicate call_which_t(?,*,?,?,?,?,?).  293:- meta_predicate call_which_t(?,*,?,?,?,?,?,?).  294
  295:- meta_predicate holds_f(*,?,?,?,?,?).  296:- meta_predicate holds_f(*,?,?,?,?,?,?).  297:- meta_predicate holds_t(*,?,?,?,?,?).  298:- meta_predicate holds_t(*,?,?,?,?,?,?).  299
  300
  301:- meta_predicate call_f(*,?,?,?).  302:- meta_predicate call_f(*,*,?,?,?).  303:- meta_predicate call_f(*,*,?,?,?,?,?).  304:- meta_predicate call_mt_f(*,?,?,?).  305:- meta_predicate call_mt_f(*,*,?,?,?).  306:- meta_predicate call_mt_f(*,*,?,?,?,?,?).  307:- meta_predicate call_which_t(*,*,?,?,?,?,?).  308:- meta_predicate call_which_t(*,*,?,?,?,?,?,?).  309:- meta_predicate holds_f(*,?).  310:- meta_predicate holds_f(*,?,?,?,?,?).  311:- meta_predicate holds_f(*,?,?,?,?,?,?).  312:- meta_predicate holds_relaxed_0_f(*,*,?,?).  313:- meta_predicate xcall_f(0).  314:- meta_predicate xcall_f(*,?).  315:- meta_predicate xcall_f(*,?,?,?,?).  316:- meta_predicate xcall_f(*,?,?,?,?,?,?).  317:- meta_predicate xcall_t(0).  318:- meta_predicate xcall_t(*,?).  319:- meta_predicate xcall_t(?,?,?).  320:- meta_predicate xcall_t(*,?,?,?).  321:- meta_predicate xcall_t(*,?,?,?,?).  322:- meta_predicate xcall_t(*,?,?,?,?,?).  323:- meta_predicate xcall_t(*,?,?,?,?,?,?).  324
  325:- meta_predicate call_whichlist_t(?,0,?).  326
  327:- dynamic((
  328(which_t)/1
  329/*
  330fact_always_true/1
  331add_arg_parts_of_speech/4,
  332agent_action_queue/3,
  333agent_text_command/4,
  334argIsa_call_or_undressed/4,
  335create_random_fact/1,
  336deduce_facts/2,
  337fact_is_false/2,
  338fact_maybe_deduced/1,
  339fskel/7,
  340hooked_random_instance/3,
  341isCycPredArity_ignoreable/2,
  342% lmcache:loaded_external_kbs/1,
  343%local_term_anglify/2,
  344mpred_fact_arity/2,
  345%mpred_module_ready/0,
  346never_mpred_tcall/1,
  347telnet_fmt_shown/3,
  348term_anglify_last/2,
  349term_anglify_np/3,
  350term_anglify_np_last/3,
  351never_assert_u/2,
  352% use_cyc_database/0,
  353verb_after_arg/3
  354*/
  355
  356
  357
  358
  359/*
  360if_result/2,
  361insert_into/4,
  362into_plist/2,
  363into_plist_arities/4,
  364inverse_args/2,
  365mpred_fa_call/3,
  366mpred_plist_t/2,
  367list_update_op/3,
  368compute_value/2,
  369compute_value_no_dice/2,
  370*/
  371/*
  372prologHybridFact/1,
  373flatten_append/3,
  374replace_arg/4,
  375replace_nth_arglist/4,
  376replace_nth_ref/5,
  377same_vars/2,
  378update_value/3,
  379*/
  380)).  381% :- registerCycPredMtWhy([genlPreds/4,genlInverse/4,localityOfObject/4]).
  382
  383/* <module> mpred_mpred_t
  384% Provides a prolog dabase in these predicates...
  385%
  386%  t/N
  387%  hybridRule/2
  388%  
  389%
  390% Logicmoo Project PrologMUD: A MUD server written in Prolog
  391% Maintainer: Douglas Miles
  392% Dec 13, 2035
  393%
  394*/
  395
  396:- set_how_virtualize_file(bodies).  397
  398
  399% %%% :- kb_shared(create_random_fact/1).
  400
  401% % %%% :- kb_shared baseKB:decl_database_hook/2.
  402% %%% :- kb_shared deduce_facts/2.
  403% %%% :- kb_shared default_type_props/3.
  404% %%% :- kb_shared fact_always_true/1.
  405% %%% :- kb_shared fact_maybe_deduced/1.
  406% %%% :- kb_shared never_assert_u/2.
  407% %%% :- kb_shared fskel/7.
  408% %%% :- kb_shared hooked_random_instance/3.
  409
  410% %%% :- kb_shared now_unused/1.
  411
  412
  413% %%% :- kb_shared(baseKB:startup_option/2).
  414% %%% :- kb_shared(is_edited_clause/3).
  415
  416% %%% :- kb_shared(lmcache:loaded_external_kbs/1).
  417
  418
  419% %%% :- kb_shared fact_is_false/2.
  420
  421
  422
  423
  424% %%% :- kb_shared mudKeyword/2.
  425% %%% :- kb_shared baseKB:only_if_pttp/0.
  426% %%% :- kb_shared relationMostInstance/3.
  427
  428
  429% %%% :- kb_shared tFarthestReachableItem/1.
  430% %%% :- kb_shared tNearestReachableItem/1.
  431
  432
  433:- multifile(baseKB:use_cyc_database/0).  434:- thread_local(baseKB:use_cyc_database/0).  435% % %%% :- kb_shared decl_database_hook/2.
  436
  437
  438% %%% :- kb_shared(mpred_module_ready).
  439
  440% % %%% :- kb_shared loading_module/1.
  441% %%% :- kb_shared local_term_anglify/2.
  442
  443
  444% %%% :- kb_shared term_anglify_last/2.
  445% %%% :- kb_shared term_anglify_np/3.
  446% %%% :- kb_shared term_anglify_np_last/3.
  447
  448% ================================================================================
  449% begin holds_t
  450% ================================================================================
  451
  452%= 	 	 
 isCycPredArity_ignoreable(?VALUE1, ?VALUE2) is semidet
If Is A Cyc Predicate Arity Ignoreable.
  458isCycPredArity_ignoreable(F,A):- ignore(local_qh_mpred_prop(_,F,A,cycPred(A))),ignore(arity(F,A)).
  459
  460
  461%= 	 	 
 which_t(?VALUE1) is semidet
Which True Stucture.
  467which_t(dac(d,a_notnow,c,no_fallback)).
  468
  469
  470%= 	 	 
 holds_t(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Holds True Stucture.
  476holds_t(P,A1,A2,A3,A4,A5,A6,A7):- isCycPredArity_ignoreable(P,7),which_t(DBS),(call_which_t(DBS,P,A1,A2,A3,A4,A5,A6,A7);call_mt_t(DBS,P,A1,A2,A3,A4,A5,A6,A7,_,_);assertion_t([P,A1,A2,A3,A4,A5,A6,A7])).
  477
  478%= 	 	 
 holds_t(:PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Holds True Stucture.
  484holds_t(P,A1,A2,A3,A4,A5,A6):- isCycPredArity_ignoreable(P,6),which_t(DBS),(call_which_t(DBS,P,A1,A2,A3,A4,A5,A6);call_mt_t(DBS,P,A1,A2,A3,A4,A5,A6,_,_)).
  485
  486
  487%= 	 	 
 holds_t(:PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Holds True Stucture.
  493holds_t(P,A1,A2,A3,A4,A5):- isCycPredArity_ignoreable(P,5),which_t(DBS),(call_which_t(DBS,P,A1,A2,A3,A4,A5);call_mt_t(DBS,P,A1,A2,A3,A4,A5,_,_)).
  494
  495
  496%= 	 	 
 holds_t(?P, ?A1, ?A2, ?A3, ?A4) is semidet
Holds True Stucture.
  502holds_t(P,A1,A2,A3,A4):- isCycPredArity_ignoreable(P,4),which_t(DBS),(call_which_t(DBS,P,A1,A2,A3,A4);call_mt_t(DBS,P,A1,A2,A3,A4,_,_)).
  503
  504%= 	 	 
 holds_t(?P, ?A1, ?A2, ?A3) is semidet
Holds True Stucture.
  510holds_t(P,A1,A2,A3):- isCycPredArity_ignoreable(P,3),which_t(DBS),(call_which_t(DBS,P,A1,A2,A3);call_mt_t(DBS,P,A1,A2,A3,_,_)).
  511%holds_t(P,A1,A2):- quietly(holds_relaxed_t(P,A1,A2)).
  512
  513%= 	 	 
 holds_t(?P, ?A1, ?A2) is semidet
Holds True Stucture.
  519holds_t(P,A1,A2):- isCycPredArity_ignoreable(P,2),which_t(DBS),(call_which_t(DBS,P,A1,A2);call_mt_t(DBS,P,A1,A2,_,_)).
  520
  521%= 	 	 
 holds_t(?P, ?A1) is semidet
Holds True Stucture.
  527holds_t(P,A1):- isCycPredArity_ignoreable(P,1),which_t(DBS),(call_which_t(DBS,P,A1);call_mt_t(DBS,P,A1,_,_)).
  528
  529
  530% holds_relaxed_t(P,A1,A2):-var(A1),var(A2),!,t(P,A1,A2).
  531
  532%= 	 	 
 holds_relaxed_t(?P, ?A1, ?A2) is semidet
Holds Relaxed True Stucture.
  538holds_relaxed_t(P,A1,A2):-
  539  isCycPredArity_ignoreable(P,2),which_t(DBS),
  540      relax_term(P,PR,A1,R1,A2,R2),
  541         holds_relaxed_0_t(DBS,PR,R1,R2).
  542
  543
  544%= 	 	 
 holds_relaxed_0_t(?DBS, ?P, ?A1, ?A2) is semidet
holds relaxed Primary Helper True Stucture.
  550holds_relaxed_0_t(DBS,P,A1,A2):- call_which_t(DBS,P,A1,A2).
  551holds_relaxed_0_t(DBS,P,A1,A2):- call_mt_t(DBS,P,A1,A2,_,_).
  552
  553/*
  554holds_relaxed_0_t(dac(_,a,_,_),P,A1,A2):- assertion_t([P,A1,A2]).
  555holds_relaxed_0_t(dac(d,_,_,_),P,A1,A2):- t(P,A1,A2).
  556holds_relaxed_0_t(dac(_,_,_,h),P,A1,A2):- call_which_t(DBS,P,A1,A2).
  557holds_relaxed_0_t(DBS,P,A1,A2):- call_mt_t(DBS,P,A1,A2,_,_).
  558holds_relaxed_0_t(_DBS,P,A1,A2):- ground((P,A1)), TEMPL=..[P,T1,_],t(relationMostInstance,TEMPL,T1,A2),call_u(isa(A1,T1)),!.
  559*/
  560
  561
  562%= 	 	 
 holds_t(:TermCALL) is semidet
Holds True Stucture.
  568holds_t([AH,P|LIST]):- is_holds_true(AH),!,holds_plist_t(P,LIST).
  569holds_t([AH,P|LIST]):- is_holds_false(AH),!,holds_f_p2(P,LIST).
  570holds_t([P|LIST]):- !,holds_plist_t(P,LIST).
  571holds_t(not(CALL)):- !, holds_f(CALL).
  572holds_t(CALL):- '=..'(CALL,PLIST),holds_t(PLIST).
  573
  574
  575%= 	 	 
 holds_plist_t(?P, ?LIST) is semidet
Holds Plist True Stucture.
  581holds_plist_t(P,LIST):- apply(holds_t,[P|LIST]).
 add_arg_parts_of_speech(?F, ?N, :TermARG3, :TermARG4) is semidet
Add Argument Parts Of Speech.
  596add_arg_parts_of_speech(_F,_N,[],[]).
  597add_arg_parts_of_speech(F,N,[A|ARGS0],[ARG|ARGS]):-argIsa_call_or_undressed(F,N,A,ARG),N1 is N+1, add_arg_parts_of_speech(F,N1,ARGS0,ARGS).
 argIsa_call_or_undressed(?F, ?N, ?Obj, ?Obj) is semidet
Argument (isa/2) call or undressed.
  606argIsa_call_or_undressed(F,N,Obj,fN(Obj,Type)):- call_u(argIsa(F,N,Type)),!.
  607argIsa_call_or_undressed(_F,_N,Obj,Obj).
 verb_after_arg(?VALUE1, ?VALUE2, :PRED1VALUE3) is semidet
Verb After Argument.
  616verb_after_arg(_,_,1).
  617
  618
  619
  620%= 	 	 
 print_sentence(?Proof) is semidet
Print Sentence.
  626print_sentence(Proof):- fix_sentence(Proof,New),!,ignore((Proof\=New,!,must_det(retract(Proof)),assert(assert_next_queue(New)))),!.
  627
  628
  629
  630%= 	 	 
 fix_sentence(?X, ?X) is semidet
Fix Sentence.
  636fix_sentence(X,X).
  637
  638
  639%= 	 	 
 relax_term(?P, ?P, ?Aic, ?Aic, ?Bic, ?Bic) is semidet
Relax Term.
  645relax_term(P,P,Aic,Aic,Bic,Bic):- !.
  646/*
  647relax_term(P,P,A,A,Bi,Bc):- arg(_,v(genls,isa),P),!,fail.
  648relax_term(P,P,Ai,Ac,Bic,Bic):- when_met(nonvar(Ac), same_arg(same_or(isa),Ac,Ai)),!.
  649relax_term(P,P,Ai,Ac,Bi,Bc):- is_type(Ai),!,when_met(pred(nonvar,Ac), (same_arg(same_or(genls),Ac,Ai),same_arg(same_or(equals),Bc,Bi))),!.
  650relax_term(P,P,Ai,Ac,Bi,Bc):- when_met(pred(nonvar,Ac),when_met(pred(nonvar,Bc), (same_arg(same_or(genls),Ac,Ai),same_arg(same_or(equals),Bc,Bi)))).
  651*/
  652
  653% ?- member(R,[a,b,c]),when_met(nonvar(Re), dbase:same_arg(same_or(termOfUnit),n,Re)),Re=R,write(chose(R)).
  654
  655differentTerms(A,B):- dif:dif(A,B).
  656
  657
  658
  659/*
  660:- kb_local(baseKB:admittedArgument/3).
  661baseKB:admittedArgument(P,N,A):-var_non_attvar(P),!,freeze(P,admittedArgument(P,N,A)).
  662baseKB:admittedArgument(P,N,A):-var_non_attvar(A),!,freeze(A,admittedArgument(P,N,A)).
  663baseKB:admittedArgument(P,N,A):-var_non_attvar(N),!,freeze(N,(number(N),admittedArgument(P,N,A))).
  664baseKB:admittedArgument(P,N,A):-nop(wdmsg(admittedArgument(P,N,A))).
  665*/
  666
  667%= 	 	 
 callable_tf(?F, ?A) is semidet
Callable True/false.
  674callable_tf(F,A):- functor_safe(P,F,A),predicate_property(P,_),!.
  675%callable_tf(P,2):- cheaply_u(mpred_arity_pred(P)),!,fail.
  676
  677
  678
  679%= 	 	 
 call_whichlist_t(?UPARAM1, :GoalGOAL2, ?List) is semidet
Call Whichlist True Stucture.
  685call_whichlist_t(dac(d,_,_,_),CALL,_):- call_u(t(CALL)).
  686call_whichlist_t(dac(_,a,_,_),_,List):- assertion_t(List).
  687call_whichlist_t(dac(_,_,c,_),CALL,_):- xcall_t(CALL).
  688call_whichlist_t(dac(_,_,_,holds_t),CALL,_):- holds_t(CALL).
  689
  690
  691%= 	 	 
 call_which_t(?DBS, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Call Which True Stucture.
  697call_which_t(DBS,P,A1,A2,A3,A4,A5,A6,A7):- callable_tf(P,7),List= [P,A1,A2,A3,A4,A5,A6,A7], CALL=..List, call_whichlist_t(DBS,CALL,List).
  698call_which_t(dac(_,_,_,h),P,A1,A2,A3,A4,A5,A6,A7):- holds_t(P,A1,A2,A3,A4,A5,A6,A7).
  699
  700
  701%= 	 	 
 call_which_t(?UPARAM1, :PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Call Which True Stucture.
  707call_which_t(dac(d,_,_,_),P,A1,A2,A3,A4,A5,A6):- t(P,A1,A2,A3,A4,A5,A6).
  708call_which_t(dac(_,a,_,_),P,A1,A2,A3,A4,A5,A6):- assertion_t([P,A1,A2,A3,A4,A5,A6]).
  709call_which_t(dac(_,_,c,_),P,A1,A2,A3,A4,A5,A6):- callable_tf(P,6),xcall_t(P,A1,A2,A3,A4,A5,A6).
  710call_which_t(dac(_,_,_,holds_t),P,A1,A2,A3,A4,A5,A6):- holds_t(P,A1,A2,A3,A4,A5,A6).
  711
  712
  713%= 	 	 
 call_which_t(?UPARAM1, :PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Call Which True Stucture.
  719call_which_t(dac(d,_,_,_),P,A1,A2,A3,A4,A5):- t(P,A1,A2,A3,A4,A5).
  720call_which_t(dac(_,a,_,_),P,A1,A2,A3,A4,A5):- assertion_t([P,A1,A2,A3,A4,A5]).
  721call_which_t(dac(_,_,c,_),P,A1,A2,A3,A4,A5):- callable_tf(P,5),xcall_t(P,A1,A2,A3,A4,A5).
  722call_which_t(dac(_,_,_,holds_t),P,A1,A2,A3,A4,A5):- holds_t(P,A1,A2,A3,A4,A5).
  723
  724
  725%= 	 	 
 call_which_t(?UPARAM1, :PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Call Which True Stucture.
  731call_which_t(dac(d,_,c,_),P,A1,A2,A3,A4):- t(P,A1,A2,A3,A4).
  732call_which_t(dac(_,a,_,_),P,A1,A2,A3,A4):- assertion_t([P,A1,A2,A3,A4]).
  733call_which_t(dac(_,_,c,_),P,A1,A2,A3,A4):- callable_tf(P,4),xcall_t(P,A1,A2,A3,A4).
  734call_which_t(dac(_,_,_,holds_t),P,A1,A2,A3,A4):- holds_t(P,A1,A2,A3,A4).
  735
  736
  737%= 	 	 
 call_which_t(?UPARAM1, :PRED3P, ?A1, ?A2, ?A3) is semidet
Call Which True Stucture.
  743call_which_t(dac(d,_,_,_),P,A1,A2,A3):- t(P,A1,A2,A3).
  744call_which_t(dac(_,a,_,_),P,A1,A2,A3):- assertion_t([P,A1,A2,A3]).
  745call_which_t(dac(_,_,c,_),P,A1,A2,A3):- callable_tf(P,3),xcall_t(P,A1,A2,A3).
  746call_which_t(dac(_,_,_,holds_t),P,A1,A2,A3):- holds_t(P,A1,A2,A3).
  747
  748
  749%= 	 	 
 call_which_t(?UPARAM1, :PRED2P, ?A1, ?A2) is semidet
Call Which True Stucture.
  755call_which_t(dac(d,_,_,_),P,A1,A2):- t(P,A1,A2).
  756call_which_t(dac(_,a,_,_),P,A1,A2):- assertion_t([P,A1,A2]).
  757call_which_t(dac(_,_,c,_),P,A1,A2):- callable_tf(P,2),xcall_t(P,A1,A2).
  758call_which_t(dac(_,_,_,holds_t),P,A1,A2):- holds_t(P,A1,A2).
  759
  760
  761%= 	 	 
 call_which_t(?UPARAM1, :PRED1P, ?A1) is semidet
Call Which True Stucture.
  767call_which_t(dac(d,_,_,_),P,A1):- call_u(t(P,A1)).
  768call_which_t(dac(_,a,_,_),P,A1):- assertion_t([P,A1]).
  769call_which_t(dac(_,_,c,_),P,A1):- callable_tf(P,1),xcall_t(P,A1).
  770call_which_t(dac(_,_,_,holds_t),P,A1):- holds_t(P,A1).
  771
  772
  773%= 	 	 
 call_mt_t(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8, ?A9) is semidet
Call User Microtheory True Stucture.
  779call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7,A8,A9):- callable_tf(P,9),CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8,A9],xcall_t(CALL).
  780
  781%= 	 	 
 call_mt_t(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8) is semidet
Call User Microtheory True Stucture.
  787call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7,A8):- callable_tf(P,8),CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8],xcall_t(CALL).
  788
  789%= 	 	 
 call_mt_t(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Call User Microtheory True Stucture.
  795call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7):- callable_tf(P,7),CALL=..[P,A1,A2,A3,A4,A5,A6,A7],xcall_t(CALL).
  796
  797%= 	 	 
 call_mt_t(?UPARAM1, :PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Call User Microtheory True Stucture.
  803call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6):- callable_tf(P,6),xcall_t(P,A1,A2,A3,A4,A5,A6).
  804
  805%= 	 	 
 call_mt_t(?UPARAM1, :PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Call User Microtheory True Stucture.
  811call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4,A5):- callable_tf(P,5),xcall_t(P,A1,A2,A3,A4,A5).
  812
  813%= 	 	 
 call_mt_t(?UPARAM1, :PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Call User Microtheory True Stucture.
  819call_mt_t(dac(_,_,_,mt),P,A1,A2,A3,A4):- callable_tf(P,4),xcall_t(P,A1,A2,A3,A4).
  820
  821%= 	 	 
 call_mt_t(?UPARAM1, :PRED3P, ?A1, ?A2, ?A3) is semidet
Call User Microtheory True Stucture.
  827call_mt_t(dac(_,_,_,mt),P,A1,A2,A3):- callable_tf(P,3),xcall_t(P,A1,A2,A3).
  828
  829%= 	 	 
 call_mt_t(?UPARAM1, :PRED2P, ?A1, ?A2) is semidet
Call User Microtheory True Stucture.
  835call_mt_t(dac(_,_,_,mt),P,A1,A2):- callable_tf(P,3),xcall_t(P,A1,A2).
  836
  837
  838%= 	 	 
 xcall_t(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8, ?A9) is semidet
Extended Call True Stucture.
  844xcall_t(P,A1,A2,A3,A4,A5,A6,A7,A8,A9):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8,A9],call(CALL).
  845
  846%= 	 	 
 xcall_t(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8) is semidet
Extended Call True Stucture.
  852xcall_t(P,A1,A2,A3,A4,A5,A6,A7,A8):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8],call(CALL).
  853
  854%= 	 	 
 xcall_t(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Extended Call True Stucture.
  860xcall_t(P,A1,A2,A3,A4,A5,A6,A7):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7],call(CALL).
  861
  862%= 	 	 
 xcall_t(:PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Extended Call True Stucture.
  868xcall_t(P,A1,A2,A3,A4,A5,A6):- call(P,A1,A2,A3,A4,A5,A6).
  869
  870%= 	 	 
 xcall_t(:PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Extended Call True Stucture.
  876xcall_t(P,A1,A2,A3,A4,A5):- call(P,A1,A2,A3,A4,A5).
  877
  878%= 	 	 
 xcall_t(:PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Extended Call True Stucture.
  884xcall_t(P,A1,A2,A3,A4):- call(P,A1,A2,A3,A4).
  885
  886%= 	 	 
 xcall_t(:PRED3P, ?A1, ?A2, ?A3) is semidet
Extended Call True Stucture.
  892xcall_t(P,A1,A2,A3):- call(P,A1,A2,A3).
  893
  894%= 	 	 
 xcall_t(:PRED2P, ?A1, ?A2) is semidet
Extended Call True Stucture.
  900xcall_t(P,A1,A2):- call(P,A1,A2).
  901
  902%= 	 	 
 xcall_t(:PRED1P, ?A1) is semidet
Extended Call True Stucture.
  908xcall_t(P,A1):- call(P,A1).
  909
  910%= 	 	 
 xcall_t(:GoalP) is semidet
Extended Call True Stucture.
  916xcall_t(P):- call(P).
  917
  918% todo hook into loaded files!
  919:- was_export(assertion_t/1).  920
  921% assertion_t(Call):- t_l:useOnlyExternalDBs,!,baseKB:use_cyc_database,locally_hide(t_l:useOnlyExternalDBs,kb_t(Call)).
  922
  923%= 	 	 
 assertion_t(?Call) is semidet
Assertion True Stucture.
  929assertion_t(Call):- baseKB:use_cyc_database,!,locally_tl(useOnlyExternalDBs,kb_t(Call)).
  930% assertion_t(Call):- locally_tl(useOnlyExternalDBs,loop_check(call_u(Call))).
  931
  932% ================================================================================
  933% end holds_t
  934% ================================================================================
  935
  936% % :- ensure_loaded(logicmoo(plarkc/mpred_cyc_kb)).
  937
  938% ================================================================================
  939% begin holds_f
  940% ================================================================================
  941
  942%= 	 	 
 which_f(?VALUE1) is semidet
Which False.
  948which_f(dac(d,no_a,no_c,no_mt)).
  949
  950
  951%= 	 	 
 holds_f(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Holds False.
  957holds_f(P,A1,A2,A3,A4,A5,A6,A7):- isCycPredArity_ignoreable(P,7),which_f(DBS),(call_f(DBS,P,A1,A2,A3,A4,A5,A6,A7);call_mt_f(DBS,P,A1,A2,A3,A4,A5,A6,A7,_,_);assertion_f([P,A1,A2,A3,A4,A5,A6,A7])).
  958
  959%= 	 	 
 holds_f(:PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Holds False.
  965holds_f(P,A1,A2,A3,A4,A5,A6):- isCycPredArity_ignoreable(P,6),which_f(DBS),(call_f(DBS,P,A1,A2,A3,A4,A5,A6);call_mt_f(DBS,P,A1,A2,A3,A4,A5,A6,_,_)).
  966
  967%= 	 	 
 holds_f(:PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Holds False.
  973holds_f(P,A1,A2,A3,A4,A5):- isCycPredArity_ignoreable(P,5),which_f(DBS),(call_f(DBS,P,A1,A2,A3,A4,A5);call_mt_f(DBS,P,A1,A2,A3,A4,A5,_,_)).
  974
  975%= 	 	 
 holds_f(?P, ?A1, ?A2, ?A3, ?A4) is semidet
Holds False.
  981holds_f(P,A1,A2,A3,A4):- isCycPredArity_ignoreable(P,4),which_f(DBS),(call_f(DBS,P,A1,A2,A3,A4);call_mt_f(DBS,P,A1,A2,A3,A4,_,_)).
  982
  983%= 	 	 
 holds_f(?P, ?A1, ?A2, ?A3) is semidet
Holds False.
  989holds_f(P,A1,A2,A3):- isCycPredArity_ignoreable(P,3),which_f(DBS),(call_f(DBS,P,A1,A2,A3);call_mt_f(DBS,P,A1,A2,A3,_,_)).
  990
  991%= 	 	 
 holds_f(?P, ?A1, ?A2) is semidet
Holds False.
  997holds_f(P,A1,A2):- holds_relaxed_f(P,A1,A2).
  998
  999%= 	 	 
 holds_f(:PRED1P, ?A1) is semidet
Holds False.
 1005holds_f(P,A1):- isCycPredArity_ignoreable(P,1),which_f(DBS),(call_f(DBS,P,A1);call_mt_f(DBS,P,A1,_,_)).
 1006
 1007
 1008
 1009%= 	 	 
 holds_relaxed_f(?P, ?A1, ?A2) is semidet
Holds Relaxed False.
 1015holds_relaxed_f(P,A1,A2):- isCycPredArity_ignoreable(P,2),which_f(DBS),!,relax_term(P,PR,A1,R1,A2,R2),holds_relaxed_0_f(DBS,PR,R1,R2).
 1016
 1017%= 	 	 
 holds_relaxed_0_f(?DBS, :PRED4P, ?A1, ?A2) is semidet
holds relaxed Primary Helper False.
 1023holds_relaxed_0_f(DBS,P,A1,A2):- call_f(DBS,P,A1,A2).
 1024holds_relaxed_0_f(DBS,P,A1,A2):- call_mt_f(DBS,P,A1,A2,_,_).
 1025
 1026
 1027
 1028%= 	 	 
 holds_f(:TermCALL) is semidet
Holds False.
 1034holds_f([AH,P|LIST]):- is_holds_true(AH),!,holds_f_p2(P,LIST).
 1035holds_f([AH,P|LIST]):- is_holds_false(AH),!,holds_plist_t(P,LIST).
 1036holds_f([P|LIST]):- !, holds_f_p2(P,LIST).
 1037holds_f(CALL):- CALL=..[P|LIST],holds_f([P|LIST]).
 1038
 1039%= 	 	 
 holds_f_p2(?P, ?LIST) is semidet
Holds False Pred Extended Helper.
 1045holds_f_p2(P,LIST):- CALL=..[holds_f,P|LIST],call(CALL).
 1046
 1047
 1048%= 	 	 
 mpred_f(?List) is semidet
Managed Predicate False.
 1054mpred_f(List):- is_list(List),!,Call=..[mpred_f|List],call_u(Call).
 1055mpred_f(List):- holds_f(List).
 1056
 1057
 1058
 1059%= 	 	 
 call_f(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Call False.
 1065call_f(_,P,A1,A2,A3,A4,A5,A6,A7):- callable_tf(P,7),List= [P,A1,A2,A3,A4,A5,A6,A7], CALL=..List,(assertion_f(List);mpred_f(CALL);xcall_f(CALL)).
 1066
 1067%= 	 	 
 call_f(?UPARAM1, :PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Call False.
 1073call_f(dac(d,_,_,_),P,A1,A2,A3,A4,A5,A6):- call_u(mpred_f([P,A1,A2,A3,A4,A5,A6])).
 1074call_f(dac(_,a,_,_),P,A1,A2,A3,A4,A5,A6):- assertion_f([P,A1,A2,A3,A4,A5,A6]).
 1075call_f(dac(_,_,c,_),P,A1,A2,A3,A4,A5,A6):- callable_tf(P,6),xcall_f(P,A1,A2,A3,A4,A5,A6).
 1076
 1077%= 	 	 
 call_f(?UPARAM1, :PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Call False.
 1083call_f(dac(d,_,_,_),P,A1,A2,A3,A4,A5):- call_u(mpred_f(P,A1,A2,A3,A4,A5)).
 1084call_f(dac(_,a,_,_),P,A1,A2,A3,A4,A5):- assertion_f([P,A1,A2,A3,A4,A5]).
 1085call_f(dac(_,_,c,_),P,A1,A2,A3,A4,A5):- callable_tf(P,5),xcall_f(P,A1,A2,A3,A4,A5).
 1086
 1087%= 	 	 
 call_f(?UPARAM1, :PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Call False.
 1093call_f(dac(d,_,_,_),P,A1,A2,A3,A4):- call_u(mpred_f(P,A1,A2,A3,A4)).
 1094call_f(dac(_,a,_,_),P,A1,A2,A3,A4):- assertion_f([P,A1,A2,A3,A4]).
 1095call_f(dac(_,_,c,_),P,A1,A2,A3,A4):- callable_tf(P,4),xcall_f(P,A1,A2,A3,A4).
 1096
 1097%= 	 	 
 call_f(?UPARAM1, :PRED3P, ?A1, ?A2, ?A3) is semidet
Call False.
 1103call_f(dac(d,_,_,_),P,A1,A2,A3):- call_u(mpred_f(P,A1,A2,A3)).
 1104call_f(dac(_,a,_,_),P,A1,A2,A3):- assertion_f([P,A1,A2,A3]).
 1105call_f(dac(_,_,c,_),P,A1,A2,A3):- callable_tf(P,3),xcall_f(P,A1,A2,A3).
 1106
 1107%= 	 	 
 call_f(?UPARAM1, :PRED2P, ?A1, ?A2) is semidet
Call False.
 1113call_f(dac(d,_,_,_),P,A1,A2):- call_u(mpred_f(P,A1,A2)).
 1114call_f(dac(_,a,_,_),P,A1,A2):- assertion_f([P,A1,A2]).
 1115call_f(dac(_,_,c,_),P,A1,A2):- callable_tf(P,2),xcall_f(P,A1,A2).
 1116
 1117%= 	 	 
 call_f(?UPARAM1, :PRED1P, ?A1) is semidet
Call False.
 1123call_f(dac(d,_,_,_),P,A1):- call_u(mpred_f(P,A1)).
 1124call_f(dac(_,a,_,_),P,A1):- assertion_f([P,A1]).
 1125call_f(dac(_,_,c,_),P,A1):- callable_tf(P,1),xcall_f(P,A1).
 1126
 1127
 1128%= 	 	 
 call_mt_f(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8, ?A9) is semidet
Call User Microtheory False.
 1134call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7,A8,A9):- callable_tf(P,9),CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8,A9],xcall_f(CALL).
 1135
 1136%= 	 	 
 call_mt_f(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8) is semidet
Call User Microtheory False.
 1142call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7,A8):- callable_tf(P,8),CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8],xcall_f(CALL).
 1143
 1144%= 	 	 
 call_mt_f(?VALUE1, ?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Call User Microtheory False.
 1150call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6,A7):- callable_tf(P,7),CALL=..[P,A1,A2,A3,A4,A5,A6,A7],xcall_f(CALL).
 1151
 1152%= 	 	 
 call_mt_f(?UPARAM1, :PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Call User Microtheory False.
 1158call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4,A5,A6):- callable_tf(P,6),xcall_f(P,A1,A2,A3,A4,A5,A6).
 1159
 1160%= 	 	 
 call_mt_f(?UPARAM1, :PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Call User Microtheory False.
 1166call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4,A5):- callable_tf(P,5),xcall_f(P,A1,A2,A3,A4,A5).
 1167
 1168%= 	 	 
 call_mt_f(?UPARAM1, :PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Call User Microtheory False.
 1174call_mt_f(dac(_,_,_,mt),P,A1,A2,A3,A4):- callable_tf(P,4),xcall_f(P,A1,A2,A3,A4).
 1175
 1176%= 	 	 
 call_mt_f(?UPARAM1, :PRED3P, ?A1, ?A2, ?A3) is semidet
Call User Microtheory False.
 1182call_mt_f(dac(_,_,_,mt),P,A1,A2,A3):- callable_tf(P,3),xcall_f(P,A1,A2,A3).
 1183
 1184%= 	 	 
 call_mt_f(?UPARAM1, :PRED2P, ?A1, ?A2) is semidet
Call User Microtheory False.
 1190call_mt_f(dac(_,_,_,mt),P,A1,A2):- callable_tf(P,2),xcall_f(P,A1,A2).
 1191
 1192
 1193%= 	 	 
 xcall_f(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8, ?A9) is semidet
Extended Call False.
 1199xcall_f(P,A1,A2,A3,A4,A5,A6,A7,A8,A9):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8,A9],\+ xcall_t(CALL).
 1200
 1201%= 	 	 
 xcall_f(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7, ?A8) is semidet
Extended Call False.
 1207xcall_f(P,A1,A2,A3,A4,A5,A6,A7,A8):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7,A8],\+ xcall_t(CALL).
 1208
 1209%= 	 	 
 xcall_f(?P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7) is semidet
Extended Call False.
 1215xcall_f(P,A1,A2,A3,A4,A5,A6,A7):- CALL=..[P,A1,A2,A3,A4,A5,A6,A7],\+ xcall_t(CALL).
 1216
 1217%= 	 	 
 xcall_f(:PRED6P, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6) is semidet
Extended Call False.
 1223xcall_f(P,A1,A2,A3,A4,A5,A6):- \+ xcall_t(P,A1,A2,A3,A4,A5,A6).
 1224
 1225%= 	 	 
 xcall_f(:PRED5P, ?A1, ?A2, ?A3, ?A4, ?A5) is semidet
Extended Call False.
 1231xcall_f(P,A1,A2,A3,A4,A5):- \+ xcall_t(P,A1,A2,A3,A4,A5).
 1232
 1233%= 	 	 
 xcall_f(:PRED4P, ?A1, ?A2, ?A3, ?A4) is semidet
Extended Call False.
 1239xcall_f(P,A1,A2,A3,A4):- \+ xcall_t(P,A1,A2,A3,A4).
 1240
 1241%= 	 	 
 xcall_f(:PRED3P, ?A1, ?A2, ?A3) is semidet
Extended Call False.
 1247xcall_f(P,A1,A2,A3):- \+ xcall_t(P,A1,A2,A3).
 1248
 1249%= 	 	 
 xcall_f(:PRED2P, ?A1, ?A2) is semidet
Extended Call False.
 1255xcall_f(P,A1,A2):- \+ xcall_t(P,A1,A2).
 1256
 1257%= 	 	 
 xcall_f(:PRED1P, ?A1) is semidet
Extended Call False.
 1263xcall_f(P,A1):- \+ xcall_t(P,A1).
 1264
 1265%= 	 	 
 xcall_f(:GoalP) is semidet
Extended Call False.
 1271xcall_f(P):- \+ xcall_t(P).
 1272
 1273
 1274%= 	 	 
 assertion_f(:TermAH) is semidet
Assertion False.
 1280assertion_f([AH,P|LIST]):- is_holds_true(AH),!,assertion_f([P|LIST]).
 1281assertion_f([AH,P|LIST]):- is_holds_false(AH),!,assertion_f([P|LIST]).
 1282% todo hook into loaded files!
 1283assertion_f(_):- \+(lmcache:loaded_external_kbs(_)),!,fail.
 1284%MAYBE LATER assertion_f([P|LIST]):- 'TINYKB-ASSERTION'(':FALSE-DEF',_,_UniversalVocabularyMt,_Vars,/*HL*/[P|LIST]).
 1285%MAYBE LATER assertion_f([P|LIST]):- 'TINYKB-ASSERTION'(':FALSE-MON',_,_UniversalVocabularyMt,_Vars,/*HL*/[P|LIST]).
 1286
 1287
 1288% ================================================================================
 1289% end holds_f 
 1290% ================================================================================
 1291
 1292:- fixup_exports.