2:- module(common_logic_kb_hooks,
    3 [kbp_t/1,with_el_holds_disabled/1,noGenlPreds/1,cyckb_t/3,link_to_holds2/2,
    4  assert_kif/1, assert_kif_dolce/1,
    5   assert_next_queue/1,
    6  assert_to_db_list/2,
    7  big_kb_ASSERTION/2,
    8  convert_easy_strings/0,
    9  convert_easy_strings2/0,
   10  cyckb_t/1,cyckb_t/2,cyckb_t/3,cyckb_t/4,cyckb_t/5,cyckb_t/6,cyckb_t/7,cyckb_t/8,
   11  cyckb_t_call/1,
   12  cyckb_t_implies/2,
   13  cyckb_t_via_genlPreds/1,
   14  cyckb_t_via_implies/1,
   15  drain_assert_next_buffer/0,
   16  el_holds_DISABLED_KB/0,
   17  get_assertions/2,
   18  get_b_dnf/2,
   19  get_dnf_props/6,
   20  get_props/4,
   21  cycAssert/1,cycAssert/2,
   22  get_varsp/2,
   23  hide_empty_strings/0,
   24  hide_term_rewrites/0,
   25
   26  kb_f/1,
   27  kb_mt/2,
   28  kb_t/1,
   29  kb_t/3,
   30  kbp_t/1,
   31  kbp_t_list/1,
   32  kbp_t_list/2,
   33  kbp_t_list/3,
   34  kbp_t_list_0/3,
   35  kbp_t_list_1/3,
   36  kbp_t_list_prehook/2,
   37  kbp_to_mpred_0/0,
   38  kbp_to_mpred_nomore/0,
   39  kbp_to_mpred_t/0,
   40  link_to_holds/2,
   41  link_to_holds/3,
   42  link_to_holds2/2,
   43  link_to_holds2/3,
   44  link_to_holds_DYNAMIC/2,
   45  link_to_holds_list/2,
   46  
   47  move_implied/0,
   48  move_kb_assertions_matching/4,
   49noGenlPreds/1,
   50  nv1000/1,
   51  proof_from_clause/3,
   52  prove_calllist/3,
   53  tiny_kb_ASSERTION/2,
   54  with_el_holds_disabled/1,
   55  with_el_holds_enabled/1,
   56  with_kb_assertions_matching/3,
   57  write_assertions/0
   58  ]).   59
   60:- include(library('logicmoo/common_logic/common_header.pi')).   61
   62%:- baseKB:ensure_loaded(library(pfc)).
   63
   64% :- dynamic_multifile kbp_t_list_prehook/2.
   65
   66:-
   67  op(1150,fx,(was_export)),
   68  op(1150,fx,(dynamic_multifile)).   69
   70
   71
   72:- dynamic_multifile el_assertions:el_holds/4.
   73:- dynamic_multifile el_assertions:el_holds/5.
   74:- dynamic_multifile el_assertions:el_holds/6.
   75:- dynamic_multifile el_assertions:el_holds/7.
   76:- dynamic_multifile el_assertions:el_holds/8.
   77:- dynamic_multifile el_assertions:el_holds/9.
   78:- dynamic_multifile el_assertions:el_holds/10.
   79:- dynamic_multifile el_assertions:el_holds/11.
   80:- dynamic_multifile el_assertions:el_holds/12.
   81:- dynamic_multifile el_assertions:el_holds/13.
   82:- dynamic_multifile el_assertions:el_holds/14.
   83
   84:- meta_predicate with_kb_assertions_matching(?,?,0).   85
   86:- dynamic_multifile(el_assertions:el_holds_pred_impl/1).   87%:- dynamic_multifile is_cyckb_t_pred/2.
   88:- dynamic_multifile el_assertions:el_holds_pred_impl/1.
   89%:- dynamic_multifile el_assertions:is_cyckb_t_pred/2.
   90:- dynamic cyckb_t/3.   91
   92:- was_export(kbp_t/1). 
   93
   94:- set_how_virtualize_file(bodies).
 assert_kif(?String) is det
Assert Knowledge Interchange Format.
  101assert_kif(D):- ain(clif(D)).
 assert_kif_dolce(?String) is det
Assert Knowledge Interchange Format Dolce.
  107assert_kif_dolce(String):-input_to_forms(String,Forms,_Vars),dmsg(warn(assert_kif_dolce(Forms))),!,assert_kif(Forms).
  108
  109cycAssert(O):-assert_kif(O).
  110cycAssert(O,Mt):-assert_kif(Mt:O).
  111
  112%= 	 	 
 kbp_t(?VALUE1) is semidet
Knowledge Base P- True Stucture.
  118kbp_t(_):- \+ lmcache:loaded_external_kbs(_),!,fail.
  119% kbp_t(PLIST):- ground(PLIST),!,no_repeats(call_no_cuts(kbp_t_list_prehook(PLIST,PLISTO))),kbp_t_list(PLISTO).
  120% kbp_t(PLIST):- kbp_t_list_prehook(PLIST,PLISTO),kbp_t_list(PLISTO).
  121% TODO RE-ENABLE 
  122% kbp_t(PLIST):- kbp_t_list(PLIST). % append(PLIST,[_MT,_PROOF],PLISTO), apply(el_assertions:el_holds,PLISTO).  % el_assertions:el_holds has 2 extra args our callers shouldnt be forced to use.. but this is a big slowdown
  123
  124
  125:- was_export(kb_f/1).  126
  127%= 	 	 
 kb_f(?X) is semidet
Knowledge Base False.
  133kb_f(X):- assertion_f(X).
  134
  135
  136
  137%= 	 	 
 get_b_dnf(?DNFA, ?DNFAO) is semidet
Get Backtackable Disjunctive Normal Form.
  143get_b_dnf([DNFA],DNFA):-!.
  144get_b_dnf(DNFA,DNFAO):- length(DNFA,L),atom_concat(and,L,Pred),!,DNFAO=..[Pred|DNFA].
  145
  146
  147%= 	 	 
 get_dnf_props(?TRUTH, ?VALUE2, ?DNFC, ?VARS, ?MT, :TermDNFCO) is semidet
Get Disjunctive Normal Form Props.
  153get_dnf_props(TRUTH,[],DNFC,VARS,MT,[dnf(c,DNFCO)|PROPS]):-!,get_props(TRUTH,VARS,MT,PROPS),get_b_dnf(DNFC,DNFCO).
  154get_dnf_props(TRUTH,DNFA,[],VARS,MT,[dnf(a,DNFAO)|PROPS]):-!,get_props(TRUTH,VARS,MT,PROPS),get_b_dnf(DNFA,DNFAO).
  155get_dnf_props(TRUTH,DNFA,DNFC,VARS,MT,[dnf(ca,(DNFCO<DNFAO))|PROPS]):-!,get_props(TRUTH,VARS,MT,PROPS),get_b_dnf(DNFC,DNFCO),get_b_dnf(DNFA,DNFAO).
  156
  157
  158%= 	 	 
 get_props(?TRUTH, ?VARS, ?VALUE3, :TermVARSP) is semidet
Get Props.
  164get_props(TRUTH,VARS,isMissing,VARSP):-!,get_props(TRUTH,VARS,notmissing,[_|VARSP]),!.
  165get_props(':TRUE-DEF',VARS,MT,[amt(MT),str(':DEFAULT'),truth(':TRUE')|VARSP]):-get_varsp(VARS,VARSP),!.
  166get_props(':FALSE-DEF',VARS,MT,[amt(MT),str(':DEFAULT'),truth(':FALSE')|VARSP]):-get_varsp(VARS,VARSP),!.
  167get_props(':TRUE-MON',VARS,MT,[amt(MT),str(':MONOTONIC'),truth(':TRUE')|VARSP]):-get_varsp(VARS,VARSP),!.
  168get_props(':FALSE-MON',VARS,MT,[amt(MT),str(':MONOTONIC'),truth(':FALSE')|VARSP]):-get_varsp(VARS,VARSP),!.
  169
  170%= 	 	 
 get_varsp(?VARS, ?VARS) is semidet
Get Varsp.
  176get_varsp([],[]):-!.
  177get_varsp(VARS,[vars(VARS)]):-!.
  178
  179
  180%= 	 	 
 tiny_kb_ASSERTION(?PLIST, ?PROPS) is semidet
Tiny Knowledge Base Assertion.
  186tiny_kb_ASSERTION(_PLIST,_PROPS):-!,fail.
  187%MAYBE LATER tiny_kb_ASSERTION(PLIST,PROPS):- 'TINYKB-ASSERTION'(TRUTH,[DNFA,DNFC],MT,VARS,PLIST),get_dnf_props(TRUTH,DNFA,DNFC,VARS,MT,PROPS).
  188%MAYBE LATER tiny_kb_ASSERTION(PLIST,PROPS):- 'TINYKB-ASSERTION'(TRUTH,[DNFA,DNFC],MT,VARS,_HL,PLIST),get_dnf_props(TRUTH,DNFA,DNFC,VARS,MT,PROPS).
  189
  190%big_kb_ASSERTION(PLIST,[dir(DIR),refcl(A1437)|PROPS]):- 'ASSERTION'(TRUTH, DNF, MT, VARS, A1437, DIR),dnf_to_pnf(DNF,PLIST),get_props(TRUTH,VARS,MT,PROPS).
  191%big_kb_ASSERTION(PLIST,[dir(DIR),refcl(A1437)|PROPS]):- 'ASSERTION'(TRUTH, _DNF, MT, VARS, A1437, DIR,_,PLIST),get_props(TRUTH,VARS,MT,PROPS).
  192%big_kb_ASSERTION(PLIST,[dir(DIR),refcl(A1437)|PROPS]):- 'ASSERTION'(TRUTH, _DNF, MT, VARS, A1437, DIR,PLIST),get_props(TRUTH,VARS,MT,PROPS).
  193
  194%= 	 	 
 big_kb_ASSERTION(?VALUE1, ?VALUE2) is semidet
Big Knowledge Base Assertion.
  200big_kb_ASSERTION(_,_):-fail.
  201
  202:- was_export(get_assertions/2).  203% get_assertions(PLIST,PROPS):-big_kb_ASSERTION(PLISTIn,PROPS),nv1000(PLISTIn-PROPS),fix_sentence(PLISTIn,PLIST).
  204
  205%= 	 	 
 get_assertions(?PLIST, ?PROPS) is semidet
Get Assertions.
  211get_assertions(PLIST,PROPS):-current_predicate(tiny_kb_ASSERTION/2),!,tiny_kb_ASSERTION(PLISTIn,PROPS),nv1000(PLISTIn-PROPS),fix_sentence(PLISTIn,PLIST).
  212get_assertions(PLIST,PROPS):-between(2,19,X),length(PLISTIn,X),kbp_t_list(PLISTIn,PROPS,_),nv1000(PLISTIn-PROPS),fix_sentence(PLISTIn,PLIST).
  213
  214
  215
  216%= 	 	 
 nv1000(?S) is semidet
Nv Secondary Helper Primary Helper Primary Helper Primary Helper.
  222nv1000(S):-numbervars(S,100,_,[singletons(true),attvar(bind)]).
  223
  224
  225% length(SENT,N),N>1,append(SENT,[MT,Props],PLIST),apply(el_assertions:el_holds,PLIST),member(Var,SENT),var(Var).
  226% length(SENT,N),N>1,kbp_t_list(SENT,Proof),member(Var,SENT),var(Var).
  227
  228:- was_export((kb_t/1)).  229
  230%= 	 	 
 kb_t(?Call) is semidet
Knowledge Base True Stucture.
  236kb_t(Call):- into_plist(Call,PLIST),[AH|LIST]=PLIST,!, kb_t(AH,LIST,PLIST).
  237
  238
  239
  240%= 	 	 
 kb_t(?AH, ?VALUE2, ?PLIST) is semidet
Knowledge Base True Stucture.
  246kb_t(AH,_,PLIST):-var(AH),!,kbp_t(PLIST).
  247kb_t(t,PLIST,_):- !,kbp_t(PLIST).  % t is our versuion of '$holds' or call/N
  248kb_t(genls,PLIST,_):- !,kbp_t([genls|PLIST]). % rewrite hack for SUMO callers
  249kb_t(AH,PLIST,_):- is_holds_true(AH),!,kb_t(PLIST). % is_holds_true/1 is temp disabled for speed
  250kb_t(AH,PLIST,_):- is_holds_false(AH),!,kb_f(PLIST). % is_holds_false(not).
  251kb_t(_,_,PLIST):- kbp_t(PLIST).
  252
  253
  254:- was_export(link_to_holds2/2).  255
  256%= 	 	 
 link_to_holds2(?Pred, ?TargetPred) is semidet
Link Converted To Holds Extended Helper.
  262link_to_holds2(Pred,Target:TPred):- !,link_to_holds2(Pred,Target,TPred).
  263link_to_holds2(Pred,TargetPred):- !,link_to_holds2(Pred,user,TargetPred).
  264
  265
  266%= 	 	 
 link_to_holds2(?Pred, ?M, ?TargetPred) is semidet
Link Converted To Holds Extended Helper.
  272link_to_holds2(Pred,M,TargetPred):- 
  273  forall(between(2,12,X),((length(PLIST,X),append(PLIST,[_MT],PLISTMT),append(PLISTMT,[_PROOF],PLISTMTPROOF), 
  274   export(Pred/X),  
  275 % X2 is X + 2, nop(export(TargetPred/X2)),  
  276  A=..[Pred|PLIST],
  277  B=..[TargetPred|PLISTMTPROOF],  
  278   assertz_if_new((A :- (M:B) ))))).
  279
  280:- was_export(link_to_holds/2).  281
  282%= 	 	 
 link_to_holds(?Pred, ?TargetPred) is semidet
Link Converted To Holds.
  288link_to_holds(Pred,Target:TPred):- !,link_to_holds(Pred,Target,TPred).
  289link_to_holds(Pred,TargetPred):- !,link_to_holds(Pred,user,TargetPred).
  290
  291%= 	 	 
 link_to_holds(?Pred, ?M, ?TargetPred) is semidet
Link Converted To Holds.
  297link_to_holds(Pred,M,TargetPred):- 
  298  doall((between(2,12,X),length(PLIST,X),
  299   export(Pred/X),  
  300   nop(export(TargetPred/X)),  
  301  A=..[Pred|PLIST],
  302  B=..[TargetPred|PLIST],  
  303   assertz_if_new((A:- M:B)))).
  304
  305:- was_export(link_to_holds_DYNAMIC/2).  306
  307%= 	 	 
 link_to_holds_DYNAMIC(?Pred, ?TargetPred) is semidet
Link Converted To Holds Dynamic.
  313link_to_holds_DYNAMIC(Pred,TargetPred):- 
  314  doall((between(2,12,X),length(PLIST,X),
  315   export(Pred/X),  
  316   export(TargetPred/X),  
  317  A=..[Pred|PLIST],
  318  B=..[TargetPred|PLIST],  
  319   assertz_if_new((A:-B)))).
  320:- was_export(link_to_holds_list/2).  321
  322%= 	 	 
 link_to_holds_list(?Pred, ?TargetPred) is semidet
Link Converted To Holds List.
  328link_to_holds_list(Pred,TargetPred):- 
  329  doall((between(2,12,X),length(PLIST,X),
  330   export(Pred/X),  
  331   export(TargetPred/1),  
  332  A=..[Pred|PLIST],
  333  B=..[TargetPred,PLIST],  
  334   assertz_if_new((A:-B)))).
  335
  336
  337/*
  338cyckb_t(P,A1,A2,A3,A4,A5,A6,A7):- t([P,A1,A2,A3,A4,A5,A6,A7]).
  339cyckb_t(P,A1,A2,A3,A4,A5,A6):- t([P,A1,A2,A3,A4,A5,A6]).
  340cyckb_t(P,A1,A2,A3,A4,A5):- t([P,A1,A2,A3,A4,A5]).
  341cyckb_t(P,A1,A2,A3,A4):- t([P,A1,A2,A3,A4]).
  342cyckb_t(P,A1,A2,A3):- t([P,A1,A2,A3]).
  343cyckb_t(P,A1,A2):- t([P,A1,A2]).
  344cyckb_t(P,A1):- t([P,A1]).
  345*/
  346
  347:- dynamic_multifile(el_holds_DISABLED_KB/0).  348:- was_export(el_holds_DISABLED_KB/0).  349:- asserta(el_holds_DISABLED_KB).  350
  351
  352%= 	 	 
 with_el_holds_enabled(:Goal) is semidet
Using El Holds Enabled.
  358:- meta_predicate(with_el_holds_enabled(0)).  359with_el_holds_enabled(Goal):-locally_hide(el_holds_DISABLED_KB,Goal).
  360
  361%= 	 	 
 with_el_holds_disabled(:Goal) is semidet
Using El Holds Disabled.
  367:- meta_predicate(with_el_holds_disabled(0)).  368with_el_holds_disabled(Goal):-locally(el_holds_DISABLED_KB,Goal).
  369
  370%:- link_to_holds_DYNAMIC(cyckb_t,el_holds_DISABLED_KB).
  371:- link_to_holds2(cyckb_t,el_assertions:el_holds).  372
  373:- was_export(cyckb_t/1).  374
  375%= 	 	 
 cyckb_t(?Compound) is semidet
Cyckb True Stucture.
  381cyckb_t([P|LIST]):-!, \+ (el_holds_DISABLED_KB), apply(cyckb_t,[P|LIST]).
  382cyckb_t(Compound):- \+ (el_holds_DISABLED_KB), Compound=..[F,A|List] , apply(cyckb_t,[F,A|List]).
  383
  384:- was_export(noGenlPreds/1).  385
  386%= 	 	 
 noGenlPreds(?X) is semidet
No Genl Predicates.
  392noGenlPreds(coGenlPreds).
  393noGenlPreds(isa).
  394noGenlPreds(genls).
  395noGenlPreds(X):-not(atom(X)),!.
  396noGenlPreds(_).
  397
  398:- link_to_holds_list(cyckb_t,cyckb_t_via_genlPreds).  399
  400%= 	 	 
 cyckb_t_via_genlPreds(:TermGP) is semidet
Cyckb True Structure Via Genl Predicates.
  406cyckb_t_via_genlPreds([GP|_]):- noGenlPreds(GP),!,fail.
  407cyckb_t_via_genlPreds([GP,A,B]):- loop_check(cyckb_t(genlInverse,P,GP)), P\=GP, loop_check(cyckb_t([P,B,A])).
  408cyckb_t_via_genlPreds([GP|LIST]):- loop_check(cyckb_t(genlPreds,P,GP)), P\=GP, loop_check(cyckb_t([P|LIST])).
  409
  410
  411:- link_to_holds_list(cyckb_t,cyckb_t_via_implies).  412
  413%= 	 	 
 cyckb_t_via_implies(?CONSEQ) is semidet
Cyckb True Structure Via Implies.
  419cyckb_t_via_implies(CONSEQ):- fail, loop_check(cyckb_t_implies(ANTE,CONSEQ)), loop_check(cyckb_t_call(ANTE)).
  420
  421
  422%= 	 	 
 cyckb_t_call(?ANTE) is semidet
Cyckb True Structure Call.
  428cyckb_t_call(ANTE):- nop(cyckb_t_call(ANTE)),!,fail.
  429
  430%= 	 	 
 cyckb_t_implies(?ANTE, ?CONSEQ) is semidet
Cyckb True Structure Implies.
  436cyckb_t_implies(ANTE,CONSEQ):- nop(cyckb_t_implies(ANTE,CONSEQ)),!,fail.
  437
  438:- thread_local t_l:useDbase_t/0.  439
  440
  441%= 	 	 
 kbp_t_list_prehook(?PLIST, ?PLIST) is semidet
Knowledge Base P- True Structure List Prehook.

:- kb_shared(kbp_t_list_prehook/2).

  448kbp_t_list_prehook(PLIST,PLIST).
  449
  450:- was_export(kbp_t_list/1). 
  451
  452%= 	 	 
 kbp_t_list(?PLIST) is semidet
Knowledge Base P- True Structure List.
  459kbp_t_list(PLIST):- t_l:useDbase_t, call_u(t(PLIST)).
  460kbp_t_list(PLIST):- apply(cyckb_t,PLIST).
  461
  462
  463:- was_export(kbp_t_list/2). 
  464% kbp_t_list(PLIST,t(PLIST)):- t_l:useDbase_t,  t(PLIST).
  465
  466%= 	 	 
 kbp_t_list(?PLIST, ?Proof) is semidet
Knowledge Base P- True Structure List.
  472kbp_t_list(PLIST,Proof):- kbp_t_list(PLIST,_A,Proof).
  473
  474% 
  475%  current_predicate(F/A),functor(P,F,A),predicate_property(P,number_of_clauses(N)),dif(B,true), clause(P, B, Ref),B\=(!,_), B=true.
  476
  477:- was_export(kbp_t_list/3). 
  478kbp_t_list(PLIST,Props):- tiny_kb_ASSERTION(PLIST,Props).
  479
  480%= 	 	 
 kbp_t_list(?PLIST, ?Props, ?Proof) is semidet
Knowledge Base P- True Structure List.
  486kbp_t_list(PLIST,[amt(t)],Proof):- t_l:useDbase_t,  CallList = [t|PLIST],Call=..CallList,/*Call,*/ clause(Call,true,Ref),clause(Head, Body, Ref),proof_from_clause(Head, Body, Proof).
  487kbp_t_list(PLIST,Props,Proof):- is_list(PLIST),!,kbp_t_list_1(PLIST,Props,Proof).
  488kbp_t_list(PLIST,Props,Proof):- kbp_t_list_0(PLIST,Props,Proof).
  489
  490
  491%= 	 	 
 kbp_t_list_0(?PLIST, ?Props, ?Proof) is semidet
Knowledge Base P- True Structure list Primary Helper.
  497kbp_t_list_0(PLIST,Props,Proof):- between(3,2,N), length(PLIST,N),kbp_t_list_1(PLIST,Props,Proof).
  498kbp_t_list_0(PLIST,Props,Proof):- between(4,12,N), length(PLIST,N),kbp_t_list_1(PLIST,Props,Proof).
  499
  500
  501%= 	 	 
 kbp_t_list_1(?PLIST, :TermMT, ?Proof) is semidet
Knowledge Base P- True Structure list Secondary Helper.
  507kbp_t_list_1(PLIST,[amt(MT)|PropsV], Proof):- append(PLIST,[MT,PropsV],CallList),!,prove_calllist(el_assertions:el_holds,CallList,Proof).
  508% kbp_t_list_1(PLIST,[cyckb_t], Proof):- CallList = [cyckb_t|PLIST],prove_calllist(cyckb_t,CallList,Proof).
  509
  510
  511%= 	 	 
 prove_calllist(?Functor, ?CallList, ?Proof) is semidet
Prove Calllist.
  517prove_calllist(Functor,CallList,Proof):- Call =.. [Functor|CallList], clause(Call, true,Ref),clause(PHead, PBody, Ref),proof_from_clause(PHead, PBody, Proof).
  518prove_calllist(Functor,CallList,Proof):- dif(Body,true), Head =.. [Functor|CallList],clause(Head, Body, Ref),must_det(not(Body=true)),Body,clause(PHead, PBody, Ref),proof_from_clause(PHead, PBody, Proof).
  519
  520:- was_export(kb_mt/2).  521
  522%= 	 	 
 kb_mt(?C, ?MT) is semidet
Knowledge Base User Microtheory.
  528kb_mt(C,MT):- into_plist(C,PLIST),!,  append([el_assertions:el_holds|PLIST],[MT,_PropsV],CallList),Call=..CallList,Call.
  529kb_mt(C,t):- t_l:useDbase_t, call_u(t(C)).
  530
  531
  532
  533
  534%= 	 	 
 proof_from_clause(?Head, ?VALUE2, ?Head) is semidet
Proof Converted From Clause.
  540proof_from_clause(Head, true, Head):-!.
  541proof_from_clause(Head, Body, ((Head:- Body))).
  542
  543:- dynamic assert_next_queue/1.  544:- export(assert_next_queue/1).  545
  546:- was_export(move_kb_assertions_matching/4).  547
  548%= 	 	 
 move_kb_assertions_matching(?PLIST, ?Match, ?Replace, ?Where) is semidet
Move Knowledge Base Assertions Matching.
  554move_kb_assertions_matching(PLIST,Match,Replace,Where):- 
  555% dmsg(move_kb_assertions_matching(PLIST,Match,Replace,to(Where))),
  556  doall((kbp_t_list(PLIST,Call),
  557   forall(retract(Call),
  558   (subst(PLIST:Call,Match,Replace,NewPLIST:NewCall),
  559   assert_to_db_list(Where,[rewrite,NewPLIST,NewCall]))))).
  560
  561
  562
  563%= 	 	 
 assert_to_db_list(?HOLDS, ?PLIST) is semidet
Assert Converted To Database List.
  569assert_to_db_list(HOLDS,PLIST):- safe_univ(Call,[HOLDS|PLIST]), assert(assert_next_queue(Call)).
  570
  571
  572
  573%= 	 	 
 with_kb_assertions_matching(?PLIST, ?Proof, :Goal) is semidet
Using Knowledge Base Assertions Matching.
  579with_kb_assertions_matching(PLIST,Proof,Call):- doall((kbp_t_list(PLIST, Proof),Call)).
  580 
  581:- was_export(kbp_to_mpred_t/0).  582
  583%= 	 	 
 kbp_to_mpred_t is semidet
Knowledge Base P- Converted To Managed Predicate True Stucture.
  589kbp_to_mpred_t:- must_det(locally_tl(useOnlyExternalDBs,kbp_to_mpred_0)).
  590
  591
  592%= 	 	 
 kbp_to_mpred_0 is semidet
Knowledge Base P- Converted To Managed Predicate Primary Helper.
  598kbp_to_mpred_0:-!.
  599% kbp_to_mpred_0:- once(time_call(move_implied)),fail.
  600kbp_to_mpred_0:- once(time_call(hide_term_rewrites)),fail.
  601kbp_to_mpred_0:- once(time_call(hide_empty_strings)),fail.
  602% kbp_to_mpred_0:- once(time_call(convert_easy_strings)),fail.
  603% kbp_to_mpred_0:- once(time_call(convert_easy_strings2)),fail.
  604kbp_to_mpred_0:- time_call(drain_assert_next_buffer),!.
  605
  606
  607%= 	 	 
 kbp_to_mpred_nomore is semidet
Knowledge Base P- Converted To Managed Predicate No More.
  613kbp_to_mpred_nomore:- forall((into_plist(_Call,PLIST),kbp_t(PLIST)),assert_to_db_list(_F,PLIST)),
  614 retractall(baseKB:use_cyc_database),tell('a.txt'),listing(t),listing('ASSERTION'),told,dmsg(done_mpred_t).
  615
  616
  617:- was_export(move_implied/0).  618
  619%= 	 	 
 move_implied is semidet
Move Implied.
  625move_implied:-doall((between(2,6,Len),length(PLIST,Len), 
  626   Call=..[assertion_holds,implied|PLIST],
  627   retract(hl_holds:Call),
  628   append(ALIST,[Last],PLIST),NewCall=..[assertion_holds,impliedBy,ALIST,Last],
  629   assert(assert_next_queue(hl_holds:NewCall)))),
  630   drain_assert_next_buffer.
  631
  632:- was_export(hide_term_rewrites/0).  633
  634%= 	 	 
 hide_term_rewrites is semidet
Hide Term Rewrites.
  640hide_term_rewrites :- locally_tl(useOnlyExternalDBs,
  641 % remove badjuju from the KB (that is unbould slots in the middle of GAFs)
  642 % hl_holds:retractall(assertion_holds(isa, badjuju, 'Thing')),
  643 % hl_holds:retractall(el_assertions:el_holds(genls, badjuju, 'AerosolStuff',_,_)), 
  644 % hl_holds:retractall(assertion_holds(genls, badjuju, 'BiologicalAgentStuff')), 
  645 % the next few lines will cover the top
  646 doall((between(2,6,Len),length(PLIST,Len),
  647 forall(member(vvvar,PLIST),move_kb_assertions_matching(PLIST,vvvar,_,term_rewrites_kb))))),
  648 drain_assert_next_buffer.
  649
  650:- was_export(hide_empty_strings/0).  651
  652%= 	 	 
 hide_empty_strings is semidet
Hide Empty Strings.
  658hide_empty_strings :- locally_tl(useOnlyExternalDBs,
  659 % remove more badjuju from the KB (that is unbould slots in the middle of GAFs)
  660 % the next few lines will cover the top
  661 doall((between(2,6,Len),length(PLIST,Len),
  662 forall(member('',PLIST),move_kb_assertions_matching(PLIST,'','',term_rewrites_kb))))),
  663 drain_assert_next_buffer.
  664
  665
  666:- was_export(convert_easy_strings/0).  667
  668%= 	 	 
 convert_easy_strings is semidet
Convert Easy Strings.
  674convert_easy_strings:-
  675 doall((between(2,6,Len),length(PLIST,Len),
  676 forall(member(string(_),PLIST),
  677  time_call(with_kb_assertions_matching(PLIST,Proof,must_det(print_sentence(Proof))))))),drain_assert_next_buffer.
  678
  679
  680%= 	 	 
 convert_easy_strings2 is semidet
Convert Easy Strings Extended Helper.
  686convert_easy_strings2:-
  687 doall((between(2,6,Len),length(PLIST,Len),
  688 forall(member([_|_],PLIST),
  689  time_call(with_kb_assertions_matching(PLIST,Proof,must_det(print_sentence(Proof))))))),drain_assert_next_buffer.
  690
  691
  692%= 	 	 
 drain_assert_next_buffer is semidet
Drain Assert Next Buffer.
  698drain_assert_next_buffer:- predicate_property(assert_next_queue(_),number_of_clauses(CL)),dmsg(drain_assert_next_buffer(CL)),
  699 time_call(doall((retract(assert_next_queue(Call)),asserta_if_new(Call)))).
  700
  701
  702%= 	 	 
 write_assertions is semidet
Write Assertions.
  708write_assertions:-
  709 tell(holds_all),
  710 listing(assertion_holds_mworld0),
  711 listing(assertion_holds),
  712 listing(term_rewrites_kb),
  713 told.
  714
  715:- fixup_exports.